]> git.unchartedbackwaters.co.uk Git - francis/ofc.git/commitdiff
Replace folds with strict versions.
authorFrancis Russell <francis@unchartedbackwaters.co.uk>
Sat, 15 Sep 2012 16:56:08 +0000 (17:56 +0100)
committerFrancis Russell <francis@unchartedbackwaters.co.uk>
Sat, 15 Sep 2012 16:56:08 +0000 (17:56 +0100)
src/ParsedOFL.hs
src/Parsing.hs

index 27bbd2cd3ed36de65e507ea9a8a20251179606d4..95ee451df1b5ce8da880b9f22e7d90a13dd8a60a 100644 (file)
@@ -1,5 +1,6 @@
 module ParsedOFL where
 import Data.Map as Map (Map, lookup, insertWithKey, empty)
+import Data.List (foldl')
 
 -- The top-level types
 data BaseType = RealType | FunctionType | IntegerType deriving (Eq, Enum, Bounded)
@@ -151,7 +152,7 @@ validateExpression :: OFL -> Expression -> ValidationResult
 
 validateExpression ofl (IndexedIdentifier name indices) = do
   valueExists ofl name
-  foldl (>>) validationSuccess $ map (indexExists ofl) indices
+  foldl' (>>) validationSuccess $ map (indexExists ofl) indices
   let indexTypes = map (getIndexType ofl) indices in
     case indexTypes == (getIndices ofl name) of
       True -> validationSuccess
index 0fc091472674a24b097db9c2b7ffd2d472a06578..9cbc2841b766a98aa46f6b1d2a36ede3bc8e703c 100644 (file)
@@ -1,5 +1,6 @@
 module Parsing where
 import ParsedOFL
+import Data.List (foldl1')
 import Text.Parsec
 import Text.Parsec.Expr
 import Text.Parsec.Token
@@ -41,8 +42,8 @@ oflOperatorTable = [[Infix  (do _ <- lSymbol "^"; return (\x y -> Power x y)) As
                     ,Infix  (do _ <- lSymbol "-"; return (\x y -> Sub x y)) AssocLeft]
                    ]
 
-parseType = foldl1 (<|>) [do lReserved $ show t; return t | t <- [minBound::BaseType ..]]
-parseIndex = foldl1 (<|>) [do lReserved $ show t; return t | t <- [minBound::IndexType ..]]
+parseType = foldl1' (<|>) [do lReserved $ show t; return t | t <- [minBound::BaseType ..]]
+parseIndex = foldl1' (<|>) [do lReserved $ show t; return t | t <- [minBound::IndexType ..]]
 
 parseDeclaration :: Parsec String OFL ()
 parseDeclaration = parseValueDeclaration <|> parseIndexDeclaration
@@ -52,14 +53,14 @@ parseValueDeclaration = do
   valueType <- parseType
   indices <- option [] (lBrackets $ lCommaSep parseIndex)
   names <- lCommaSep1 parseIdentifier
-  foldl1 (>>) [modifyState(\x -> addValueDeclaration x name valueType indices) | name <- names]
+  foldl1' (>>) [modifyState(\x -> addValueDeclaration x name valueType indices) | name <- names]
   <?> "value declaration"
 
 parseIndexDeclaration :: Parsec String OFL ()
 parseIndexDeclaration = do
   indexType <- parseIndex
   names <- lCommaSep1 parseIdentifier
-  foldl1 (>>) [modifyState(\x -> addIndexDeclaration x name indexType) | name <- names]
+  foldl1' (>>) [modifyState(\x -> addIndexDeclaration x name indexType) | name <- names]
   <?> "index declaration"
 
 parseIdentifier = lIdentifier <?> "identifier"