[commit: ghc] wip/nfs-locking: Add apply function for transforming expressions. (505302b)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:00:17 UTC 2017


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

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

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

commit 505302b7e32640ed8782bbf6cb45c02d0c58fe0f
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Fri Jul 24 04:10:50 2015 +0100

    Add apply function for transforming expressions.


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

505302b7e32640ed8782bbf6cb45c02d0c58fe0f
 src/Expression.hs | 21 +++++++++++++--------
 1 file changed, 13 insertions(+), 8 deletions(-)

diff --git a/src/Expression.hs b/src/Expression.hs
index f33e236..7ac380d 100644
--- a/src/Expression.hs
+++ b/src/Expression.hs
@@ -6,7 +6,8 @@ module Expression (
     Expr, DiffExpr, fromDiffExpr,
     Predicate, PredicateLike (..), applyPredicate, (??),
     Args, Ways, Packages,
-    append, appendM, remove, appendSub, appendSubD, filterSub, removeSub,
+    apply, append, appendM, remove,
+    appendSub, appendSubD, filterSub, removeSub,
     interpret, interpretExpr,
     stage, package, builder, file, way
     ) where
@@ -57,15 +58,19 @@ type Packages  = DiffExpr [Package]
 type Ways      = DiffExpr [Way]
 
 -- Basic operations on expressions:
--- 1) append something to an expression
+-- 1) transform an expression by applying a given function
+apply :: (a -> a) -> DiffExpr a
+apply = return . Diff
+
+-- 2) append something to an expression
 append :: Monoid a => a -> DiffExpr a
-append x = return . Diff $ (<> x)
+append x = apply (<> x)
 
--- 2) remove given elements from a list expression
+-- 3) remove given elements from a list expression
 remove :: Eq a => [a] -> DiffExpr [a]
-remove xs = return . Diff $ filter (`notElem` xs)
+remove xs = apply . filter $ (`notElem` xs)
 
--- 3) apply a predicate to an expression
+-- 4) apply a predicate to an expression
 applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a
 applyPredicate predicate expr = do
     bool <- predicate
@@ -105,7 +110,7 @@ appendM mx = lift mx >>= append
 appendSub :: String -> [String] -> Args
 appendSub prefix xs
     | xs' == [] = mempty
-    | otherwise = return . Diff $ go False
+    | otherwise = apply . go $ False
   where
     xs' = filter (/= "") xs
     go True  []     = []
@@ -120,7 +125,7 @@ appendSubD :: String -> Args -> Args
 appendSubD prefix diffExpr = fromDiffExpr diffExpr >>= appendSub prefix
 
 filterSub :: String -> (String -> Bool) -> Args
-filterSub prefix p = return . Diff $ map filterSubstr
+filterSub prefix p = apply . map $ filterSubstr
   where
     filterSubstr s
         | prefix `isPrefixOf` s = unwords . filter p . words $ s



More information about the ghc-commits mailing list