-- | Parses a file in OPL's @.dat@. module AM3.DatParser ( -- * Types Assig(..) , Value(..) -- * Parser , pdat -- * AST traversal , flatten ) where import Control.Monad import Text.Megaparsec hiding (fromFile) import Text.Megaparsec.ByteString.Lazy import Text.Megaparsec.Lexer (decimal) -- | An identifier is assigned a 'Value'. data Assig = Assig String Value deriving (Show) -- | A 'Value' can either be an integer or a list of 'Value's. data Value = Num Int | List [Value] deriving (Show) -- | Traversal of the AST in inorder. flatten :: Value -> [Int] flatten (Num x) = [x] flatten (List xs) = concatMap flatten xs plist :: Parser Value plist = List <$> between openSquare closeSquare (many pvalue) pvalue :: Parser Value pvalue = pnum <|> plist openSquare :: Parser () openSquare = void (char '[') <* space closeSquare :: Parser () closeSquare = void (char ']') <* space pnum :: Parser Value pnum = Num . fromIntegral <$> decimal <* space semicolon :: Parser () semicolon = void (char ';') <* space equals :: Parser () equals = void (char '=') <* space identifier :: Parser String identifier = some letterChar <* space passig :: Parser Assig passig = do ident <- identifier equals v <- pvalue semicolon return (Assig ident v) -- | Parser of a @.dat@ file. pdat :: Parser [Assig] pdat = space >> many passig