[commit: packages/filepath] master: Remove the Expr constructor from the Generate module (259f9e2)

git at git.haskell.org git at git.haskell.org
Thu Mar 19 11:36:40 UTC 2015


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

On branch  : master
Link       : http://git.haskell.org/packages/filepath.git/commitdiff/259f9e21e0cdacb8b44dcab01861b5fb12f87462

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

commit 259f9e21e0cdacb8b44dcab01861b5fb12f87462
Author: Neil Mitchell <ndmitchell at gmail.com>
Date:   Wed Oct 29 09:27:20 2014 +0000

    Remove the Expr constructor from the Generate module


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

259f9e21e0cdacb8b44dcab01861b5fb12f87462
 Generate.hs | 14 ++++----------
 1 file changed, 4 insertions(+), 10 deletions(-)

diff --git a/Generate.hs b/Generate.hs
index 274e1ca..c990a05 100755
--- a/Generate.hs
+++ b/Generate.hs
@@ -9,14 +9,9 @@ import System.Directory
 import System.IO
 
 
-data Test
-    = Expr String
-    | Test [String] String
+data Test = Test {testVars :: [String], _testBody :: String}
       deriving Show
 
-isExpr (Expr{}) = True
-isExpr _ = False
-
 
 main :: IO ()
 main = do
@@ -41,7 +36,6 @@ getTest (line,xs) | "-- > " `isPrefixOf` xs = f $ drop 5 xs
             | "Posix:"   `isPrefixOf` x = let res = grabTest (drop 6 x) in [g "P" res]
             | otherwise = let res = grabTest x in [g "W" res, g "P" res]
 
-        g p (Expr x) = (line,Expr (h p x))
         g p (Test a x) = (line,Test a (h p x))
         
         h p x = joinLex $ map (addPrefix p) $ makeValid $ splitLex x
@@ -61,7 +55,7 @@ fpops = ["</>","<.>"]
 
 
 grabTest :: String -> Test
-grabTest x = if null free then Expr x else Test free x
+grabTest x = Test free x
     where
         free = sort $ nub [x | x <- lexs, length x == 1, all isAlpha x]
         lexs = splitLex x
@@ -102,7 +96,7 @@ rejoinTests xs = unlines $
 genTests :: [(Int, Test)] -> String
 genTests xs = rejoinTests $ concatMap f $ zip [1..] (one++many)
     where
-        (one,many) = partition (isExpr . snd) xs
+        (one,many) = partition (null . testVars . snd) xs
 
         f (tno,(lno,test)) =
             [" putStrLn \"Test " ++ show tno ++ ", from line " ++ show lno ++ "\""
@@ -110,7 +104,7 @@ genTests xs = rejoinTests $ concatMap f $ zip [1..] (one++many)
 
 -- the result must be a line of the type "IO ()"
 genTest :: Test -> String
-genTest (Expr x) = "test (" ++ x ++ ")"
+genTest (Test [] x) = "test (" ++ x ++ ")"
 genTest (Test free x) = "test (\\" ++ concatMap ((' ':) . f) free ++ " -> (" ++ x ++ "))"
     where
         f [a] | a >= 'x' = "(QFilePath " ++ [a] ++ ")"



More information about the ghc-commits mailing list