Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module contains Dhall's parsing logic
Synopsis
- exprFromText :: String -> Text -> Either ParseError (Expr Src Import)
- exprAndHeaderFromText :: String -> Text -> Either ParseError (Header, Expr Src Import)
- censor :: ParseError -> ParseError
- createHeader :: Text -> Header
- expr :: Parser (Expr Src Import)
- exprA :: Parser a -> Parser (Expr Src a)
- newtype Header = Header Text
- data Src = Src {}
- data SourcedException e = SourcedException Src e
- data ParseError = ParseError {}
- newtype Parser a = Parser {}
Utilities
:: String | User-friendly name describing the input expression, used in parsing error messages |
-> Text | Input expression to parse |
-> Either ParseError (Expr Src Import) |
Parse an expression from Text
containing a Dhall program
exprAndHeaderFromText Source #
:: String | User-friendly name describing the input expression, used in parsing error messages |
-> Text | Input expression to parse |
-> Either ParseError (Header, Expr Src Import) |
Like exprFromText
but also returns the leading comments and whitespace
(i.e. header) up to the last newline before the code begins
In other words, if you have a Dhall file of the form:
-- Comment 1 {- Comment -} 2
Then this will preserve Comment 1
, but not Comment 2
This is used by dhall-format
to preserve leading comments and whitespace
censor :: ParseError -> ParseError Source #
Replace the source code with spaces when rendering error messages
This utility is used to implement the --censor
flag
createHeader :: Text -> Header Source #
Create a header with stripped leading spaces and trailing newlines
Parsers
exprA :: Parser a -> Parser (Expr Src a) Source #
Deprecated: Support for parsing custom imports will be dropped in a future release
Parser for a top-level Dhall expression. The expression is parameterized over any parseable type, allowing the language to be extended as needed.
Types
A header corresponds to the leading comment at the top of a Dhall file.
The header includes comment characters but is stripped of leading spaces and trailing newlines
Source code extract
Instances
Eq Src Source # | |
Data Src Source # | |
Defined in Dhall.Src gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Src -> c Src # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Src # dataTypeOf :: Src -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Src) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Src) # gmapT :: (forall b. Data b => b -> b) -> Src -> Src # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Src -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Src -> r # gmapQ :: (forall d. Data d => d -> u) -> Src -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Src -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Src -> m Src # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Src -> m Src # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Src -> m Src # | |
Ord Src Source # | |
Show Src Source # | |
Generic Src Source # | |
NFData Src Source # | |
Pretty Src Source # | |
Lift Src Source # | |
type Rep Src Source # | |
Defined in Dhall.Src type Rep Src = D1 ('MetaData "Src" "Dhall.Src" "dhall-1.41.2-CygVEUAXWhKKGHhZSAzzm9" 'False) (C1 ('MetaCons "Src" 'PrefixI 'True) (S1 ('MetaSel ('Just "srcStart") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SourcePos) :*: (S1 ('MetaSel ('Just "srcEnd") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SourcePos) :*: S1 ('MetaSel ('Just "srcText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) |
data SourcedException e Source #
An exception annotated with a Src
span
Instances
Show e => Show (SourcedException e) Source # | |
Defined in Dhall.Parser.Combinators showsPrec :: Int -> SourcedException e -> ShowS # show :: SourcedException e -> String # showList :: [SourcedException e] -> ShowS # | |
Exception e => Exception (SourcedException e) Source # | |
Defined in Dhall.Parser.Combinators toException :: SourcedException e -> SomeException # fromException :: SomeException -> Maybe (SourcedException e) # displayException :: SourcedException e -> String # |
data ParseError Source #
A parsing error
Instances
Show ParseError Source # | |
Defined in Dhall.Parser showsPrec :: Int -> ParseError -> ShowS # show :: ParseError -> String # showList :: [ParseError] -> ShowS # | |
Exception ParseError Source # | |
Defined in Dhall.Parser toException :: ParseError -> SomeException # fromException :: SomeException -> Maybe ParseError # displayException :: ParseError -> String # |
A Parser
that is almost identical to
Text.Megaparsec.
except treating Haskell-style
comments as whitespaceParsec