summaryrefslogtreecommitdiff
path: root/gnu/packages/patches
diff options
context:
space:
mode:
authorLars-Dominik Braun <lars@6xq.net>2023-01-15 10:09:44 +0100
committerLars-Dominik Braun <lars@6xq.net>2023-02-26 10:26:07 +0100
commit49a320aaa6fb4c20d6b30c56c35a8c7ffceed822 (patch)
tree3b05df103e8fbccfcab2011dca32adbb43bf01b9 /gnu/packages/patches
parent9262c14d73b4b216bb9c1f76fb6b3a9709da1de3 (diff)
Upgrade Haskell packages.
Script-aided bulk change.
Diffstat (limited to 'gnu/packages/patches')
-rw-r--r--gnu/packages/patches/cabal-install-base16-bytestring1.0.patch29
-rw-r--r--gnu/packages/patches/cabal-install-ghc8.10.patch393
-rw-r--r--gnu/packages/patches/ghc-bloomfilter-ghc9.2.patch303
-rw-r--r--gnu/packages/patches/ghc-bytestring-handle-ghc9.patch67
-rw-r--r--gnu/packages/patches/ngless-unliftio.patch66
-rw-r--r--gnu/packages/patches/xmonad-dynamic-linking.patch24
-rw-r--r--gnu/packages/patches/xmonad-next-dynamic-linking.patch16
7 files changed, 382 insertions, 516 deletions
diff --git a/gnu/packages/patches/cabal-install-base16-bytestring1.0.patch b/gnu/packages/patches/cabal-install-base16-bytestring1.0.patch
deleted file mode 100644
index 998bf08718..0000000000
--- a/gnu/packages/patches/cabal-install-base16-bytestring1.0.patch
+++ /dev/null
@@ -1,29 +0,0 @@
-Restore compatibility with newer version of base16-bytestring.
-
-Taken from https://raw.githubusercontent.com/archlinux/svntogit-community/packages/trunk/cabal-install-base16-bytestring1.0.patch
-
-diff --git a/Distribution/Client/HashValue.hs b/Distribution/Client/HashValue.hs
-index 54b8aee9e..11e647c1c 100644
---- a/Distribution/Client/HashValue.hs
-+++ b/Distribution/Client/HashValue.hs
-@@ -1,3 +1,4 @@
-+{-# LANGUAGE CPP #-}
- {-# LANGUAGE DeriveDataTypeable #-}
- {-# LANGUAGE DeriveGeneric #-}
- module Distribution.Client.HashValue (
-@@ -72,10 +73,14 @@ hashFromTUF (Sec.Hash hashstr) =
- --TODO: [code cleanup] either we should get TUF to use raw bytestrings or
- -- perhaps we should also just use a base16 string as the internal rep.
- case Base16.decode (BS.pack hashstr) of
-+#if MIN_VERSION_base16_bytestring(1,0,0)
-+ Right hash -> HashValue hash
-+ Left _ -> error "hashFromTUF: cannot decode base16"
-+#else
- (hash, trailing) | not (BS.null hash) && BS.null trailing
- -> HashValue hash
- _ -> error "hashFromTUF: cannot decode base16 hash"
--
-+#endif
-
- -- | Truncate a 32 byte SHA256 hash to
- --
diff --git a/gnu/packages/patches/cabal-install-ghc8.10.patch b/gnu/packages/patches/cabal-install-ghc8.10.patch
deleted file mode 100644
index 67c0953058..0000000000
--- a/gnu/packages/patches/cabal-install-ghc8.10.patch
+++ /dev/null
@@ -1,393 +0,0 @@
-From ac9b41eef3c781ce188ded2551f98fe75152e30c Mon Sep 17 00:00:00 2001
-From: Oleg Grenrus <oleg.grenrus@iki.fi>
-Date: Tue, 14 Apr 2020 11:31:34 +0300
-Subject: [PATCH] GHC-8.10 support for 3.2
-
-Includes cherry-picked commits:
-
-- Test cabal-install with GHC-8.10 #6709
-- Add GHC-8.10.1 job. Only tests Cabal-the-lib part atm. #6617
-
-Also add topHandler' signature.
----
- .docker/validate-8.10.1.dockerfile | 60 ++++++
- .github/workflows/artifacts.yml | 6 +-
- .github/workflows/bootstrap.yml | 4 +-
- .github/workflows/linux.yml | 179 ++++++++++++------
- .github/workflows/macos.yml | 40 ++--
- .github/workflows/quick-jobs.yml | 4 +-
- .github/workflows/windows.yml | 117 +++++++++++-
- .../Distribution/PackageDescription/Quirks.hs | 19 +-
- Makefile | 4 +
- boot/ci-artifacts.template.yml | 6 +-
- boot/ci-bootstrap.template.yml | 4 +-
- boot/ci-linux.template.yml | 8 +-
- boot/ci-macos.template.yml | 7 +-
- boot/ci-quick-jobs.template.yml | 4 +-
- boot/ci-windows.template.yml | 8 +-
- cabal-dev-scripts/src/GenValidate.hs | 33 ++--
- Distribution/Client/CmdSdist.hs | 3 +
- .../Distribution/Client/FetchUtils.hs | 4 +-
- .../Distribution/Client/IndexUtils.hs | 2 +-
- Distribution/Client/Sandbox.hs | 5 +-
- .../Distribution/Client/TargetSelector.hs | 2 +-
- Distribution/Client/Update.hs | 4 +-
- .../Distribution/Client/Utils/Json.hs | 13 +-
- .../Distribution/Solver/Modular/Assignment.hs | 11 +-
- .../Distribution/Solver/Modular/Builder.hs | 10 +-
- .../Distribution/Solver/Modular/Index.hs | 6 +-
- .../Solver/Modular/IndexConversion.hs | 8 +-
- .../Distribution/Solver/Modular/Solver.hs | 12 +-
- .../Distribution/Solver/Modular/Validate.hs | 5 +-
- bootstrap.sh | 6 +-
- cabal-install.cabal | 4 +-
- cabal-install.cabal.pp | 4 +-
- .../targets/complex/q/q.cabal | 3 +-
- cabal-testsuite/cabal-testsuite.cabal | 4 +-
- validate.sh | 21 +-
- 35 files changed, 461 insertions(+), 169 deletions(-)
- create mode 100644 .docker/validate-8.10.1.dockerfile
-diff --git a/Distribution/Client/CmdSdist.hs b/Distribution/Client/CmdSdist.hs
-index 9ce0c80100e..a22317004c4 100644
---- a/Distribution/Client/CmdSdist.hs
-+++ b/Distribution/Client/CmdSdist.hs
-@@ -237,7 +237,10 @@ packageToSdist verbosity projectRootDir format outputFile pkg = do
- (norm NoExec -> nonexec, norm Exec -> exec) <-
- listPackageSources verbosity (flattenPackageDescription $ packageDescription pkg) knownSuffixHandlers
-
-+ print $ map snd exec
-+ print $ map snd nonexec
- let files = nub . sortOn snd $ nonexec ++ exec
-+ print files
-
- case format of
- SourceList nulSep -> do
-diff --git a/Distribution/Client/FetchUtils.hs b/Distribution/Client/FetchUtils.hs
-index e9a31a91f84..4e5e581f9ec 100644
---- a/Distribution/Client/FetchUtils.hs
-+++ b/Distribution/Client/FetchUtils.hs
-@@ -176,8 +176,8 @@ fetchRepoTarball verbosity' repoCtxt repo pkgid = do
- verbosity = verboseUnmarkOutput verbosity'
-
- downloadRepoPackage = case repo of
-- RepoLocal{..} -> return (packageFile repo pkgid)
-- RepoLocalNoIndex{..} -> return (packageFile repo pkgid)
-+ RepoLocal{} -> return (packageFile repo pkgid)
-+ RepoLocalNoIndex{} -> return (packageFile repo pkgid)
-
- RepoRemote{..} -> do
- transport <- repoContextGetTransport repoCtxt
-diff --git a/Distribution/Client/IndexUtils.hs b/Distribution/Client/IndexUtils.hs
-index a76becc05ba..bf0ff7cf5ba 100644
---- a/Distribution/Client/IndexUtils.hs
-+++ b/Distribution/Client/IndexUtils.hs
-@@ -634,7 +634,7 @@ withIndexEntries
- -> ([IndexCacheEntry] -> IO a)
- -> ([NoIndexCacheEntry] -> IO a)
- -> IO a
--withIndexEntries _ (RepoIndex repoCtxt repo@RepoSecure{..}) callback _ =
-+withIndexEntries _ (RepoIndex repoCtxt repo@RepoSecure{}) callback _ =
- repoContextWithSecureRepo repoCtxt repo $ \repoSecure ->
- Sec.withIndex repoSecure $ \Sec.IndexCallbacks{..} -> do
- -- Incrementally (lazily) read all the entries in the tar file in order,
-diff --git a/Distribution/Client/Sandbox.hs b/Distribution/Client/Sandbox.hs
-index 66b415d7239..14bad3f2135 100644
---- a/Distribution/Client/Sandbox.hs
-+++ b/Distribution/Client/Sandbox.hs
-@@ -666,7 +666,7 @@ reinstallAddSourceDeps :: Verbosity
- -> FilePath
- -> IO WereDepsReinstalled
- reinstallAddSourceDeps verbosity configFlags' configExFlags
-- installFlags globalFlags sandboxDir = topHandler' $ do
-+ installFlags globalFlags sandboxDir = topHandlerWith errorMsg $ do
- let sandboxDistPref = sandboxBuildDir sandboxDir
- configFlags = configFlags'
- { configDistPref = Flag sandboxDistPref }
-@@ -710,7 +710,8 @@ reinstallAddSourceDeps verbosity configFlags' configExFlags
- ++ "offending packages or recreating the sandbox."
- logMsg message rest = debugNoWrap verbosity message >> rest
-
-- topHandler' = topHandlerWith $ \_ -> do
-+ errorMsg :: a -> IO WereDepsReinstalled
-+ errorMsg _ = do
- warn verbosity "Couldn't reinstall some add-source dependencies."
- -- Here we can't know whether any deps have been reinstalled, so we have
- -- to be conservative.
-diff --git a/Distribution/Client/TargetSelector.hs b/Distribution/Client/TargetSelector.hs
-index 23d92f580fd..f8f683d9875 100644
---- a/Distribution/Client/TargetSelector.hs
-+++ b/Distribution/Client/TargetSelector.hs
-@@ -222,7 +222,7 @@ readTargetSelectorsWith :: (Applicative m, Monad m) => DirActions m
- -> Maybe ComponentKindFilter
- -> [String]
- -> m (Either [TargetSelectorProblem] [TargetSelector])
--readTargetSelectorsWith dirActions@DirActions{..} pkgs mfilter targetStrs =
-+readTargetSelectorsWith dirActions@DirActions{} pkgs mfilter targetStrs =
- case parseTargetStrings targetStrs of
- ([], usertargets) -> do
- usertargets' <- mapM (getTargetStringFileStatus dirActions) usertargets
-diff --git a/Distribution/Client/Update.hs b/Distribution/Client/Update.hs
-index 52bb1f76c96..8ded78b9d2e 100644
---- a/Distribution/Client/Update.hs
-+++ b/Distribution/Client/Update.hs
-@@ -73,8 +73,8 @@ updateRepo :: Verbosity -> UpdateFlags -> RepoContext -> Repo -> IO ()
- updateRepo verbosity updateFlags repoCtxt repo = do
- transport <- repoContextGetTransport repoCtxt
- case repo of
-- RepoLocal{..} -> return ()
-- RepoLocalNoIndex{..} -> return ()
-+ RepoLocal{} -> return ()
-+ RepoLocalNoIndex{} -> return ()
- RepoRemote{..} -> do
- downloadResult <- downloadIndex transport verbosity repoRemote repoLocalDir
- case downloadResult of
-diff --git a/Distribution/Client/Utils/Json.hs b/Distribution/Client/Utils/Json.hs
-index 89a13af87a4..01d5753136b 100644
---- a/Distribution/Client/Utils/Json.hs
-+++ b/Distribution/Client/Utils/Json.hs
-@@ -15,12 +15,9 @@ module Distribution.Client.Utils.Json
- )
- where
-
--import Data.Char
--import Data.Int
--import Data.String
--import Data.Word
--import Data.List
--import Data.Monoid
-+import Distribution.Client.Compat.Prelude
-+
-+import Data.Char (intToDigit)
-
- import Data.ByteString.Builder (Builder)
- import qualified Data.ByteString.Builder as BB
-@@ -135,13 +132,13 @@ encodeArrayBB :: [Value] -> Builder
- encodeArrayBB [] = "[]"
- encodeArrayBB jvs = BB.char8 '[' <> go jvs <> BB.char8 ']'
- where
-- go = Data.Monoid.mconcat . intersperse (BB.char8 ',') . map encodeValueBB
-+ go = mconcat . intersperse (BB.char8 ',') . map encodeValueBB
-
- encodeObjectBB :: Object -> Builder
- encodeObjectBB [] = "{}"
- encodeObjectBB jvs = BB.char8 '{' <> go jvs <> BB.char8 '}'
- where
-- go = Data.Monoid.mconcat . intersperse (BB.char8 ',') . map encPair
-+ go = mconcat . intersperse (BB.char8 ',') . map encPair
- encPair (l,x) = encodeStringBB l <> BB.char8 ':' <> encodeValueBB x
-
- encodeStringBB :: String -> Builder
-diff --git a/Distribution/Solver/Modular/Assignment.hs b/Distribution/Solver/Modular/Assignment.hs
-index be5e63bfbc1..b05a099ec5a 100644
---- a/Distribution/Solver/Modular/Assignment.hs
-+++ b/Distribution/Solver/Modular/Assignment.hs
-@@ -9,10 +9,11 @@ module Distribution.Solver.Modular.Assignment
- import Prelude ()
- import Distribution.Solver.Compat.Prelude hiding (pi)
-
--import Data.Array as A
--import Data.List as L
--import Data.Map as M
--import Data.Maybe
-+import qualified Data.Array as A
-+import qualified Data.List as L
-+import qualified Data.Map as M
-+
-+import Data.Maybe (fromJust)
-
- import Distribution.PackageDescription (FlagAssignment, mkFlagAssignment) -- from Cabal
-
-@@ -79,7 +80,7 @@ toCPs (A pa fa sa) rdm =
- -- Dependencies per package.
- depp :: QPN -> [(Component, PI QPN)]
- depp qpn = let v :: Vertex
-- v = fromJust (cvm qpn)
-+ v = fromJust (cvm qpn) -- TODO: why this is safe?
- dvs :: [(Component, Vertex)]
- dvs = tg A.! v
- in L.map (\ (comp, dv) -> case vm dv of (_, x, _) -> (comp, PI x (pa M.! x))) dvs
-diff --git a/Distribution/Solver/Modular/Builder.hs b/Distribution/Solver/Modular/Builder.hs
-index eb11a36aa16..5d196f4fd9f 100644
---- a/Distribution/Solver/Modular/Builder.hs
-+++ b/Distribution/Solver/Modular/Builder.hs
-@@ -19,10 +19,10 @@ module Distribution.Solver.Modular.Builder (
- -- flag-guarded dependencies, we cannot introduce them immediately. Instead, we
- -- store the entire dependency.
-
--import Data.List as L
--import Data.Map as M
--import Data.Set as S
--import Prelude hiding (sequence, mapM)
-+import qualified Data.List as L
-+import qualified Data.Map as M
-+import qualified Data.Set as S
-+import Prelude
-
- import qualified Distribution.Solver.Modular.ConflictSet as CS
- import Distribution.Solver.Modular.Dependency
-@@ -55,7 +55,7 @@ data BuildState = BS {
- }
-
- -- | Map of available linking targets.
--type LinkingState = Map (PN, I) [PackagePath]
-+type LinkingState = M.Map (PN, I) [PackagePath]
-
- -- | Extend the set of open goals with the new goals listed.
- --
-diff --git a/Distribution/Solver/Modular/Index.hs b/Distribution/Solver/Modular/Index.hs
-index fdddfc8237a..ac60fec7d65 100644
---- a/Distribution/Solver/Modular/Index.hs
-+++ b/Distribution/Solver/Modular/Index.hs
-@@ -6,10 +6,12 @@ module Distribution.Solver.Modular.Index
- , mkIndex
- ) where
-
--import Data.List as L
--import Data.Map as M
- import Prelude hiding (pi)
-
-+import Data.Map (Map)
-+import qualified Data.List as L
-+import qualified Data.Map as M
-+
- import Distribution.Solver.Modular.Dependency
- import Distribution.Solver.Modular.Flag
- import Distribution.Solver.Modular.Package
-diff --git a/Distribution/Solver/Modular/IndexConversion.hs b/Distribution/Solver/Modular/IndexConversion.hs
-index c9565c80dba..8e9ef614184 100644
---- a/Distribution/Solver/Modular/IndexConversion.hs
-+++ b/Distribution/Solver/Modular/IndexConversion.hs
-@@ -2,12 +2,12 @@ module Distribution.Solver.Modular.IndexConversion
- ( convPIs
- ) where
-
--import Data.List as L
-+import qualified Data.List as L
- import Data.Map.Strict (Map)
- import qualified Data.Map.Strict as M
--import Data.Maybe
-+import Data.Maybe (mapMaybe, fromMaybe, maybeToList)
- import Data.Monoid as Mon
--import Data.Set as S
-+import qualified Data.Set as S
-
- import Distribution.Compiler
- import Distribution.InstalledPackageInfo as IPI
-@@ -330,7 +330,7 @@ flagInfo (StrongFlags strfl) =
-
- -- | Internal package names, which should not be interpreted as true
- -- dependencies.
--type IPNs = Set PN
-+type IPNs = S.Set PN
-
- -- | Convenience function to delete a 'Dependency' if it's
- -- for a 'PN' that isn't actually real.
-diff --git a/Distribution/Solver/Modular/Solver.hs b/Distribution/Solver/Modular/Solver.hs
-index 32452550556..e6aa1fb4374 100644
---- a/Distribution/Solver/Modular/Solver.hs
-+++ b/Distribution/Solver/Modular/Solver.hs
-@@ -9,9 +9,9 @@ module Distribution.Solver.Modular.Solver
- , PruneAfterFirstSuccess(..)
- ) where
-
--import Data.Map as M
--import Data.List as L
--import Data.Set as S
-+import qualified Data.Map as M
-+import qualified Data.List as L
-+import qualified Data.Set as S
- import Distribution.Verbosity
-
- import Distribution.Compiler (CompilerInfo)
-@@ -91,8 +91,8 @@ solve :: SolverConfig -- ^ solver parameters
- -> Index -- ^ all available packages as an index
- -> PkgConfigDb -- ^ available pkg-config pkgs
- -> (PN -> PackagePreferences) -- ^ preferences
-- -> Map PN [LabeledPackageConstraint] -- ^ global constraints
-- -> Set PN -- ^ global goals
-+ -> M.Map PN [LabeledPackageConstraint] -- ^ global constraints
-+ -> S.Set PN -- ^ global goals
- -> RetryLog Message SolverFailure (Assignment, RevDepMap)
- solve sc cinfo idx pkgConfigDB userPrefs userConstraints userGoals =
- explorePhase $
-@@ -232,7 +232,7 @@ instance GSimpleTree (Tree d c) where
-
- -- Show conflict set
- goCS :: ConflictSet -> String
-- goCS cs = "{" ++ (intercalate "," . L.map showVar . CS.toList $ cs) ++ "}"
-+ goCS cs = "{" ++ (L.intercalate "," . L.map showVar . CS.toList $ cs) ++ "}"
- #endif
-
- -- | Replace all goal reasons with a dummy goal reason in the tree
-diff --git a/Distribution/Solver/Modular/Validate.hs b/Distribution/Solver/Modular/Validate.hs
-index 6195d101b02..a3dec6e1f67 100644
---- a/Distribution/Solver/Modular/Validate.hs
-+++ b/Distribution/Solver/Modular/Validate.hs
-@@ -15,11 +15,12 @@ module Distribution.Solver.Modular.Validate (validateTree) where
- import Control.Applicative
- import Control.Monad.Reader hiding (sequence)
- import Data.Function (on)
--import Data.List as L
--import Data.Set as S
- import Data.Traversable
- import Prelude hiding (sequence)
-
-+import qualified Data.List as L
-+import qualified Data.Set as S
-+
- import Language.Haskell.Extension (Extension, Language)
-
- import Data.Map.Strict as M
-diff --git a/bootstrap.sh b/bootstrap.sh
-index 077d7f4efd2..d5141660474 100755
---- a/bootstrap.sh
-+++ b/bootstrap.sh
-@@ -260,9 +260,9 @@ EDIT_DISTANCE_VER="0.2.2.1"; EDIT_DISTANCE_VER_REGEXP="0\.2\.2\.?"
- # 0.2.2.*
- ED25519_VER="0.0.5.0"; ED25519_VER_REGEXP="0\.0\.?"
- # 0.0.*
--HACKAGE_SECURITY_VER="0.6.0.0"; HACKAGE_SECURITY_VER_REGEXP="0\.6\."
-- # >= 0.7.0.0 && < 0.7
--TAR_VER="0.5.1.0"; TAR_VER_REGEXP="0\.5\.([1-9]|1[0-9]|0\.[3-9]|0\.1[0-9])\.?"
-+HACKAGE_SECURITY_VER="0.6.0.1"; HACKAGE_SECURITY_VER_REGEXP="0\.6\."
-+ # >= 0.6.0.0 && < 0.7
-+TAR_VER="0.5.1.1"; TAR_VER_REGEXP="0\.5\.([1-9]|1[0-9]|0\.[3-9]|0\.1[0-9])\.?"
- # >= 0.5.0.3 && < 0.6
- DIGEST_VER="0.0.1.2"; DIGEST_REGEXP="0\.0\.(1\.[2-9]|[2-9]\.?)"
- # >= 0.0.1.2 && < 0.1
-diff --git a/cabal-install.cabal b/cabal-install.cabal
-index 985ea9a5a69..c9d713c29fe 100644
---- a/cabal-install.cabal
-+++ b/cabal-install.cabal
-@@ -316,7 +316,7 @@ executable cabal
- build-depends:
- async >= 2.0 && < 2.3,
- array >= 0.4 && < 0.6,
-- base >= 4.8 && < 4.14,
-+ base >= 4.8 && < 4.15,
- base16-bytestring >= 0.1.1 && < 0.2,
- binary >= 0.7.3 && < 0.9,
- bytestring >= 0.10.6.0 && < 0.11,
-@@ -341,7 +341,7 @@ executable cabal
- time >= 1.5.0.1 && < 1.10,
- transformers >= 0.4.2.0 && < 0.6,
- zlib >= 0.5.3 && < 0.7,
-- hackage-security >= 0.6.0.0 && < 0.7,
-+ hackage-security >= 0.6.0.1 && < 0.7,
- text >= 1.2.3 && < 1.3,
- parsec >= 3.1.13.0 && < 3.2
-
-diff --git a/tests/IntegrationTests2/targets/complex/q/q.cabal b/tests/IntegrationTests2/targets/complex/q/q.cabal
-index 556fa4a4202..7ee22fcb28d 100644
---- a/tests/IntegrationTests2/targets/complex/q/q.cabal
-+++ b/tests/IntegrationTests2/targets/complex/q/q.cabal
-@@ -5,7 +5,8 @@ cabal-version: >= 1.2
-
- library
- exposed-modules: Q
-- build-depends: base, filepath
-+ -- we rely that filepath has filepath-tests component
-+ build-depends: base, filepath >=1.4.0.0
-
- executable buildable-false
- main-is: Main.hs
diff --git a/gnu/packages/patches/ghc-bloomfilter-ghc9.2.patch b/gnu/packages/patches/ghc-bloomfilter-ghc9.2.patch
new file mode 100644
index 0000000000..97caf2cc9b
--- /dev/null
+++ b/gnu/packages/patches/ghc-bloomfilter-ghc9.2.patch
@@ -0,0 +1,303 @@
+Taken from https://github.com/bos/bloomfilter/pull/20
+
+From fb79b39c44404fd791a3bed973e9d844fb084f1e Mon Sep 17 00:00:00 2001
+From: Simon Jakobi <simon.jakobi@gmail.com>
+Date: Fri, 12 Nov 2021 01:37:36 +0100
+Subject: [PATCH] Fix build with GHC 9.2
+
+The `FastShift.shift{L,R}` methods are replaced with `unsafeShift{L,R}`
+introduced in base-4.5.
+
+Fixes #19.
+---
+ Data/BloomFilter.hs | 16 +++++------
+ Data/BloomFilter/Hash.hs | 15 +++++-----
+ Data/BloomFilter/Mutable.hs | 20 +++++++-------
+ Data/BloomFilter/Util.hs | 55 ++++++-------------------------------
+ bloomfilter.cabal | 2 +-
+ 5 files changed, 34 insertions(+), 74 deletions(-)
+
+diff --git a/Data/BloomFilter.hs b/Data/BloomFilter.hs
+index 2210cef..6b47c21 100644
+--- a/Data/BloomFilter.hs
++++ b/Data/BloomFilter.hs
+@@ -78,8 +78,8 @@ import Control.DeepSeq (NFData(..))
+ import Data.Array.Base (unsafeAt)
+ import qualified Data.Array.Base as ST
+ import Data.Array.Unboxed (UArray)
+-import Data.Bits ((.&.))
+-import Data.BloomFilter.Util (FastShift(..), (:*)(..))
++import Data.Bits ((.&.), unsafeShiftL, unsafeShiftR)
++import Data.BloomFilter.Util ((:*)(..))
+ import qualified Data.BloomFilter.Mutable as MB
+ import qualified Data.BloomFilter.Mutable.Internal as MB
+ import Data.BloomFilter.Mutable.Internal (Hash, MBloom)
+@@ -98,7 +98,7 @@ data Bloom a = B {
+ }
+
+ instance Show (Bloom a) where
+- show ub = "Bloom { " ++ show ((1::Int) `shiftL` shift ub) ++ " bits } "
++ show ub = "Bloom { " ++ show ((1::Int) `unsafeShiftL` shift ub) ++ " bits } "
+
+ instance NFData (Bloom a) where
+ rnf !_ = ()
+@@ -172,7 +172,7 @@ singleton hash numBits elt = create hash numBits (\mb -> MB.insert mb elt)
+ -- | Given a filter's mask and a hash value, compute an offset into
+ -- a word array and a bit offset within that word.
+ hashIdx :: Int -> Word32 -> (Int :* Int)
+-hashIdx mask x = (y `shiftR` logBitsInHash) :* (y .&. hashMask)
++hashIdx mask x = (y `unsafeShiftR` logBitsInHash) :* (y .&. hashMask)
+ where hashMask = 31 -- bitsInHash - 1
+ y = fromIntegral x .&. mask
+
+@@ -191,7 +191,7 @@ hashesU ub elt = hashIdx (mask ub) `map` hashes ub elt
+ -- /still/ some possibility that @True@ will be returned.
+ elem :: a -> Bloom a -> Bool
+ elem elt ub = all test (hashesU ub elt)
+- where test (off :* bit) = (bitArray ub `unsafeAt` off) .&. (1 `shiftL` bit) /= 0
++ where test (off :* bit) = (bitArray ub `unsafeAt` off) .&. (1 `unsafeShiftL` bit) /= 0
+
+ modify :: (forall s. (MBloom s a -> ST s z)) -- ^ mutation function (result is discarded)
+ -> Bloom a
+@@ -255,11 +255,11 @@ insertList elts = modify $ \mb -> mapM_ (MB.insert mb) elts
+ -- is /still/ some possibility that @True@ will be returned.
+ notElem :: a -> Bloom a -> Bool
+ notElem elt ub = any test (hashesU ub elt)
+- where test (off :* bit) = (bitArray ub `unsafeAt` off) .&. (1 `shiftL` bit) == 0
++ where test (off :* bit) = (bitArray ub `unsafeAt` off) .&. (1 `unsafeShiftL` bit) == 0
+
+ -- | Return the size of an immutable Bloom filter, in bits.
+ length :: Bloom a -> Int
+-length = shiftL 1 . shift
++length = unsafeShiftL 1 . shift
+
+ -- | Build an immutable Bloom filter from a seed value. The seeding
+ -- function populates the filter as follows.
+@@ -318,7 +318,7 @@ fromList hashes numBits = unfold hashes numBits convert
+ logPower2 :: Int -> Int
+ logPower2 k = go 0 k
+ where go j 1 = j
+- go j n = go (j+1) (n `shiftR` 1)
++ go j n = go (j+1) (n `unsafeShiftR` 1)
+
+ -- $overview
+ --
+diff --git a/Data/BloomFilter/Hash.hs b/Data/BloomFilter/Hash.hs
+index 132a3a4..d071fd4 100644
+--- a/Data/BloomFilter/Hash.hs
++++ b/Data/BloomFilter/Hash.hs
+@@ -38,8 +38,7 @@ module Data.BloomFilter.Hash
+ ) where
+
+ import Control.Monad (foldM)
+-import Data.Bits ((.&.), (.|.), xor)
+-import Data.BloomFilter.Util (FastShift(..))
++import Data.Bits ((.&.), (.|.), unsafeShiftL, unsafeShiftR, xor)
+ import Data.List (unfoldr)
+ import Data.Int (Int8, Int16, Int32, Int64)
+ import Data.Word (Word8, Word16, Word32, Word64)
+@@ -91,11 +90,11 @@ class Hashable a where
+ -> Word64 -- ^ salt
+ -> IO Word64
+ hashIO64 v salt = do
+- let s1 = fromIntegral (salt `shiftR` 32) .&. maxBound
++ let s1 = fromIntegral (salt `unsafeShiftR` 32) .&. maxBound
+ s2 = fromIntegral salt
+ h1 <- hashIO32 v s1
+ h2 <- hashIO32 v s2
+- return $ (fromIntegral h1 `shiftL` 32) .|. fromIntegral h2
++ return $ (fromIntegral h1 `unsafeShiftL` 32) .|. fromIntegral h2
+
+ -- | Compute a 32-bit hash.
+ hash32 :: Hashable a => a -> Word32
+@@ -149,8 +148,8 @@ cheapHashes :: Hashable a => Int -- ^ number of hashes to compute
+ cheapHashes k v = go 0
+ where go i | i == j = []
+ | otherwise = hash : go (i + 1)
+- where !hash = h1 + (h2 `shiftR` i)
+- h1 = fromIntegral (h `shiftR` 32)
++ where !hash = h1 + (h2 `unsafeShiftR` i)
++ h1 = fromIntegral (h `unsafeShiftR` 32)
+ h2 = fromIntegral h
+ h = hashSalt64 0x9150a946c4a8966e v
+ j = fromIntegral k
+@@ -163,7 +162,7 @@ instance Hashable Integer where
+ (salt `xor` 0x3ece731e)
+ | otherwise = hashIO32 (unfoldr go k) salt
+ where go 0 = Nothing
+- go i = Just (fromIntegral i :: Word32, i `shiftR` 32)
++ go i = Just (fromIntegral i :: Word32, i `unsafeShiftR` 32)
+
+ instance Hashable Bool where
+ hashIO32 = hashOne32
+@@ -224,7 +223,7 @@ instance Hashable Word64 where
+ -- | A fast unchecked shift. Nasty, but otherwise GHC 6.8.2 does a
+ -- test and branch on every shift.
+ div4 :: CSize -> CSize
+-div4 k = fromIntegral ((fromIntegral k :: HTYPE_SIZE_T) `shiftR` 2)
++div4 k = fromIntegral ((fromIntegral k :: HTYPE_SIZE_T) `unsafeShiftR` 2)
+
+ alignedHash :: Ptr a -> CSize -> Word32 -> IO Word32
+ alignedHash ptr bytes salt
+diff --git a/Data/BloomFilter/Mutable.hs b/Data/BloomFilter/Mutable.hs
+index edff1fc..0bb5cc9 100644
+--- a/Data/BloomFilter/Mutable.hs
++++ b/Data/BloomFilter/Mutable.hs
+@@ -65,9 +65,9 @@ module Data.BloomFilter.Mutable
+ import Control.Monad (liftM, forM_)
+ import Control.Monad.ST (ST)
+ import Data.Array.Base (unsafeRead, unsafeWrite)
+-import Data.Bits ((.&.), (.|.))
++import Data.Bits ((.&.), (.|.), unsafeShiftL, unsafeShiftR)
+ import Data.BloomFilter.Array (newArray)
+-import Data.BloomFilter.Util (FastShift(..), (:*)(..), nextPowerOfTwo)
++import Data.BloomFilter.Util ((:*)(..), nextPowerOfTwo)
+ import Data.Word (Word32)
+ import Data.BloomFilter.Mutable.Internal
+
+@@ -86,9 +86,9 @@ new hash numBits = MB hash shft msk `liftM` newArray numElems numBytes
+ | numBits > maxHash = maxHash
+ | isPowerOfTwo numBits = numBits
+ | otherwise = nextPowerOfTwo numBits
+- numElems = max 2 (twoBits `shiftR` logBitsInHash)
+- numBytes = numElems `shiftL` logBytesInHash
+- trueBits = numElems `shiftL` logBitsInHash
++ numElems = max 2 (twoBits `unsafeShiftR` logBitsInHash)
++ numBytes = numElems `unsafeShiftL` logBytesInHash
++ trueBits = numElems `unsafeShiftL` logBitsInHash
+ shft = logPower2 trueBits
+ msk = trueBits - 1
+ isPowerOfTwo n = n .&. (n - 1) == 0
+@@ -109,7 +109,7 @@ logBytesInHash = 2 -- logPower2 (sizeOf (undefined :: Hash))
+ -- | Given a filter's mask and a hash value, compute an offset into
+ -- a word array and a bit offset within that word.
+ hashIdx :: Int -> Word32 -> (Int :* Int)
+-hashIdx msk x = (y `shiftR` logBitsInHash) :* (y .&. hashMask)
++hashIdx msk x = (y `unsafeShiftR` logBitsInHash) :* (y .&. hashMask)
+ where hashMask = 31 -- bitsInHash - 1
+ y = fromIntegral x .&. msk
+
+@@ -125,7 +125,7 @@ insert mb elt = do
+ let mu = bitArray mb
+ forM_ (hashesM mb elt) $ \(word :* bit) -> do
+ old <- unsafeRead mu word
+- unsafeWrite mu word (old .|. (1 `shiftL` bit))
++ unsafeWrite mu word (old .|. (1 `unsafeShiftL` bit))
+
+ -- | Query a mutable Bloom filter for membership. If the value is
+ -- present, return @True@. If the value is not present, there is
+@@ -135,7 +135,7 @@ elem elt mb = loop (hashesM mb elt)
+ where mu = bitArray mb
+ loop ((word :* bit):wbs) = do
+ i <- unsafeRead mu word
+- if i .&. (1 `shiftL` bit) == 0
++ if i .&. (1 `unsafeShiftL` bit) == 0
+ then return False
+ else loop wbs
+ loop _ = return True
+@@ -145,7 +145,7 @@ elem elt mb = loop (hashesM mb elt)
+
+ -- | Return the size of a mutable Bloom filter, in bits.
+ length :: MBloom s a -> Int
+-length = shiftL 1 . shift
++length = unsafeShiftL 1 . shift
+
+
+ -- | Slow, crummy way of computing the integer log of an integer known
+@@ -153,7 +153,7 @@ length = shiftL 1 . shift
+ logPower2 :: Int -> Int
+ logPower2 k = go 0 k
+ where go j 1 = j
+- go j n = go (j+1) (n `shiftR` 1)
++ go j n = go (j+1) (n `unsafeShiftR` 1)
+
+ -- $overview
+ --
+diff --git a/Data/BloomFilter/Util.hs b/Data/BloomFilter/Util.hs
+index 7f695dc..6ade6e5 100644
+--- a/Data/BloomFilter/Util.hs
++++ b/Data/BloomFilter/Util.hs
+@@ -2,15 +2,11 @@
+
+ module Data.BloomFilter.Util
+ (
+- FastShift(..)
+- , nextPowerOfTwo
++ nextPowerOfTwo
+ , (:*)(..)
+ ) where
+
+-import Data.Bits ((.|.))
+-import qualified Data.Bits as Bits
+-import GHC.Base
+-import GHC.Word
++import Data.Bits ((.|.), unsafeShiftR)
+
+ -- | A strict pair type.
+ data a :* b = !a :* !b
+@@ -22,46 +18,11 @@ nextPowerOfTwo :: Int -> Int
+ {-# INLINE nextPowerOfTwo #-}
+ nextPowerOfTwo n =
+ let a = n - 1
+- b = a .|. (a `shiftR` 1)
+- c = b .|. (b `shiftR` 2)
+- d = c .|. (c `shiftR` 4)
+- e = d .|. (d `shiftR` 8)
+- f = e .|. (e `shiftR` 16)
+- g = f .|. (f `shiftR` 32) -- in case we're on a 64-bit host
++ b = a .|. (a `unsafeShiftR` 1)
++ c = b .|. (b `unsafeShiftR` 2)
++ d = c .|. (c `unsafeShiftR` 4)
++ e = d .|. (d `unsafeShiftR` 8)
++ f = e .|. (e `unsafeShiftR` 16)
++ g = f .|. (f `unsafeShiftR` 32) -- in case we're on a 64-bit host
+ !h = g + 1
+ in h
+-
+--- | This is a workaround for poor optimisation in GHC 6.8.2. It
+--- fails to notice constant-width shifts, and adds a test and branch
+--- to every shift. This imposes about a 10% performance hit.
+-class FastShift a where
+- shiftL :: a -> Int -> a
+- shiftR :: a -> Int -> a
+-
+-instance FastShift Word32 where
+- {-# INLINE shiftL #-}
+- shiftL (W32# x#) (I# i#) = W32# (x# `uncheckedShiftL#` i#)
+-
+- {-# INLINE shiftR #-}
+- shiftR (W32# x#) (I# i#) = W32# (x# `uncheckedShiftRL#` i#)
+-
+-instance FastShift Word64 where
+- {-# INLINE shiftL #-}
+- shiftL (W64# x#) (I# i#) = W64# (x# `uncheckedShiftL64#` i#)
+-
+- {-# INLINE shiftR #-}
+- shiftR (W64# x#) (I# i#) = W64# (x# `uncheckedShiftRL64#` i#)
+-
+-instance FastShift Int where
+- {-# INLINE shiftL #-}
+- shiftL (I# x#) (I# i#) = I# (x# `iShiftL#` i#)
+-
+- {-# INLINE shiftR #-}
+- shiftR (I# x#) (I# i#) = I# (x# `iShiftRA#` i#)
+-
+-instance FastShift Integer where
+- {-# INLINE shiftL #-}
+- shiftL = Bits.shiftL
+-
+- {-# INLINE shiftR #-}
+- shiftR = Bits.shiftR
+diff --git a/bloomfilter.cabal b/bloomfilter.cabal
+index 821a5d7..c621f7f 100644
+--- a/bloomfilter.cabal
++++ b/bloomfilter.cabal
+@@ -18,7 +18,7 @@ extra-source-files: README.markdown cbits/lookup3.c cbits/lookup3.h
+ library
+ build-depends:
+ array,
+- base >= 4.4 && < 5,
++ base >= 4.5 && < 5,
+ bytestring >= 0.9,
+ deepseq
+ exposed-modules: Data.BloomFilter
diff --git a/gnu/packages/patches/ghc-bytestring-handle-ghc9.patch b/gnu/packages/patches/ghc-bytestring-handle-ghc9.patch
new file mode 100644
index 0000000000..43dd472bf6
--- /dev/null
+++ b/gnu/packages/patches/ghc-bytestring-handle-ghc9.patch
@@ -0,0 +1,67 @@
+Taken from https://raw.githubusercontent.com/archlinux/svntogit-community/packages/haskell-bytestring-handle/trunk/ghc9.patch
+
+--- bytestring-handle-0.1.0.6/src/Data/ByteString/Handle/Write.hs.orig 2021-06-21 14:54:12.217134401 +0800
++++ bytestring-handle-0.1.0.6/src/Data/ByteString/Handle/Write.hs 2021-06-21 15:24:01.794796505 +0800
+@@ -17,7 +17,7 @@
+
+ import GHC.IO.Buffer ( BufferState(..), emptyBuffer, Buffer(..) )
+ import GHC.IO.BufferedIO ( BufferedIO(..) )
+-import GHC.IO.Device ( IODevice(..), IODeviceType(..), SeekMode(..) )
++import GHC.IO.Device ( IODevice(..), IODeviceType(..), SeekMode(..), RawIO(..) )
+ #if MIN_VERSION_base(4,5,0)
+ import GHC.IO.Encoding ( getLocaleEncoding )
+ #else
+@@ -138,6 +138,7 @@
+ seek_base = error "seek_base needs to be updated"
+ })
+ modifyIORef (write_size ws) (`max` newSeekPos)
++ pure newSeekPos
+
+ tell ws = do
+ ss <- readIORef (write_seek_state ws)
+@@ -152,6 +153,12 @@
+
+ devType _ = return RegularFile -- TODO: is this correct?
+
++instance RawIO WriteState where
++ read _ _ _ _ = return 0
++ readNonBlocking _ _ _ _ = return Nothing
++ write _ _ _ _ = return ()
++ writeNonBlocking _ _ _ _ = return 0
++
+ ioe_seekOutOfRange :: IO a
+ ioe_seekOutOfRange =
+ ioException $ IOError Nothing InvalidArgument ""
+--- bytestring-handle-0.1.0.6/src/Data/ByteString/Handle/Read.hs.orig 2021-06-21 14:53:55.433129276 +0800
++++ bytestring-handle-0.1.0.6/src/Data/ByteString/Handle/Read.hs 2021-06-21 15:24:25.998784996 +0800
+@@ -24,7 +24,7 @@
+ , emptyBuffer, isEmptyBuffer, newBuffer, newByteBuffer
+ , bufferElems, withBuffer, withRawBuffer )
+ import GHC.IO.BufferedIO ( BufferedIO(..) )
+-import GHC.IO.Device ( IODevice(..), IODeviceType(..), SeekMode(..) )
++import GHC.IO.Device ( IODevice(..), IODeviceType(..), SeekMode(..), RawIO(..) )
+ #if MIN_VERSION_base(4,5,0)
+ import GHC.IO.Encoding ( getLocaleEncoding )
+ #else
+@@ -155,7 +155,7 @@
+ (seek_before_length curSeekState)
+ (fromIntegral (seek_pos curSeekState) + seekPos)
+ SeekFromEnd -> normalisedSeekState (read_chunks_backwards rs) [] (read_length rs) seekPos
+- maybe ioe_seekOutOfRange (writeIORef (read_seek_state rs)) newSeekState
++ maybe ioe_seekOutOfRange (\nss -> writeIORef (read_seek_state rs) nss >> pure (fromIntegral(seek_pos nss))) newSeekState
+
+ tell rs = do
+ ss <- readIORef (read_seek_state rs)
+@@ -166,6 +166,12 @@
+
+ devType _ = return RegularFile -- TODO: is this correct?
+
++instance RawIO ReadState where
++ read _ _ _ _ = return 0
++ readNonBlocking _ _ _ _ = return Nothing
++ write _ _ _ _ = return ()
++ writeNonBlocking _ _ _ _ = return 0
++
+ ioe_seekOutOfRange :: IO a
+ ioe_seekOutOfRange =
+ ioException $ IOError Nothing InvalidArgument ""
diff --git a/gnu/packages/patches/ngless-unliftio.patch b/gnu/packages/patches/ngless-unliftio.patch
deleted file mode 100644
index 87f5e79fcf..0000000000
--- a/gnu/packages/patches/ngless-unliftio.patch
+++ /dev/null
@@ -1,66 +0,0 @@
-From 919565adc1216b9d3108b3043e8d307292b37393 Mon Sep 17 00:00:00 2001
-From: Luis Pedro Coelho <luis@luispedro.org>
-Date: Fri, 7 May 2021 11:42:56 +0800
-Subject: [PATCH] BLD Update to LTS-17.10
-
-- Updates the GHC version
-- Requires `extra-deps` for `diagrams` package
-- Simplifies code for NGLessIO monad as UnliftIO can now be auto-derived
----
- NGLess/NGLess/NGError.hs | 8 ++------
- stack.yaml | 11 ++++++++---
- 2 files changed, 10 insertions(+), 9 deletions(-)
-
-diff --git a/NGLess/NGLess/NGError.hs b/NGLess/NGLess/NGError.hs
-index a22e557f..c7eddf5b 100644
---- a/NGLess/NGLess/NGError.hs
-+++ b/NGLess/NGLess/NGError.hs
-@@ -50,7 +50,8 @@ type NGLess = Either NGError
-
- newtype NGLessIO a = NGLessIO { unwrapNGLessIO :: ResourceT IO a }
- deriving (Functor, Applicative, Monad, MonadIO,
-- MonadResource, MonadThrow, MonadCatch, MonadMask)
-+ MonadResource, MonadThrow, MonadCatch, MonadMask,
-+ MonadUnliftIO)
-
-
- instance MonadError NGError NGLessIO where
-@@ -62,11 +63,6 @@ instance PrimMonad NGLessIO where
- primitive act = NGLessIO (primitive act)
- {-# INLINE primitive #-}
-
--instance MonadUnliftIO NGLessIO where
-- askUnliftIO = NGLessIO $ do
-- u <- askUnliftIO
-- return $ UnliftIO (\(NGLessIO act) -> unliftIO u act)
--
- instance MonadFail NGLessIO where
- fail err = throwShouldNotOccur err
-
-diff --git a/stack.yaml b/stack.yaml
-index 051d973d..11b65887 100644
---- a/stack.yaml
-+++ b/stack.yaml
-@@ -1,14 +1,19 @@
- # For more information, see: https://github.com/commercialhaskell/stack/blob/release/doc/yaml_configuration.md
-
--resolver: lts-14.20
-+resolver: lts-17.10
- compiler-check: newer-minor
-
- # Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3)
- extra-deps:
- - git: "https://github.com/ngless-toolkit/interval-to-int"
- commit: "78289f6b48d41f7cc48169520ec9b77b050a0029"
--
--
-+ - diagrams-core-1.4.2@sha256:47de45658e8a805b7cb7f535e7b093daf7e861604fa3c70e25bd4ef481bf1571,2997
-+ - diagrams-lib-1.4.3@sha256:04f77778d4b550d3c8e54440800685f88467bef91075e82e009a8a6f45c51033,8232
-+ - diagrams-svg-1.4.3@sha256:36708b0b4cf35507ccf689f1a25f6f81b8f41c2c4c2900793de820f66d4e241c,3181
-+ - active-0.2.0.14@sha256:e618aba4a7881eb85dc1585e0a01230af6b4fbab6693931e4a5d0d3a5b184406,1823
-+ - dual-tree-0.2.2.1@sha256:9ff31e461d873ae74ba51d93b454c0c4094726d7cb78a0c454394c965e83539d,2830
-+ - monoid-extras-0.5.1@sha256:438dbfd7b4dce47d8f0ca577f56caf94bd1e21391afa545cad09fe7cf2e5793d,2333
-+ - svg-builder-0.1.1@sha256:22de54d326a6b6912e461e1302edb9108b02aac0b6a6368fcdc3c4a224d487fd,1440
- allow-newer: true
-
- # Override default flag values for local packages and extra-deps
diff --git a/gnu/packages/patches/xmonad-dynamic-linking.patch b/gnu/packages/patches/xmonad-dynamic-linking.patch
index 4f3386e53a..a1d71825b6 100644
--- a/gnu/packages/patches/xmonad-dynamic-linking.patch
+++ b/gnu/packages/patches/xmonad-dynamic-linking.patch
@@ -2,15 +2,15 @@ This patch is required for xmonad to make use of shared libraries.
Without it, xmonad will not work since we do not (by default) use
statically linked Haskell libraries.
-diff -ruN xmonad-0.15-a/src/XMonad/Core.hs xmonad-0.15-b/src/XMonad/Core.hs
---- xmonad-0.15-a/src/XMonad/Core.hs 1969-12-31 19:00:00.000000000 -0500
-+++ xmonad-0.15-b/src/XMonad/Core.hs 1969-12-31 19:00:00.000000000 -0500
-@@ -681,6 +681,8 @@
- compileGHC bin dir errHandle =
- runProcess "ghc" ["--make"
- , "xmonad.hs"
-+ , "-dynamic"
-+ , "-fPIC"
- , "-i"
- , "-ilib"
- , "-fforce-recomp"
+index 46a0939..5ad4f8f 100644
+--- a/src/XMonad/Core.hs
++++ b/src/XMonad/Core.hs
+@@ -664,6 +664,8 @@ compile dirs method =
+ where
+ ghcArgs = [ "--make"
+ , "xmonad.hs"
++ , "-dynamic"
++ , "-fPIC"
+ , "-i" -- only look in @lib@
+ , "-ilib"
+ , "-fforce-recomp"
diff --git a/gnu/packages/patches/xmonad-next-dynamic-linking.patch b/gnu/packages/patches/xmonad-next-dynamic-linking.patch
deleted file mode 100644
index a1d71825b6..0000000000
--- a/gnu/packages/patches/xmonad-next-dynamic-linking.patch
+++ /dev/null
@@ -1,16 +0,0 @@
-This patch is required for xmonad to make use of shared libraries.
-Without it, xmonad will not work since we do not (by default) use
-statically linked Haskell libraries.
-
-index 46a0939..5ad4f8f 100644
---- a/src/XMonad/Core.hs
-+++ b/src/XMonad/Core.hs
-@@ -664,6 +664,8 @@ compile dirs method =
- where
- ghcArgs = [ "--make"
- , "xmonad.hs"
-+ , "-dynamic"
-+ , "-fPIC"
- , "-i" -- only look in @lib@
- , "-ilib"
- , "-fforce-recomp"