| License | BSD-3-Clause |
|---|---|
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Swarm.Language.Parser.Core
Description
Core data type definitions and utilities for the Swarm language parser.
Synopsis
- data Antiquoting
- data LanguageVersion
- data ParserConfig
- defaultParserConfig :: ParserConfig
- antiquoting :: Lens' ParserConfig Antiquoting
- languageVersion :: Lens' ParserConfig LanguageVersion
- data CommentState = CS {
- _freshLine :: Bool
- _comments :: Seq Comment
- freshLine :: Lens' CommentState Bool
- comments :: Lens' CommentState (Seq Comment)
- type Parser = ReaderT ParserConfig (StateT CommentState (Parsec Void Text))
- type ParserError = ParseErrorBundle Text Void
- runParser :: Parser a -> Text -> Either ParserError (a, Seq Comment)
- runParser' :: ParserConfig -> Parser a -> Text -> Either ParserError (a, Seq Comment)
- runParserTH :: (Monad m, MonadFail m) => (String, Int, Int) -> Parser a -> String -> m a
Parser configuration
data Antiquoting Source #
When parsing a term using a quasiquoter (i.e. something in the Swarm source code that will be parsed at compile time), we want to allow antiquoting, i.e. writing something like $x to refer to an existing Haskell variable. But when parsing a term entered by the user at the REPL, we do not want to allow this syntax.
Constructors
| AllowAntiquoting | |
| DisallowAntiquoting |
Instances
| Show Antiquoting Source # | |
Defined in Swarm.Language.Parser.Core Methods showsPrec :: Int -> Antiquoting -> ShowS # show :: Antiquoting -> String # showList :: [Antiquoting] -> ShowS # | |
| Eq Antiquoting Source # | |
Defined in Swarm.Language.Parser.Core | |
| Ord Antiquoting Source # | |
Defined in Swarm.Language.Parser.Core Methods compare :: Antiquoting -> Antiquoting -> Ordering # (<) :: Antiquoting -> Antiquoting -> Bool # (<=) :: Antiquoting -> Antiquoting -> Bool # (>) :: Antiquoting -> Antiquoting -> Bool # (>=) :: Antiquoting -> Antiquoting -> Bool # max :: Antiquoting -> Antiquoting -> Antiquoting # min :: Antiquoting -> Antiquoting -> Antiquoting # | |
data LanguageVersion Source #
Which version of the Swarm language are we parsing? As a general
rule, we want to support one older version in addition to the
current version, to allow for upgrading code via swarm format.
Constructors
| SwarmLang0_5 | |
| SwarmLangLatest |
Instances
data ParserConfig Source #
Read-only parser configuration.
Comment parsing state
data CommentState Source #
Constructors
| CS | |
Fields
| |
Parser type
type Parser = ReaderT ParserConfig (StateT CommentState (Parsec Void Text)) Source #
type ParserError = ParseErrorBundle Text Void Source #
Running
runParser :: Parser a -> Text -> Either ParserError (a, Seq Comment) Source #
Run a parser on some input text, returning either the result + all collected comments, or a parse error message.
runParser' :: ParserConfig -> Parser a -> Text -> Either ParserError (a, Seq Comment) Source #
Like runParser, but allow configuring with an arbitrary
ParserConfig.