Safe Haskell | None |
---|---|
Language | Haskell98 |
- class Inputable a where
- type Parser = Parsec String Integer
- lexer :: GenTokenParser String u Identity
- reserved :: String -> ParsecT String u Identity ()
- reservedOp :: String -> ParsecT String u Identity ()
- parens :: ParsecT String u Identity a -> ParsecT String u Identity a
- brackets :: ParsecT String u Identity a -> ParsecT String u Identity a
- angles :: ParsecT String u Identity a -> ParsecT String u Identity a
- braces :: ParsecT String u Identity a -> ParsecT String u Identity a
- semi :: ParsecT String u Identity String
- comma :: ParsecT String u Identity String
- colon :: ParsecT String u Identity String
- dcolon :: Stream s m Char => ParsecT s u m String
- whiteSpace :: ParsecT String u Identity ()
- blanks :: Stream s m Char => ParsecT s u m [Char]
- pairP :: Parser a -> Parser z -> Parser b -> Parser (a, b)
- lowerIdP :: Parser Symbol
- upperIdP :: Parser Symbol
- symbolP :: Parser Symbol
- constantP :: Parser Constant
- integer :: Stream s m Char => ParsecT s u m Integer
- bindP :: ParsecT String Integer Identity Symbol
- sortP :: Parser Sort
- mkQual :: Symbol -> [(Symbol, Sort)] -> Expr -> SourcePos -> Qualifier
- exprP :: Parser Expr
- predP :: Parser Expr
- funAppP :: ParsecT String Integer Identity Expr
- qualifierP :: Parser Sort -> ParsecT String Integer Identity Qualifier
- refaP :: Parser Expr
- refP :: Parser (Reft -> a) -> Parser a
- refDefP :: Symbol -> Parser Expr -> Parser (Reft -> a) -> Parser a
- refBindP :: Parser Symbol -> Parser Expr -> Parser (Reft -> a) -> Parser a
- bvSortP :: ParsecT String u Identity Sort
- condIdP :: HashSet Char -> (String -> Bool) -> Parser Symbol
- locParserP :: Parser a -> Parser (Located a)
- locLowerIdP :: Parser (Located Symbol)
- locUpperIdP :: Parser (Located Symbol)
- freshIntP :: Parser Integer
- doParse' :: Num u => ParsecT String u Identity a -> SourceName -> String -> a
- parseFromFile :: Parser b -> SourceName -> IO b
- remainderP :: Monad m => ParsecT t1 u m t -> ParsecT t1 u m (t, t1, SourcePos)
- isSmall :: Char -> Bool
Top Level Class for Parseable Values
Top Level Class for Parseable Values
Lexer to add new tokens
Some Important keyword and parsers
whiteSpace :: ParsecT String u Identity () Source
Parsing basic entities
Parsing recursive entities
qualifierP :: Parser Sort -> ParsecT String Integer Identity Qualifier Source
Parsing Qualifiers ---------------------------------------------
Some Combinators
Add a Location to a parsed value
locParserP :: Parser a -> Parser (Located a) Source
locLowerIdP :: Parser (Located Symbol) Source
locUpperIdP :: Parser (Located Symbol) Source
Getting a Fresh Integer while parsing
Parsing Function
parseFromFile :: Parser b -> SourceName -> IO b Source