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)
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
module Parsing where
import ParsedOFL
+import Data.List (foldl1')
import Text.Parsec
import Text.Parsec.Expr
import Text.Parsec.Token
,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
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"