Copyright | (c) 2013-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Synopsis
- data Ident
- mkIdent :: Text -> Ident
- mkInfix :: Text -> Ident
- isInfixIdent :: Ident -> Bool
- nullIdent :: Ident -> Bool
- identText :: Ident -> Text
- data ModName
- modRange :: Module name -> Range
- data PName
- getModName :: PName -> Maybe ModName
- getIdent :: PName -> Ident
- mkUnqual :: Ident -> PName
- mkQual :: ModName -> Ident -> PName
- data Named a = Named {}
- data Pass
- = NoPat
- | MonoValues
- data Assoc
- data Schema n = Forall [TParam n] [Prop n] (Type n) (Maybe Range)
- data TParam n = TParam {}
- data Kind
- data Type n
- data Prop n
- data Module name = Module {}
- newtype Program name = Program [TopDecl name]
- data TopDecl name
- = Decl (TopLevel (Decl name))
- | TDNewtype (TopLevel (Newtype name))
- | Include (Located FilePath)
- | DParameterType (ParameterType name)
- | DParameterConstraint [Located (Prop name)]
- | DParameterFun (ParameterFun name)
- data Decl name
- data Fixity = Fixity {}
- defaultFixity :: Fixity
- data FixityCmp
- compareFixity :: Fixity -> Fixity -> FixityCmp
- data TySyn n = TySyn (Located n) [TParam n] (Type n)
- data PropSyn n = PropSyn (Located n) [TParam n] [Prop n]
- data Bind name = Bind {}
- data BindDef name
- type LBindDef = Located (BindDef PName)
- data Pragma
- data ExportType
- data TopLevel a = TopLevel {}
- data Import = Import {}
- data ImportSpec
- data Newtype name = Newtype {}
- data ParameterType name = ParameterType {}
- data ParameterFun name = ParameterFun {}
- data ReplInput name
- data Expr n
- = EVar n
- | ELit Literal
- | ENeg (Expr n)
- | EComplement (Expr n)
- | ETuple [Expr n]
- | ERecord [Named (Expr n)]
- | ESel (Expr n) Selector
- | EUpd (Maybe (Expr n)) [UpdField n]
- | EList [Expr n]
- | EFromTo (Type n) (Maybe (Type n)) (Type n)
- | EInfFrom (Expr n) (Maybe (Expr n))
- | EComp (Expr n) [[Match n]]
- | EApp (Expr n) (Expr n)
- | EAppT (Expr n) [TypeInst n]
- | EIf (Expr n) (Expr n) (Expr n)
- | EWhere (Expr n) [Decl n]
- | ETyped (Expr n) (Type n)
- | ETypeVal (Type n)
- | EFun [Pattern n] (Expr n)
- | ELocated (Expr n) Range
- | ESplit (Expr n)
- | EParens (Expr n)
- | EInfix (Expr n) (Located n) Fixity (Expr n)
- data Literal
- data NumInfo
- data Match name
- data Pattern n
- data Selector
- data TypeInst name
- data UpdField n = UpdField UpdHow [Located Selector] (Expr n)
- data UpdHow
- data Located a = Located {}
- type LPName = Located PName
- type LString = Located String
- type LIdent = Located Ident
- class NoPos t where
- noPos :: t -> t
- cppKind :: Kind -> Doc
- ppSelector :: Selector -> Doc
Names
Identifiers, along with a flag that indicates whether or not they're infix operators. The boolean is present just as cached information from the lexer, and never used during comparisons.
Instances
Eq Ident Source # | |
Ord Ident Source # | |
Show Ident Source # | |
IsString Ident Source # | |
Defined in Cryptol.Utils.Ident fromString :: String -> Ident # | |
Generic Ident Source # | |
NFData Ident Source # | |
Defined in Cryptol.Utils.Ident | |
PP Ident Source # | |
ShowParseable Ident Source # | |
Defined in Cryptol.TypeCheck.Parseable showParseable :: Ident -> Doc Source # | |
type Rep Ident Source # | |
Defined in Cryptol.Utils.Ident type Rep Ident = D1 (MetaData "Ident" "Cryptol.Utils.Ident" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "Ident" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
isInfixIdent :: Ident -> Bool Source #
Module names are just text.
Names that originate in the parser.
UnQual !Ident | Unqualified names like |
Qual !ModName !Ident | Qualified names like |
NewName !Pass !Int | Fresh names generated by a pass. |
Instances
Instances
Passes that can generate fresh names.
Information about associativity.
Types
Instances
Instances
Functor TParam Source # | |
Rename TParam Source # | |
Eq n => Eq (TParam n) Source # | |
Show n => Show (TParam n) Source # | |
Generic (TParam n) Source # | |
NFData n => NFData (TParam n) Source # | |
Defined in Cryptol.Parser.AST | |
PPName name => PP (TParam name) Source # | |
AddLoc (TParam name) Source # | |
HasLoc (TParam name) Source # | |
NoPos (TParam name) Source # | |
BindsNames (TParam PName) Source # | Generate the naming environment for a type parameter. |
Defined in Cryptol.ModuleSystem.NamingEnv | |
type Rep (TParam n) Source # | |
Defined in Cryptol.Parser.AST type Rep (TParam n) = D1 (MetaData "TParam" "Cryptol.Parser.AST" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "TParam" PrefixI True) (S1 (MetaSel (Just "tpName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 n) :*: (S1 (MetaSel (Just "tpKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Kind)) :*: S1 (MetaSel (Just "tpRange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Range))))) |
Instances
Eq Kind Source # | |
Show Kind Source # | |
Generic Kind Source # | |
NFData Kind Source # | |
Defined in Cryptol.Parser.AST | |
PP Kind Source # | |
type Rep Kind Source # | |
Defined in Cryptol.Parser.AST type Rep Kind = D1 (MetaData "Kind" "Cryptol.Parser.AST" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "KNum" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "KType" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KFun" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Kind) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Kind)))) |
TFun (Type n) (Type n) | [8] -> [8] |
TSeq (Type n) (Type n) | [8] a |
TBit | Bit |
TNum Integer | 10 |
TChar Char |
|
TUser n [Type n] | A type variable or synonym |
TApp TCon [Type n] |
|
TRecord [Named (Type n)] | { x : [8], y : [32] } |
TTuple [Type n] | ([8], [32]) |
TWild |
|
TLocated (Type n) Range | Location information |
TParens (Type n) | (ty) |
TInfix (Type n) (Located n) Fixity (Type n) | ty + ty |
Instances
CFin (Type n) | fin x |
CEqual (Type n) (Type n) | x == 10 |
CNeq (Type n) (Type n) | x != 10 |
CGeq (Type n) (Type n) | x >= 10 |
CZero (Type n) | Zero a |
CLogic (Type n) | Logic a |
CArith (Type n) | Arith a |
CCmp (Type n) | Cmp a |
CSignedCmp (Type n) | SignedCmp a |
CLiteral (Type n) (Type n) | Literal val a |
CUser n [Type n] | Constraint synonym |
CLocated (Prop n) Range | Location information |
CType (Type n) | After parsing |
Instances
Declarations
A parsed module.
Instances
Decl (TopLevel (Decl name)) | |
TDNewtype (TopLevel (Newtype name)) | @newtype T as = t |
Include (Located FilePath) | include File |
DParameterType (ParameterType name) | parameter type T : # |
DParameterConstraint [Located (Prop name)] | parameter type constraint (fin T) |
DParameterFun (ParameterFun name) | parameter someVal : [256] |
Instances
DSignature [Located name] (Schema name) | |
DFixity !Fixity [Located name] | |
DPragma [Located name] Pragma | |
DBind (Bind name) | |
DPatBind (Pattern name) (Expr name) | |
DType (TySyn name) | |
DProp (PropSyn name) | |
DLocated (Decl name) Range |
Instances
Instances
Eq Fixity Source # | |
Show Fixity Source # | |
Generic Fixity Source # | |
NFData Fixity Source # | |
Defined in Cryptol.Parser.Fixity | |
type Rep Fixity Source # | |
Defined in Cryptol.Parser.Fixity type Rep Fixity = D1 (MetaData "Fixity" "Cryptol.Parser.Fixity" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "Fixity" PrefixI True) (S1 (MetaSel (Just "fAssoc") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Assoc) :*: S1 (MetaSel (Just "fLevel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) |
defaultFixity :: Fixity Source #
The fixity used when none is provided.
Instances
Functor TySyn Source # | |
Rename TySyn Source # | |
Eq n => Eq (TySyn n) Source # | |
Show n => Show (TySyn n) Source # | |
Generic (TySyn n) Source # | |
NFData n => NFData (TySyn n) Source # | |
Defined in Cryptol.Parser.AST | |
PPName name => PP (TySyn name) Source # | |
NoPos (TySyn name) Source # | |
type Rep (TySyn n) Source # | |
Defined in Cryptol.Parser.AST type Rep (TySyn n) = D1 (MetaData "TySyn" "Cryptol.Parser.AST" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "TySyn" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Located n)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TParam n]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type n))))) |
Instances
Functor PropSyn Source # | |
Rename PropSyn Source # | |
Eq n => Eq (PropSyn n) Source # | |
Show n => Show (PropSyn n) Source # | |
Generic (PropSyn n) Source # | |
NFData n => NFData (PropSyn n) Source # | |
Defined in Cryptol.Parser.AST | |
PPName name => PP (PropSyn name) Source # | |
NoPos (PropSyn name) Source # | |
type Rep (PropSyn n) Source # | |
Defined in Cryptol.Parser.AST type Rep (PropSyn n) = D1 (MetaData "PropSyn" "Cryptol.Parser.AST" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "PropSyn" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Located n)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TParam n]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Prop n])))) |
Bindings. Notes:
- The parser does not associate type signatures and pragmas with their bindings: this is done in a separate pass, after de-sugaring pattern bindings. In this way we can associate pragmas and type signatures with the variables defined by pattern bindings as well.
- Currently, there is no surface syntax for defining monomorphic bindings (i.e., bindings that will not be automatically generalized by the type checker. However, they are useful when de-sugaring patterns.
Bind | |
|
Instances
Instances
Functor BindDef Source # | |
Rename BindDef Source # | |
Eq name => Eq (BindDef name) Source # | |
Show name => Show (BindDef name) Source # | |
Generic (BindDef name) Source # | |
NFData name => NFData (BindDef name) Source # | |
Defined in Cryptol.Parser.AST | |
(Show name, PPName name) => PP (BindDef name) Source # | |
type Rep (BindDef name) Source # | |
Defined in Cryptol.Parser.AST type Rep (BindDef name) = D1 (MetaData "BindDef" "Cryptol.Parser.AST" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "DPrim" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DExpr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr name)))) |
Instances
Eq Pragma Source # | |
Show Pragma Source # | |
Generic Pragma Source # | |
NFData Pragma Source # | |
Defined in Cryptol.Parser.AST | |
PP Pragma Source # | |
NoPos Pragma Source # | |
type Rep Pragma Source # | |
Defined in Cryptol.Parser.AST type Rep Pragma = D1 (MetaData "Pragma" "Cryptol.Parser.AST" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "PragmaNote" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "PragmaProperty" PrefixI False) (U1 :: Type -> Type)) |
data ExportType Source #
Export information for a declaration.
Instances
Eq ExportType Source # | |
Defined in Cryptol.Parser.AST (==) :: ExportType -> ExportType -> Bool # (/=) :: ExportType -> ExportType -> Bool # | |
Ord ExportType Source # | |
Defined in Cryptol.Parser.AST compare :: ExportType -> ExportType -> Ordering # (<) :: ExportType -> ExportType -> Bool # (<=) :: ExportType -> ExportType -> Bool # (>) :: ExportType -> ExportType -> Bool # (>=) :: ExportType -> ExportType -> Bool # max :: ExportType -> ExportType -> ExportType # min :: ExportType -> ExportType -> ExportType # | |
Show ExportType Source # | |
Defined in Cryptol.Parser.AST showsPrec :: Int -> ExportType -> ShowS # show :: ExportType -> String # showList :: [ExportType] -> ShowS # | |
Generic ExportType Source # | |
Defined in Cryptol.Parser.AST type Rep ExportType :: Type -> Type # from :: ExportType -> Rep ExportType x # to :: Rep ExportType x -> ExportType # | |
NFData ExportType Source # | |
Defined in Cryptol.Parser.AST rnf :: ExportType -> () # | |
type Rep ExportType Source # | |
A top-level module declaration.
Instances
An import declaration.
Instances
Eq Import Source # | |
Show Import Source # | |
Generic Import Source # | |
NFData Import Source # | |
Defined in Cryptol.Parser.AST | |
PP Import Source # | |
type Rep Import Source # | |
Defined in Cryptol.Parser.AST type Rep Import = D1 (MetaData "Import" "Cryptol.Parser.AST" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "Import" PrefixI True) (S1 (MetaSel (Just "iModule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ModName) :*: (S1 (MetaSel (Just "iAs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ModName)) :*: S1 (MetaSel (Just "iSpec") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ImportSpec))))) |
data ImportSpec Source #
The list of names following an import.
INVARIANT: All of the Name
entries in the list are expected to be
unqualified names; the QName
or NewName
constructors should not be
present.
Instances
Instances
Rename Newtype Source # | |
Eq name => Eq (Newtype name) Source # | |
Show name => Show (Newtype name) Source # | |
Generic (Newtype name) Source # | |
NFData name => NFData (Newtype name) Source # | |
Defined in Cryptol.Parser.AST | |
PPName name => PP (Newtype name) Source # | |
HasLoc (Newtype name) Source # | |
NoPos (Newtype name) Source # | |
BindsNames (InModule (Newtype PName)) Source # | |
Defined in Cryptol.ModuleSystem.NamingEnv | |
type Rep (Newtype name) Source # | |
Defined in Cryptol.Parser.AST type Rep (Newtype name) = D1 (MetaData "Newtype" "Cryptol.Parser.AST" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "Newtype" PrefixI True) (S1 (MetaSel (Just "nName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Located name)) :*: (S1 (MetaSel (Just "nParams") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TParam name]) :*: S1 (MetaSel (Just "nBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Named (Type name)])))) |
data ParameterType name Source #
A type parameter
Instances
data ParameterFun name Source #
A value parameter
Instances
Interactive
Input at the REPL, which can either be an expression or a let
statement.
Expressions
EVar n | x |
ELit Literal | 0x10 |
ENeg (Expr n) | -1 |
EComplement (Expr n) | ~1 |
ETuple [Expr n] | (1,2,3) |
ERecord [Named (Expr n)] | { x = 1, y = 2 } |
ESel (Expr n) Selector | e.l |
EUpd (Maybe (Expr n)) [UpdField n] | { r | x = e } |
EList [Expr n] | [1,2,3] |
EFromTo (Type n) (Maybe (Type n)) (Type n) | [1, 5 .. 117 ] |
EInfFrom (Expr n) (Maybe (Expr n)) | [1, 3 ...] |
EComp (Expr n) [[Match n]] | [ 1 | x <- xs ] |
EApp (Expr n) (Expr n) | f x |
EAppT (Expr n) [TypeInst n] | f `{x = 8}, f`{8} |
EIf (Expr n) (Expr n) (Expr n) | if ok then e1 else e2 |
EWhere (Expr n) [Decl n] | 1 + x where { x = 2 } |
ETyped (Expr n) (Type n) | 1 : [8] |
ETypeVal (Type n) |
|
EFun [Pattern n] (Expr n) | \x y -> x |
ELocated (Expr n) Range | position annotation |
ESplit (Expr n) |
|
EParens (Expr n) |
|
EInfix (Expr n) (Located n) Fixity (Expr n) |
|
Instances
Literals.
Instances
Eq Literal Source # | |
Show Literal Source # | |
Generic Literal Source # | |
NFData Literal Source # | |
Defined in Cryptol.Parser.AST | |
PP Literal Source # | |
type Rep Literal Source # | |
Defined in Cryptol.Parser.AST type Rep Literal = D1 (MetaData "Literal" "Cryptol.Parser.AST" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "ECNum" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NumInfo)) :+: C1 (MetaCons "ECString" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) |
Infromation about the representation of a numeric constant.
BinLit Int | n-digit binary literal |
OctLit Int | n-digit octal literal |
DecLit | overloaded decimal literal |
HexLit Int | n-digit hex literal |
CharLit | character literal |
PolyLit Int | polynomial literal |
Instances
Eq NumInfo Source # | |
Show NumInfo Source # | |
Generic NumInfo Source # | |
NFData NumInfo Source # | |
Defined in Cryptol.Parser.AST | |
type Rep NumInfo Source # | |
Defined in Cryptol.Parser.AST type Rep NumInfo = D1 (MetaData "NumInfo" "Cryptol.Parser.AST" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) ((C1 (MetaCons "BinLit" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: (C1 (MetaCons "OctLit" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "DecLit" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "HexLit" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: (C1 (MetaCons "CharLit" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PolyLit" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))) |
Instances
Functor Match Source # | |
Rename Match Source # | |
Eq name => Eq (Match name) Source # | |
Show name => Show (Match name) Source # | |
Generic (Match name) Source # | |
NFData name => NFData (Match name) Source # | |
Defined in Cryptol.Parser.AST | |
(Show name, PPName name) => PP (Match name) Source # | |
HasLoc (Match name) Source # | |
NoPos (Match name) Source # | |
type Rep (Match name) Source # | |
Defined in Cryptol.Parser.AST type Rep (Match name) = D1 (MetaData "Match" "Cryptol.Parser.AST" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "Match" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Pattern name)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr name))) :+: C1 (MetaCons "MatchLet" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Bind name)))) |
PVar (Located n) | x |
PWild | _ |
PTuple [Pattern n] | (x,y,z) |
PRecord [Named (Pattern n)] | { x = (a,b,c), y = z } |
PList [Pattern n] | [ x, y, z ] |
PTyped (Pattern n) (Type n) | x : [8] |
PSplit (Pattern n) (Pattern n) | (x # y) |
PLocated (Pattern n) Range | Location information |
Instances
Selectors are used for projecting from various components. Each selector has an option spec to specify the shape of the thing that is being selected. Currently, there is no surface syntax for list selectors, but they are used during the desugaring of patterns.
TupleSel Int (Maybe Int) | Zero-based tuple selection. Optionally specifies the shape of the tuple (one-based). |
RecordSel Ident (Maybe [Ident]) | Record selection. Optionally specifies the shape of the record. |
ListSel Int (Maybe Int) | List selection. Optionally specifies the length of the list. |
Instances
Instances
Functor TypeInst Source # | |
Rename TypeInst Source # | |
Eq name => Eq (TypeInst name) Source # | |
Show name => Show (TypeInst name) Source # | |
Generic (TypeInst name) Source # | |
NFData name => NFData (TypeInst name) Source # | |
Defined in Cryptol.Parser.AST | |
PPName name => PP (TypeInst name) Source # | |
NoPos (TypeInst name) Source # | |
type Rep (TypeInst name) Source # | |
Defined in Cryptol.Parser.AST type Rep (TypeInst name) = D1 (MetaData "TypeInst" "Cryptol.Parser.AST" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "NamedInst" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Named (Type name)))) :+: C1 (MetaCons "PosInst" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type name)))) |
Instances
Functor UpdField Source # | |
Rename UpdField Source # | Note that after this point the |
Eq n => Eq (UpdField n) Source # | |
Show n => Show (UpdField n) Source # | |
Generic (UpdField n) Source # | |
NFData n => NFData (UpdField n) Source # | |
Defined in Cryptol.Parser.AST | |
(Show name, PPName name) => PP (UpdField name) Source # | |
NoPos (UpdField name) Source # | |
type Rep (UpdField n) Source # | |
Defined in Cryptol.Parser.AST type Rep (UpdField n) = D1 (MetaData "UpdField" "Cryptol.Parser.AST" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "UpdField" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UpdHow) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Located Selector]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr n))))) |
Positions
Instances
Functor Located Source # | |
Eq a => Eq (Located a) Source # | |
Show a => Show (Located a) Source # | |
Generic (Located a) Source # | |
NFData a => NFData (Located a) Source # | |
Defined in Cryptol.Parser.Position | |
PPName a => PPName (Located a) Source # | |
Defined in Cryptol.Parser.Position | |
PP a => PP (Located a) Source # | |
AddLoc (Located a) Source # | |
HasLoc (Located a) Source # | |
NoPos (Located t) Source # | |
ShowParseable a => ShowParseable (Located a) Source # | |
Defined in Cryptol.TypeCheck.Parseable showParseable :: Located a -> Doc Source # | |
type Rep (Located a) Source # | |
Defined in Cryptol.Parser.Position type Rep (Located a) = D1 (MetaData "Located" "Cryptol.Parser.Position" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "Located" PrefixI True) (S1 (MetaSel (Just "srcRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Range) :*: S1 (MetaSel (Just "thing") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a))) |
Instances
NoPos Pragma Source # | |
NoPos t => NoPos [t] Source # | |
Defined in Cryptol.Parser.AST | |
NoPos t => NoPos (Maybe t) Source # | |
NoPos (Located t) Source # | |
NoPos (Prop name) Source # | |
NoPos (Type name) Source # | |
NoPos (TParam name) Source # | |
NoPos (Schema name) Source # | |
NoPos t => NoPos (Named t) Source # | |
NoPos (Pattern name) Source # | |
NoPos (Match name) Source # | |
NoPos (TypeInst name) Source # | |
NoPos (UpdField name) Source # | |
NoPos (Expr name) Source # | |
NoPos a => NoPos (TopLevel a) Source # | |
NoPos (Newtype name) Source # | |
NoPos (Bind name) Source # | |
NoPos (PropSyn name) Source # | |
NoPos (TySyn name) Source # | |
NoPos (ParameterFun x) Source # | |
Defined in Cryptol.Parser.AST noPos :: ParameterFun x -> ParameterFun x Source # | |
NoPos (ParameterType name) Source # | |
Defined in Cryptol.Parser.AST noPos :: ParameterType name -> ParameterType name Source # | |
NoPos (Decl name) Source # | |
NoPos (TopDecl name) Source # | |
NoPos (Module name) Source # | |
NoPos (Program name) Source # | |
Pretty-printing
ppSelector :: Selector -> Doc Source #
Display the thing selected by the selector, nicely.