Copyright | (c) 2013-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
At present Alex generates code with too many warnings.
Synopsis
- primLexer :: Config -> Text -> ([Located Token], Position)
- lexer :: Config -> Text -> ([Located Token], Position)
- data Layout
- data Token = Token {}
- data TokenT
- data TokenV
- data TokenKW
- = KW_else
- | KW_extern
- | KW_fin
- | KW_if
- | KW_private
- | KW_include
- | KW_inf
- | KW_lg2
- | KW_lengthFromThen
- | KW_lengthFromThenTo
- | KW_max
- | KW_min
- | KW_module
- | KW_newtype
- | KW_pragma
- | KW_property
- | KW_then
- | KW_type
- | KW_where
- | KW_let
- | KW_x
- | KW_import
- | KW_as
- | KW_hiding
- | KW_infixl
- | KW_infixr
- | KW_infix
- | KW_primitive
- | KW_parameter
- | KW_constraint
- | KW_Prop
- data TokenErr
- data TokenSym
- data TokenW
- data Located a = Located {}
- data Config = Config {
- cfgSource :: !FilePath
- cfgStart :: !Position
- cfgLayout :: !Layout
- cfgPreProc :: PreProc
- cfgAutoInclude :: [FilePath]
- cfgModuleScope :: Bool
- defaultConfig :: Config
Documentation
primLexer :: Config -> Text -> ([Located Token], Position) Source #
Returns the tokens and the last position of the input that we processed. The tokens include whte space tokens.
lexer :: Config -> Text -> ([Located Token], Position) Source #
Returns the tokens in the last position of the input that we processed. White space is removed, and layout processing is done as requested. This stream is fed to the parser.
Instances
Show Token Source # | |
Generic Token Source # | |
NFData Token Source # | |
Defined in Cryptol.Parser.LexerUtils | |
PP Token Source # | |
type Rep Token Source # | |
Defined in Cryptol.Parser.LexerUtils type Rep Token = D1 ('MetaData "Token" "Cryptol.Parser.LexerUtils" "cryptol-2.11.0-KBQWpCBm4GD4lGHyVVV39L" 'False) (C1 ('MetaCons "Token" 'PrefixI 'True) (S1 ('MetaSel ('Just "tokenType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TokenT) :*: S1 ('MetaSel ('Just "tokenText") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) |
Num !Integer !Int !Int | value, base, number of digits |
Frac !Rational !Int | value, base. |
ChrLit !Char | character literal |
Ident ![Text] !Text | (qualified) identifier |
StrLit !String | string literal |
Selector !SelectorType | .hello or .123 |
KW !TokenKW | keyword |
Op !TokenOp | operator |
Sym !TokenSym | symbol |
Virt !TokenV | virtual token (for layout) |
White !TokenW | white space token |
Err !TokenErr | error token |
EOF |
Virtual tokens, inserted by layout processing.
Instances
Eq TokenV Source # | |
Show TokenV Source # | |
Generic TokenV Source # | |
NFData TokenV Source # | |
Defined in Cryptol.Parser.LexerUtils | |
type Rep TokenV Source # | |
Defined in Cryptol.Parser.LexerUtils type Rep TokenV = D1 ('MetaData "TokenV" "Cryptol.Parser.LexerUtils" "cryptol-2.11.0-KBQWpCBm4GD4lGHyVVV39L" 'False) (C1 ('MetaCons "VCurlyL" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "VCurlyR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VSemi" 'PrefixI 'False) (U1 :: Type -> Type))) |
Instances
UnterminatedComment | |
UnterminatedString | |
UnterminatedChar | |
InvalidString | |
InvalidChar | |
LexicalError | |
MalformedLiteral | |
MalformedSelector |
Instances
Eq TokenErr Source # | |
Show TokenErr Source # | |
Generic TokenErr Source # | |
NFData TokenErr Source # | |
Defined in Cryptol.Parser.LexerUtils | |
type Rep TokenErr Source # | |
Defined in Cryptol.Parser.LexerUtils type Rep TokenErr = D1 ('MetaData "TokenErr" "Cryptol.Parser.LexerUtils" "cryptol-2.11.0-KBQWpCBm4GD4lGHyVVV39L" 'False) (((C1 ('MetaCons "UnterminatedComment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnterminatedString" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnterminatedChar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvalidString" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "InvalidChar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LexicalError" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MalformedLiteral" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MalformedSelector" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Bar | |
ArrL | |
ArrR | |
FatArrR | |
Lambda | |
EqDef | |
Comma | |
Semi | |
Dot | |
DotDot | |
DotDotDot | |
DotDotLt | |
Colon | |
BackTick | |
ParenL | |
ParenR | |
BracketL | |
BracketR | |
CurlyL | |
CurlyR | |
TriL | |
TriR | |
Lt | |
Underscore |
Instances
Instances
Eq TokenW Source # | |
Show TokenW Source # | |
Generic TokenW Source # | |
NFData TokenW Source # | |
Defined in Cryptol.Parser.LexerUtils | |
type Rep TokenW Source # | |
Defined in Cryptol.Parser.LexerUtils type Rep TokenW = D1 ('MetaData "TokenW" "Cryptol.Parser.LexerUtils" "cryptol-2.11.0-KBQWpCBm4GD4lGHyVVV39L" 'False) ((C1 ('MetaCons "BlockComment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LineComment" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Space" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DocStr" 'PrefixI 'False) (U1 :: Type -> Type))) |
Instances
Config | |
|