| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Cryptol.Parser.Token
Synopsis
- data Token = Token {}
- data TokenV
- data TokenW
- data TokenKW
- = KW_else
- | KW_fin
- | KW_if
- | KW_case
- | KW_of
- | KW_private
- | KW_include
- | KW_inf
- | KW_lg2
- | KW_lengthFromThen
- | KW_lengthFromThenTo
- | KW_max
- | KW_min
- | KW_module
- | KW_submodule
- | KW_newtype
- | KW_enum
- | 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_interface
- | KW_foreign
- | KW_Prop
- | KW_by
- | KW_down
- data TokenOp
- data TokenSym
- data TokenErr
- data SelectorType
- data TokenT
Documentation
Instances
| Generic Token Source # | |||||
Defined in Cryptol.Parser.Token Associated Types
| |||||
| Show Token Source # | |||||
| PP Token Source # | |||||
| NFData Token Source # | |||||
Defined in Cryptol.Parser.Token | |||||
| type Rep Token Source # | |||||
Defined in Cryptol.Parser.Token type Rep Token = D1 ('MetaData "Token" "Cryptol.Parser.Token" "cryptol-3.4.0-BjfKfo7TRzHF21bOobh6Es" 'False) (C1 ('MetaCons "Token" 'PrefixI 'True) (S1 ('MetaSel ('Just "tokenType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TokenT) :*: S1 ('MetaSel ('Just "tokenText") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) | |||||
Virtual tokens, inserted by layout processing.
Instances
| Generic TokenV Source # | |||||
Defined in Cryptol.Parser.Token Associated Types
| |||||
| Show TokenV Source # | |||||
| NFData TokenV Source # | |||||
Defined in Cryptol.Parser.Token | |||||
| Eq TokenV Source # | |||||
| type Rep TokenV Source # | |||||
Defined in Cryptol.Parser.Token type Rep TokenV = D1 ('MetaData "TokenV" "Cryptol.Parser.Token" "cryptol-3.4.0-BjfKfo7TRzHF21bOobh6Es" '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))) | |||||
Constructors
| BlockComment | |
| LineComment | |
| Space | |
| DocStr |
Instances
| Generic TokenW Source # | |||||
Defined in Cryptol.Parser.Token Associated Types
| |||||
| Show TokenW Source # | |||||
| NFData TokenW Source # | |||||
Defined in Cryptol.Parser.Token | |||||
| Eq TokenW Source # | |||||
| type Rep TokenW Source # | |||||
Defined in Cryptol.Parser.Token type Rep TokenW = D1 ('MetaData "TokenW" "Cryptol.Parser.Token" "cryptol-3.4.0-BjfKfo7TRzHF21bOobh6Es" '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))) | |||||
Constructors
Instances
| Generic TokenKW Source # | |||||
Defined in Cryptol.Parser.Token Associated Types
| |||||
| Show TokenKW Source # | |||||
| NFData TokenKW Source # | |||||
Defined in Cryptol.Parser.Token | |||||
| Eq TokenKW Source # | |||||
| type Rep TokenKW Source # | |||||
Defined in Cryptol.Parser.Token type Rep TokenKW = D1 ('MetaData "TokenKW" "Cryptol.Parser.Token" "cryptol-3.4.0-BjfKfo7TRzHF21bOobh6Es" 'False) (((((C1 ('MetaCons "KW_else" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_fin" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KW_if" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_case" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "KW_of" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_private" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KW_include" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KW_inf" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_lg2" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "KW_lengthFromThen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_lengthFromThenTo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KW_max" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KW_min" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_module" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KW_submodule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_newtype" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KW_enum" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KW_pragma" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_property" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "KW_then" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_type" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KW_where" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_let" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "KW_x" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_import" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KW_as" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KW_hiding" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_infixl" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "KW_infixr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_infix" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KW_primitive" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KW_parameter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_constraint" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KW_interface" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_foreign" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KW_Prop" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KW_by" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KW_down" 'PrefixI 'False) (U1 :: Type -> Type))))))) | |||||
The named operators are a special case for parsing types, and Other is
used for all other cases that lexed as an operator.
Instances
Constructors
| Bar | |
| ArrL | |
| ArrR | |
| FatArrR | |
| Lambda | |
| EqDef | |
| Comma | |
| Semi | |
| Dot | |
| DotDot | |
| DotDotDot | |
| DotDotLt | |
| DotDotGt | |
| Colon | |
| BackTick | |
| ParenL | |
| ParenR | |
| BracketL | |
| BracketR | |
| CurlyL | |
| CurlyR | |
| TriL | |
| TriR | |
| Lt | |
| Gt | |
| Underscore |
Instances
| Generic TokenSym Source # | |||||
Defined in Cryptol.Parser.Token Associated Types
| |||||
| Show TokenSym Source # | |||||
| NFData TokenSym Source # | |||||
Defined in Cryptol.Parser.Token | |||||
| Eq TokenSym Source # | |||||
| type Rep TokenSym Source # | |||||
Defined in Cryptol.Parser.Token type Rep TokenSym = D1 ('MetaData "TokenSym" "Cryptol.Parser.Token" "cryptol-3.4.0-BjfKfo7TRzHF21bOobh6Es" 'False) ((((C1 ('MetaCons "Bar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ArrL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArrR" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "FatArrR" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Lambda" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqDef" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Comma" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Semi" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Dot" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DotDot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DotDotDot" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DotDotLt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DotDotGt" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Colon" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BackTick" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ParenL" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ParenR" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BracketL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BracketR" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CurlyL" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CurlyR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TriL" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TriR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Lt" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Gt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Underscore" 'PrefixI 'False) (U1 :: Type -> Type)))))) | |||||
Constructors
| UnterminatedComment | |
| UnterminatedString | |
| UnterminatedChar | |
| InvalidString | |
| InvalidChar | |
| LexicalError | |
| MalformedLiteral | |
| MalformedSelector | |
| InvalidIndentation TokenT |
Instances
| Generic TokenErr Source # | |||||
Defined in Cryptol.Parser.Token Associated Types
| |||||
| Show TokenErr Source # | |||||
| NFData TokenErr Source # | |||||
Defined in Cryptol.Parser.Token | |||||
| Eq TokenErr Source # | |||||
| type Rep TokenErr Source # | |||||
Defined in Cryptol.Parser.Token type Rep TokenErr = D1 ('MetaData "TokenErr" "Cryptol.Parser.Token" "cryptol-3.4.0-BjfKfo7TRzHF21bOobh6Es" '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) :+: C1 ('MetaCons "InvalidIndentation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TokenT)))))) | |||||
data SelectorType Source #
Constructors
| RecordSelectorTok Text | |
| TupleSelectorTok Int |
Instances
| Generic SelectorType Source # | |||||
Defined in Cryptol.Parser.Token Associated Types
| |||||
| Show SelectorType Source # | |||||
Defined in Cryptol.Parser.Token Methods showsPrec :: Int -> SelectorType -> ShowS # show :: SelectorType -> String # showList :: [SelectorType] -> ShowS # | |||||
| NFData SelectorType Source # | |||||
Defined in Cryptol.Parser.Token Methods rnf :: SelectorType -> () # | |||||
| Eq SelectorType Source # | |||||
Defined in Cryptol.Parser.Token | |||||
| type Rep SelectorType Source # | |||||
Defined in Cryptol.Parser.Token type Rep SelectorType = D1 ('MetaData "SelectorType" "Cryptol.Parser.Token" "cryptol-3.4.0-BjfKfo7TRzHF21bOobh6Es" 'False) (C1 ('MetaCons "RecordSelectorTok" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "TupleSelectorTok" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) | |||||
Constructors
| 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 |
Instances
| Generic TokenT Source # | |||||
Defined in Cryptol.Parser.Token Associated Types
| |||||
| Show TokenT Source # | |||||
| NFData TokenT Source # | |||||
Defined in Cryptol.Parser.Token | |||||
| Eq TokenT Source # | |||||
| type Rep TokenT Source # | |||||
Defined in Cryptol.Parser.Token type Rep TokenT = D1 ('MetaData "TokenT" "Cryptol.Parser.Token" "cryptol-3.4.0-BjfKfo7TRzHF21bOobh6Es" 'False) (((C1 ('MetaCons "Num" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) :+: (C1 ('MetaCons "Frac" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Rational) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "ChrLit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Char)))) :+: (C1 ('MetaCons "Ident" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Text]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "StrLit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String)) :+: C1 ('MetaCons "Selector" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SelectorType))))) :+: ((C1 ('MetaCons "KW" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TokenKW)) :+: (C1 ('MetaCons "Op" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TokenOp)) :+: C1 ('MetaCons "Sym" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TokenSym)))) :+: ((C1 ('MetaCons "Virt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TokenV)) :+: C1 ('MetaCons "White" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TokenW))) :+: (C1 ('MetaCons "Err" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TokenErr)) :+: C1 ('MetaCons "EOF" 'PrefixI 'False) (U1 :: Type -> Type))))) | |||||