Safe Haskell | None |
---|---|
Language | Haskell2010 |
Database.Persist.Quasi.Internal.ModelParser
Synopsis
- data SourceLoc = SourceLoc {
- locFile :: Text
- locStartLine :: Int
- locStartCol :: Int
- data Attribute
- attribute :: Parser Attribute
- attributeContent :: Attribute -> Text
- data Directive = Directive {
- directiveDocCommentBlock :: Maybe DocCommentBlock
- directiveName :: DirectiveName
- directiveAttributes :: [Attribute]
- directivePos :: SourcePos
- directiveContent :: Directive -> [Text]
- data EntityField = EntityField {
- entityFieldDocCommentBlock :: Maybe DocCommentBlock
- entityFieldStrictness :: Maybe FieldStrictness
- entityFieldName :: FieldName
- entityFieldType :: TypeExpr
- entityFieldAttributes :: [Attribute]
- entityFieldPos :: SourcePos
- entityField :: Parser Member
- entityFieldContent :: EntityField -> [Text]
- newtype FieldName = FieldName Text
- fieldName :: Parser FieldName
- data ParsedEntityDef = ParsedEntityDef {
- parsedEntityDefComments :: [Text]
- parsedEntityDefEntityName :: EntityNameHS
- parsedEntityDefIsSum :: Bool
- parsedEntityDefEntityAttributes :: [Attribute]
- parsedEntityDefFields :: [(EntityField, Maybe Text)]
- parsedEntityDefDirectives :: [(Directive, Maybe Text)]
- parsedEntityDefExtras :: Map Text [ExtraLine]
- parsedEntityDefSpan :: Maybe SourceSpan
- parseSource :: PersistSettings -> Maybe SourceLoc -> Text -> ParseResult [ParsedEntityDef]
- memberEntityFields :: Member -> [EntityField]
- data ParserWarning
- parserWarningMessage :: ParserWarning -> String
- type ParseResult a = (Set ParserWarning, Either (ParseErrorBundle String Void) a)
- type CumulativeParseResult a = (Set ParserWarning, Either [EntityParseError] a)
- toCumulativeParseResult :: Monoid a => [ParseResult a] -> CumulativeParseResult a
- renderErrors :: [EntityParseError] -> String
- runConfiguredParser :: PersistSettings -> ExtraState -> Parser a -> String -> String -> InternalParseResult a
- data ParserErrorLevel
- initialExtraState :: ExtraState
Documentation
Source location: file and line/col information. This is half of a SourceSpan
.
Since: 2.16.0.0
Constructors
SourceLoc | |
Fields
|
An attribute of an entity field definition or a directive.
Since: 2.17.1.0
Constructors
Assignment Text Text | |
Parenthetical Text | |
PText Text | |
Quotation Text | Quoted field attributes are deprecated since 2.17.1.0. |
Instances
Show Attribute Source # | |
Eq Attribute Source # | |
Ord Attribute Source # | |
Defined in Database.Persist.Quasi.Internal.ModelParser |
attributeContent :: Attribute -> Text Source #
Converts an attribute into a Text representation for second-stage parsing or presentation to the user
Since: 2.16.0.0
Constructors
Directive | |
Fields
|
directiveContent :: Directive -> [Text] Source #
Converts a directive into a Text representation for second-stage parsing or presentation to the user
Since: 2.17.1.0
data EntityField Source #
Constructors
EntityField | |
Fields
|
Instances
Show EntityField Source # | |
Defined in Database.Persist.Quasi.Internal.ModelParser Methods showsPrec :: Int -> EntityField -> ShowS # show :: EntityField -> String # showList :: [EntityField] -> ShowS # |
entityField :: Parser Member Source #
entityFieldContent :: EntityField -> [Text] Source #
data ParsedEntityDef Source #
Constructors
Instances
Show ParsedEntityDef Source # | |
Defined in Database.Persist.Quasi.Internal.ModelParser Methods showsPrec :: Int -> ParsedEntityDef -> ShowS # show :: ParsedEntityDef -> String # showList :: [ParsedEntityDef] -> ShowS # |
parseSource :: PersistSettings -> Maybe SourceLoc -> Text -> ParseResult [ParsedEntityDef] Source #
memberEntityFields :: Member -> [EntityField] Source #
Represents an entity member as a list of EntityFields
Since: 2.16.0.0
data ParserWarning Source #
Since: 2.16.0.0
Instances
Show ParserWarning Source # | |
Defined in Database.Persist.Quasi.PersistSettings.Internal Methods showsPrec :: Int -> ParserWarning -> ShowS # show :: ParserWarning -> String # showList :: [ParserWarning] -> ShowS # | |
Eq ParserWarning Source # | |
Defined in Database.Persist.Quasi.PersistSettings.Internal Methods (==) :: ParserWarning -> ParserWarning -> Bool # (/=) :: ParserWarning -> ParserWarning -> Bool # | |
Ord ParserWarning Source # | |
Defined in Database.Persist.Quasi.PersistSettings.Internal Methods compare :: ParserWarning -> ParserWarning -> Ordering # (<) :: ParserWarning -> ParserWarning -> Bool # (<=) :: ParserWarning -> ParserWarning -> Bool # (>) :: ParserWarning -> ParserWarning -> Bool # (>=) :: ParserWarning -> ParserWarning -> Bool # max :: ParserWarning -> ParserWarning -> ParserWarning # min :: ParserWarning -> ParserWarning -> ParserWarning # |
parserWarningMessage :: ParserWarning -> String Source #
Uses errorBundlePretty
to render a parser warning.
Since: 2.16.0.0
type ParseResult a = (Set ParserWarning, Either (ParseErrorBundle String Void) a) Source #
Result of parsing a single source text.
Since: 2.16.0.0
type CumulativeParseResult a = (Set ParserWarning, Either [EntityParseError] a) Source #
Cumulative result of parsing multiple source texts.
Since: 2.16.0.0
toCumulativeParseResult :: Monoid a => [ParseResult a] -> CumulativeParseResult a Source #
renderErrors :: [EntityParseError] -> String Source #
Renders a list of EntityParseErrors as a String using errorBundlePretty
,
separated by line breaks.
@since 2.16.0.0
runConfiguredParser :: PersistSettings -> ExtraState -> Parser a -> String -> String -> InternalParseResult a Source #
Run a parser using provided PersistSettings and ExtraState @since 2.16.0.0
data ParserErrorLevel Source #
Since: 2.16.0.0
Constructors
LevelError | |
LevelWarning |
Instances
Show ParserErrorLevel Source # | |
Defined in Database.Persist.Quasi.PersistSettings.Internal Methods showsPrec :: Int -> ParserErrorLevel -> ShowS # show :: ParserErrorLevel -> String # showList :: [ParserErrorLevel] -> ShowS # | |
Eq ParserErrorLevel Source # | |
Defined in Database.Persist.Quasi.PersistSettings.Internal Methods (==) :: ParserErrorLevel -> ParserErrorLevel -> Bool # (/=) :: ParserErrorLevel -> ParserErrorLevel -> Bool # |
initialExtraState :: ExtraState Source #