cryptol-3.1.0: Cryptol: The Language of Cryptography
Copyright(c) 2013-2016 Galois Inc.
LicenseBSD3
Maintainercryptol@galois.com
Stabilityprovisional
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cryptol.ModuleSystem.Renamer.Error

Description

 
Synopsis

Documentation

data RenamerError Source #

Constructors

MultipleSyms (Located PName) [Name]

Multiple imported symbols contain this name

UnboundName Namespace (Located PName)

Some name not bound to any definition

OverlappingSyms [Name]

An environment has produced multiple overlapping symbols

WrongNamespace Namespace Namespace (Located PName)

expected, actual. When a name is missing from the expected namespace, but exists in another

FixityError (Located Name) Fixity (Located Name) Fixity

When the fixity of two operators conflict

OverlappingRecordUpdate (Located [Selector]) (Located [Selector])

When record updates overlap (e.g., { r | x = e1, x.y = e2 })

InvalidDependency [DepName]

Things that can't depend on each other

MultipleModParams Ident [Range]

Module parameters with the same name

InvalidFunctorImport (ImpName Name)

Can't import functors directly

UnexpectedNest Range PName

Nested modules were not supposed to appear here

ModuleKindMismatch Range (ImpName Name) ModKind ModKind

Exepcted one kind (first one) but found the other (second one)

Instances

Instances details
Generic RenamerError Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

Associated Types

type Rep RenamerError :: Type -> Type #

Show RenamerError Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

PP RenamerError Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

Methods

ppPrec :: Int -> RenamerError -> Doc Source #

NFData RenamerError Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

Methods

rnf :: RenamerError -> () #

Eq RenamerError Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

Ord RenamerError Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

type Rep RenamerError Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

type Rep RenamerError = D1 ('MetaData "RenamerError" "Cryptol.ModuleSystem.Renamer.Error" "cryptol-3.1.0-276efOa9Q2aIFSEzDdp2Mp" 'False) (((C1 ('MetaCons "MultipleSyms" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Located PName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name])) :+: C1 ('MetaCons "UnboundName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Namespace) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Located PName)))) :+: (C1 ('MetaCons "OverlappingSyms" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name])) :+: (C1 ('MetaCons "WrongNamespace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Namespace) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Namespace) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Located PName)))) :+: C1 ('MetaCons "FixityError" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Located Name)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Fixity)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Located Name)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Fixity)))))) :+: ((C1 ('MetaCons "OverlappingRecordUpdate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Located [Selector])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Located [Selector]))) :+: (C1 ('MetaCons "InvalidDependency" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DepName])) :+: C1 ('MetaCons "MultipleModParams" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Range])))) :+: (C1 ('MetaCons "InvalidFunctorImport" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ImpName Name))) :+: (C1 ('MetaCons "UnexpectedNest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PName)) :+: C1 ('MetaCons "ModuleKindMismatch" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ImpName Name))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModKind) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModKind)))))))

data DepName Source #

We use this to name dependencies. In addition to normal names we have a way to refer to module parameters and top-level module constraints, which have no explicit names

Constructors

NamedThing Name

Something with a name

ModPath ModPath

The module at this path

ModParamName Range Ident

Note that the range is important not just for error reporting but to distinguish module parameters with the same name (e.g., in nested functors)

ConstratintAt Range

Identifed by location in source

Instances

Instances details
Generic DepName Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

Associated Types

type Rep DepName :: Type -> Type #

Methods

from :: DepName -> Rep DepName x #

to :: Rep DepName x -> DepName #

Show DepName Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

PP DepName Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

Methods

ppPrec :: Int -> DepName -> Doc Source #

NFData DepName Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

Methods

rnf :: DepName -> () #

Eq DepName Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

Methods

(==) :: DepName -> DepName -> Bool #

(/=) :: DepName -> DepName -> Bool #

Ord DepName Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

type Rep DepName Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

data ModKind Source #

Constructors

AFunctor 
ASignature 
AModule 

Instances

Instances details
Generic ModKind Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

Associated Types

type Rep ModKind :: Type -> Type #

Methods

from :: ModKind -> Rep ModKind x #

to :: Rep ModKind x -> ModKind #

Show ModKind Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

PP ModKind Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

Methods

ppPrec :: Int -> ModKind -> Doc Source #

NFData ModKind Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

Methods

rnf :: ModKind -> () #

Eq ModKind Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

Methods

(==) :: ModKind -> ModKind -> Bool #

(/=) :: ModKind -> ModKind -> Bool #

Ord ModKind Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

type Rep ModKind Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

type Rep ModKind = D1 ('MetaData "ModKind" "Cryptol.ModuleSystem.Renamer.Error" "cryptol-3.1.0-276efOa9Q2aIFSEzDdp2Mp" 'False) (C1 ('MetaCons "AFunctor" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ASignature" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AModule" 'PrefixI 'False) (U1 :: Type -> Type)))

data RenamerWarning Source #

Instances

Instances details
Generic RenamerWarning Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

Associated Types

type Rep RenamerWarning :: Type -> Type #

Show RenamerWarning Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

PP RenamerWarning Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

NFData RenamerWarning Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

Methods

rnf :: RenamerWarning -> () #

Eq RenamerWarning Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

Ord RenamerWarning Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error

type Rep RenamerWarning Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Error