module ParsedOFL where
+import TargetMapping
import Data.Map as Map (Map, lookup, insertWithKey, empty)
import Data.List (foldl')
-- The symbol table
data SymbolType = ValueTag BaseType [IndexType] | IndexTag IndexType deriving Show
type SymbolTable = Map String SymbolType
+type MappingTable = Map String TargetType
data OFL = OFL {
symbols :: SymbolTable,
- assignments :: [Assignment]
+ assignments :: [Assignment],
+ targetMappings :: MappingTable
} deriving Show
-- Symbol table manipulators
addValueDeclaration ofl name baseType indices = ofl { symbols = symbols' }
where symbols' = insertWithKey errorOnDuplicate name (ValueTag baseType indices) (symbols ofl)
+addTargetMapping :: OFL -> String -> TargetType -> OFL
+addTargetMapping ofl name properties = ofl { targetMappings = targetMappings' }
+ where targetMappings' = insertWithKey errorOnDuplicate name properties (targetMappings ofl)
+
addIndexDeclaration :: OFL -> String -> IndexType -> OFL
addIndexDeclaration ofl name indexType = ofl { symbols = symbols' }
where symbols' = insertWithKey errorOnDuplicate name (IndexTag indexType) (symbols ofl)
getType ofl (Derivative e _) = getType ofl e
emptyOFL :: OFL
-emptyOFL = OFL { assignments = [], symbols = Map.empty }
+emptyOFL = OFL { assignments = [], symbols = Map.empty, targetMappings = Map.empty }
-- Validation
data ValidationError = Message String deriving Show
module Parsing where
import ParsedOFL
+import TargetMapping
import Data.List (foldl1')
import Text.Parsec
import Text.Parsec.Expr
oflKeywords :: [String]
oflKeywords = map show [minBound::IndexType ..] ++
map show [minBound::BaseType ..] ++
- ["^", "+", "-", "*", "/", "laplacian", "inner", "sum", "derivative", "r", "target"]
+ ["^", "+", "-", "*", "/", "=", "laplacian", "inner", "sum", "derivative", "r", "target"]
oflDef = emptyDef {
commentStart = "",
brackets = lBrackets,
symbol = lSymbol,
parens = lParens,
- naturalOrFloat = lNaturalOrFloat
+ naturalOrFloat = lNaturalOrFloat,
+ stringLiteral = lStringLiteral
} = makeTokenParser oflDef
oflOperatorTable = [[Infix (do _ <- lSymbol "^"; return (\x y -> Power x y)) AssocLeft],
_ <- many1 parseDeclaration
_ <- many1 parseAssignment
target <- parseTarget
- _ <- many1 anyChar
+ _ <- many parseBinding
+ _ <- many anyChar
eof
getState
+parseBinding = do
+ _ <- lSymbol "Variable" <|> lSymbol "Parameter"
+ ident <- parseIdentifier
+ _ <- lSymbol "="
+ targetType <- (parseFortranParam <|> parsePPDFunctionSet)
+ modifyState(\x -> addTargetMapping x ident targetType)
+
+parseFortranParam = do
+ _ <- lSymbol "fortran_param"
+ _ <- lSymbol "with"
+ properties <- lCommaSep parseFortranParamProperty
+ return $ FortranParameter properties
+
+parseFortranParamProperty = do
+ (parseNameProperty <|> parseTypeProperty <|> parseSpaceProperty <|> parseIndexedProperty) where
+ parseNameProperty = do _ <- lSymbol "name"; name <- lParens lStringLiteral; return $ ParamName name
+ parseTypeProperty = do _ <- lSymbol "type"; fType <- lParens parseFortranType; return $ ParamType fType
+ parseSpaceProperty = do _ <- lSymbol "space"; info <- lParens parseSpaceInfo; return $ Space info
+ parseSpaceInfo = do
+ _ <- lSymbol "psinc_fine_grid"; indices <- lParens $ lCommaSep1 lIdentifier; return $ FinePsinc indices
+ <|> do _ <- lSymbol "psinc_coarse_grid"; indices <- lParens $ lCommaSep1 lIdentifier; return $ CoarsePsinc indices
+ parseIndexedProperty = do _ <- lSymbol "indexed"; indices <- lParens $ lCommaSep1 lIdentifier; return $ Indexed indices
+
+parseFortranType = do
+ baseType <- parseBaseType;
+ maybeIndices <- optionMaybe parseArrayIndices
+ case maybeIndices of
+ Nothing -> return baseType
+ Just indices -> return $ Array baseType indices
+ where
+ parseArrayIndices = do
+ indices <- lParens $ lCommaSep1 parseArrayIndex
+ return indices
+ parseArrayIndex = do
+ _ <- lSymbol ":"; return UnnamedIndex
+ <|> do name <- lIdentifier; return $ NamedIndex name
+ parseBaseType = do
+ _ <- lSymbol "spam3"; return SPAM3
+ <|> do _ <- lSymbol "integer"; return Integer
+ <|> do _ <- lSymbol "double"; return Double
+ <|> do _ <- lSymbol "func_basis"; return FunctionBasis
+
+parsePPDFunctionSet = do
+ _ <- lSymbol "ppd_function_set"
+ _ <- lSymbol "with"
+ properties <- lCommaSep parsePPDFunctionSetProperty
+ return $ PPDFunctionSet properties
+
+parsePPDFunctionSetProperty = do
+ parseBasisProperty <|> parseDataProperty where
+ parseBasisProperty = do _ <- lSymbol "basis"; ident <- lParens lIdentifier; return $ PPDBasis ident
+ parseDataProperty = do _ <- lSymbol "data"; ident <- lParens lIdentifier; return $ PPDData ident
+
parseAsOFL inputString = runParser parseOFL emptyOFL "(unknown)" inputString