cryptol-2.3.0: Cryptol: The Language of Cryptography

Copyright(c) 2013-2016 Galois, Inc.
LicenseBSD3
Maintainercryptol@galois.com
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Cryptol.Parser.AST

Contents

Description

 

Synopsis

Names

data Ident Source

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.

type ModName = Text Source

Module names are just text.

data PName Source

Names that originate in the parser.

Constructors

UnQual !Ident

Unqualified names like x, Foo, or +.

Qual !ModName !Ident

Qualified names like Foo::bar or module::!.

NewName !Pass !Int

Fresh names generated by a pass.

Instances

Eq PName Source 
Ord PName Source 
Show PName Source 
Generic PName Source 
NFData PName Source 
PPName PName Source 
PP PName Source 
RemovePatterns [Decl PName] Source 
RemovePatterns (Expr PName) Source 
RemovePatterns (Module PName) Source 
RemovePatterns (Program PName) Source 
BindsNames (TParam PName) Source

Generate the naming environment for a type parameter.

BindsNames (Schema PName) Source

Generate a type renaming environment from the parameters that are bound by this schema.

BindsNames (Module PName) Source

The naming environment for a single module. This is the mapping from unqualified names to fully qualified names with uniques.

BindsNames (InModule (Newtype PName)) Source 
BindsNames (InModule (Bind PName)) Source

Introduce the name

BindsNames (InModule (Decl PName)) Source

The naming environment for a single declaration.

BindsNames (InModule (TopDecl PName)) Source 
type Rep PName Source 

data Named a Source

Constructors

Named 

Fields

name :: Located Ident
 
value :: a
 

data Pass Source

Passes that can generate fresh names.

Constructors

NoPat 
MonoValues 

data Assoc Source

Information about associativity.

Constructors

LeftAssoc 
RightAssoc 
NonAssoc 

Types

data Schema n Source

Constructors

Forall [TParam n] [Prop n] (Type n) (Maybe Range) 

Instances

Rename Schema Source

Rename a schema, assuming that none of its type variables are already in scope.

Eq n => Eq (Schema n) Source 
Show n => Show (Schema n) Source 
Generic (Schema n) Source 
NFData name => NFData (Schema name) Source 
PPName name => PP (Schema name) Source 
AddLoc (Schema name) Source 
HasLoc (Schema name) Source 
NoPos (Schema name) Source 
BindsNames (Schema PName) Source

Generate a type renaming environment from the parameters that are bound by this schema.

type Rep (Schema n) Source 

data TParam n Source

Constructors

TParam 

Fields

tpName :: n
 
tpKind :: Maybe Kind
 
tpRange :: Maybe Range
 

Instances

Rename TParam Source 
Eq n => Eq (TParam n) Source 
Show n => Show (TParam n) Source 
Generic (TParam n) Source 
NFData name => NFData (TParam name) Source 
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.

type Rep (TParam n) Source 

data Type n Source

Constructors

TFun (Type n) (Type n)
[8] -> [8]
TSeq (Type n) (Type n)
[8] a
TBit
Bit
TNum Integer
10
TChar Char
a
TInf
inf
TUser n [Type n]

A type variable or synonym

TApp TFun [Type n]
2 + x
TRecord [Named (Type n)]
{ x : [8], y : [32] }
TTuple [Type n]
([8], [32])
TWild

_, just some type.

TLocated (Type n) Range

Location information

TParens (Type n)
 (ty)
TInfix (Type n) (Located n) Fixity (Type n)
 ty + ty

Instances

Rename Type Source

Resolve fixity, then rename the resulting type.

Eq n => Eq (Type n) Source 
Show n => Show (Type n) Source 
Generic (Type n) Source 
NFData name => NFData (Type name) Source 
PPName name => PP (Type name) Source 
AddLoc (Type name) Source 
HasLoc (Type name) Source 
NoPos (Type name) Source 
type Rep (Type n) Source 

data Prop n Source

Constructors

CFin (Type n)
 fin x
CEqual (Type n) (Type n)
 x == 10
CGeq (Type n) (Type n)
 x >= 10
CArith (Type n)
 Arith a
CCmp (Type n)
 Cmp a
CLocated (Prop n) Range

Location information

CType (Type n)

After parsing

Instances

Rename Prop Source 
Eq n => Eq (Prop n) Source 
Show n => Show (Prop n) Source 
Generic (Prop n) Source 
NFData name => NFData (Prop name) Source 
PPName name => PP (Prop name) Source 
AddLoc (Prop name) Source 
HasLoc (Prop name) Source 
NoPos (Prop name) Source 
type Rep (Prop n) Source 

Declarations

data Module name Source

Constructors

Module 

Instances

Show name => Show (Module name) Source 
Generic (Module name) Source 
NFData name => NFData (Module name) Source 
(Show name, PPName name) => PP (Module name) Source 
HasLoc (Module name) Source 
NoPos (Module name) Source 
RemovePatterns (Module PName) Source 
BindsNames (Module PName) Source

The naming environment for a single module. This is the mapping from unqualified names to fully qualified names with uniques.

type Rep (Module name) Source 

newtype Program name Source

Constructors

Program [TopDecl name] 

Instances

Show name => Show (Program name) Source 
(Show name, PPName name) => PP (Program name) Source 
NoPos (Program name) Source 
RemovePatterns (Program PName) Source 

data TopDecl name Source

Constructors

Decl (TopLevel (Decl name)) 
TDNewtype (TopLevel (Newtype name)) 
Include (Located FilePath) 

data Decl name Source

Constructors

DSignature [Located name] (Schema name) 
DFixity !Fixity [Located name] 
DPragma [Located name] Pragma 
DBind (Bind name) 
DPatBind (Pattern name) (Expr name) 
DType (TySyn name) 
DLocated (Decl name) Range 

Instances

Rename Decl Source 
Eq name => Eq (Decl name) Source 
Show name => Show (Decl name) Source 
Generic (Decl name) Source 
NFData name => NFData (Decl name) Source 
(Show name, PPName name) => PP (Decl name) Source 
AddLoc (Decl name) Source 
HasLoc (Decl name) Source 
NoPos (Decl name) Source 
RemovePatterns [Decl PName] Source 
BindsNames (InModule (Decl PName)) Source

The naming environment for a single declaration.

FromDecl (Decl Name) Source 
type Rep (Decl name) Source 

defaultFixity :: Fixity Source

The fixity used when none is provided.

data TySyn n Source

Constructors

TySyn (Located n) [TParam n] (Type n) 

Instances

Rename TySyn Source 
Eq n => Eq (TySyn n) Source 
Show n => Show (TySyn n) Source 
Generic (TySyn n) Source 
NFData name => NFData (TySyn name) Source 
PPName name => PP (TySyn name) Source 
NoPos (TySyn name) Source 
type Rep (TySyn n) Source 

data Bind name Source

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.

Constructors

Bind 

Fields

bName :: Located name

Defined thing

bParams :: [Pattern name]

Parameters

bDef :: Located (BindDef name)

Definition

bSignature :: Maybe (Schema name)

Optional type sig

bInfix :: Bool

Infix operator?

bFixity :: Maybe Fixity

Optional fixity info

bPragmas :: [Pragma]

Optional pragmas

bMono :: Bool

Is this a monomorphic binding

bDoc :: Maybe String

Optional doc string

Instances

Rename Bind Source

Rename a binding.

Eq name => Eq (Bind name) Source 
Show name => Show (Bind name) Source 
Generic (Bind name) Source 
NFData name => NFData (Bind name) Source 
(Show name, PPName name) => PP (Bind name) Source 
HasLoc (Bind name) Source 
NoPos (Bind name) Source 
BindsNames (InModule (Bind PName)) Source

Introduce the name

type Rep (Bind name) Source 

data BindDef name Source

Constructors

DPrim 
DExpr (Expr name) 

Instances

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 
(Show name, PPName name) => PP (BindDef name) Source 
type Rep (BindDef name) Source 

data ExportSpec name Source

Constructors

ExportSpec 

Fields

eTypes :: Set name
 
eBinds :: Set name
 

Instances

Show name => Show (ExportSpec name) Source 
Generic (ExportSpec name) Source 
Ord name => Monoid (ExportSpec name) Source 
NFData name => NFData (ExportSpec name) Source 
type Rep (ExportSpec name) Source 

exportBind :: Ord name => TopLevel name -> ExportSpec name Source

Add a binding name to the export list, if it should be exported.

exportType :: Ord name => TopLevel name -> ExportSpec name Source

Add a type synonym name to the export list, if it should be exported.

isExportedBind :: Ord name => name -> ExportSpec name -> Bool Source

Check to see if a binding is exported.

isExportedType :: Ord name => name -> ExportSpec name -> Bool Source

Check to see if a type synonym is exported.

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.

Constructors

Hiding [Ident] 
Only [Ident] 

data Newtype name Source

Constructors

Newtype 

Fields

nName :: Located name

Type name

nParams :: [TParam name]

Type params

nBody :: [Named (Type name)]

Constructor

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 
PPName name => PP (Newtype name) Source 
HasLoc (Newtype name) Source 
NoPos (Newtype name) Source 
BindsNames (InModule (Newtype PName)) Source 
type Rep (Newtype name) Source 

Interactive

data ReplInput name Source

Input at the REPL, which can either be an expression or a let statement.

Constructors

ExprInput (Expr name) 
LetInput (Decl name) 

Instances

Eq name => Eq (ReplInput name) Source 
Show name => Show (ReplInput name) Source 

Expressions

data Expr n Source

Constructors

EVar n
 x
ELit Literal
 0x10
ETuple [Expr n]
 (1,2,3)
ERecord [Named (Expr n)]
 { x = 1, y = 2 }
ESel (Expr n) Selector
 e.l
EList [Expr n]
 [1,2,3]
EFromTo (Type n) (Maybe (Type n)) (Maybe (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)

`(x + 1), x is a type

EFun [Pattern n] (Expr n)
 \x y -> x
ELocated (Expr n) Range

position annotation

EParens (Expr n)

(e) (Removed by Fixity)

EInfix (Expr n) (Located n) Fixity (Expr n)

a + b (Removed by Fixity)

Instances

Rename Expr Source 
Eq n => Eq (Expr n) Source 
Show n => Show (Expr n) Source 
Generic (Expr n) Source 
NFData name => NFData (Expr name) Source 
(Show name, PPName name) => PP (Expr name) Source 
AddLoc (Expr n) Source 
HasLoc (Expr name) Source 
NoPos (Expr name) Source 
RemovePatterns (Expr PName) Source 
type Rep (Expr n) Source 

data NumInfo Source

Infromation about the representation of a numeric constant.

Constructors

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

data Match name Source

Constructors

Match (Pattern name) (Expr name)

p <- e

MatchLet (Bind name) 

Instances

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 
(Show name, PPName name) => PP (Match name) Source 
HasLoc (Match name) Source 
NoPos (Match name) Source 
type Rep (Match name) Source 

data Pattern n Source

Constructors

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

data Selector Source

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.

Constructors

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.

data TypeInst name Source

Constructors

NamedInst (Named (Type name)) 
PosInst (Type name) 

Instances

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 
PPName name => PP (TypeInst name) Source 
NoPos (TypeInst name) Source 
type Rep (TypeInst name) Source 

Positions

data Located a Source

Constructors

Located 

Fields

srcRange :: !Range
 
thing :: a
 

type LPName = Located PName Source

A name with location information.

type LString = Located String Source

A string with location information.

type LIdent = Located Ident Source

An identifier with location information.

class NoPos t where Source

Methods

noPos :: t -> t Source

Pretty-printing

cppKind :: Kind -> Doc Source

Conversational printing of kinds (e.g., to use in error messages)

ppSelector :: Selector -> Doc Source

Display the thing selected by the selector, nicely.