[commit: ghc] wip/nfs-locking: Add Base.hs (basic datatypes and imports for the build system). (4e03b1c)

git at git.haskell.org git at git.haskell.org
Thu Oct 26 23:14:33 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/nfs-locking
Link       : http://ghc.haskell.org/trac/ghc/changeset/4e03b1c45d2be172e017d3ec5d8dfff5ab8354d9/ghc

>---------------------------------------------------------------

commit 4e03b1c45d2be172e017d3ec5d8dfff5ab8354d9
Author: Andrey Mokhov <andrey.mokhov at ncl.ac.uk>
Date:   Tue Dec 23 17:44:51 2014 +0000

    Add Base.hs (basic datatypes and imports for the build system).


>---------------------------------------------------------------

4e03b1c45d2be172e017d3ec5d8dfff5ab8354d9
 Base.hs | 45 +++++++++++++++++++++++++++++++++++++++++++++
 1 file changed, 45 insertions(+)

diff --git a/Base.hs b/Base.hs
new file mode 100644
index 0000000..7e130c2
--- /dev/null
+++ b/Base.hs
@@ -0,0 +1,45 @@
+{-# LANGUAGE FlexibleInstances #-}
+
+module Base (
+    module Development.Shake,
+    module Development.Shake.FilePath,
+    module Control.Applicative,
+    module Data.Monoid,
+    Stage (..),
+    Args, arg, Condition,
+    joinArgs, joinArgsWithSpaces,
+    filterOut,
+    ) where
+
+import Development.Shake hiding ((*>))
+import Development.Shake.FilePath
+import Control.Applicative
+import Data.Monoid
+import Data.List
+
+data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum)
+
+type Args = Action [String]
+
+type Condition = Action Bool
+
+instance Monoid a => Monoid (Action a) where
+    mempty = return mempty
+    mappend p q = mappend <$> p <*> q
+
+arg :: [String] -> Args
+arg = return
+
+intercalateArgs :: String -> Args -> Args
+intercalateArgs s args = do
+    as <- args
+    return [intercalate s as]
+
+joinArgsWithSpaces :: Args -> Args
+joinArgsWithSpaces = intercalateArgs " "
+
+joinArgs :: Args -> Args
+joinArgs = intercalateArgs ""
+
+filterOut :: Args -> [String] -> Args
+filterOut args list = filter (`notElem` list) <$> args



More information about the ghc-commits mailing list