| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
LText.Expr
Contents
Synopsis
- data Expr
- type MonadPrettyPrint m = (MonadThrow m, MonadIO m)
- ppExpr :: MonadPrettyPrint m => Expr -> m String
- data ScopeUse
- data ParseState
- initParseState :: ParseState
- data ParseError
- handleParseError :: ParseError -> IO a
- type MonadParse m = (MonadState ParseState m, MonadThrow m, MonadIO m)
- runParse :: Text -> IO Expr
- runParserT :: StateT ParseState IO a -> IO a
- parseExpr :: MonadParse m => Text -> m Expr
- expr :: MonadParse m => [Lexeme] -> m Expr
- data Lexeme
- lex :: Parser [Lexeme]
- lambda :: Parser Lexeme
- arrow :: Parser Lexeme
- ident :: Parser Lexeme
- bracketed :: Parser Lexeme
Documentation
Constructors
| Abs String Expr | |
| App Expr Expr | |
| Var String | |
| Lit | |
Fields
| |
| Concat | |
Fields
| |
type MonadPrettyPrint m = (MonadThrow m, MonadIO m) Source #
data ParseState Source #
Constructors
| InsideLambda | ..-> |
| Scope ScopeUse | (..) |
Instances
| Show ParseState Source # | |
Defined in LText.Expr Methods showsPrec :: Int -> ParseState -> ShowS # show :: ParseState -> String # showList :: [ParseState] -> ShowS # | |
| Eq ParseState Source # | |
Defined in LText.Expr | |
data ParseError Source #
Constructors
| BracketsInsideLambda [Lexeme] | |
| LambdaInsideLambda [Lexeme] | |
| LambdaInStaleScope [Lexeme] Expr | |
| ArrowWithoutLambda [Lexeme] | |
| ArrowInScope [Lexeme] | |
| EmptyExpression | |
| LexerError String |
Instances
handleParseError :: ParseError -> IO a Source #
type MonadParse m = (MonadState ParseState m, MonadThrow m, MonadIO m) Source #
runParserT :: StateT ParseState IO a -> IO a Source #