Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- parseFromFile :: FilePath -> Text -> Either (NonEmpty ParserError) Module
- parseFromFiles :: forall m k. MonadError MultipleErrors m => (k -> FilePath) -> [(k, Text)] -> m [(k, Module)]
- parseModuleFromFile :: FilePath -> Text -> Either (NonEmpty ParserError) (PartialResult Module)
- parseModulesFromFiles :: forall m k. MonadError MultipleErrors m => (k -> FilePath) -> [(k, Text)] -> m [(k, PartialResult Module)]
- unwrapParserError :: forall m a. MonadError MultipleErrors m => FilePath -> Either (NonEmpty ParserError) a -> m a
- toMultipleErrors :: FilePath -> NonEmpty ParserError -> MultipleErrors
- toPositionedError :: FilePath -> ParserError -> ErrorMessage
- pureResult :: a -> PartialResult a
- module Language.PureScript.CST.Convert
- module Language.PureScript.CST.Errors
- module Language.PureScript.CST.Lexer
- type Parser = ParserM ParserError ParserState
- newtype ParserM e s a = Parser (forall r. s -> (s -> e -> r) -> (s -> a -> r) -> r)
- data ParserState = ParserState {
- parserBuff :: [LexResult]
- parserErrors :: [ParserError]
- type LexResult = Either (LexState, ParserError) SourceToken
- runParser :: ParserState -> Parser a -> (ParserState, Either (NonEmpty ParserError) a)
- runTokenParser :: Parser a -> [LexResult] -> Either (NonEmpty ParserError) a
- module Language.PureScript.CST.Parser
- module Language.PureScript.CST.Print
- module Language.PureScript.CST.Types
Documentation
parseFromFile :: FilePath -> Text -> Either (NonEmpty ParserError) Module Source #
parseFromFiles :: forall m k. MonadError MultipleErrors m => (k -> FilePath) -> [(k, Text)] -> m [(k, Module)] Source #
parseModuleFromFile :: FilePath -> Text -> Either (NonEmpty ParserError) (PartialResult Module) Source #
parseModulesFromFiles :: forall m k. MonadError MultipleErrors m => (k -> FilePath) -> [(k, Text)] -> m [(k, PartialResult Module)] Source #
unwrapParserError :: forall m a. MonadError MultipleErrors m => FilePath -> Either (NonEmpty ParserError) a -> m a Source #
toPositionedError :: FilePath -> ParserError -> ErrorMessage Source #
pureResult :: a -> PartialResult a Source #
type Parser = ParserM ParserError ParserState Source #
newtype ParserM e s a Source #
A bare bones, CPS'ed `StateT s (Except e) a`.
Parser (forall r. s -> (s -> e -> r) -> (s -> a -> r) -> r) |
data ParserState Source #
ParserState | |
|
Instances
Show ParserState Source # | |
Defined in Language.PureScript.CST.Monad showsPrec :: Int -> ParserState -> ShowS # show :: ParserState -> String # showList :: [ParserState] -> ShowS # |
type LexResult = Either (LexState, ParserError) SourceToken Source #
runParser :: ParserState -> Parser a -> (ParserState, Either (NonEmpty ParserError) a) Source #
runTokenParser :: Parser a -> [LexResult] -> Either (NonEmpty ParserError) a Source #