cryptol-2.7.0: Cryptol: The Language of Cryptography

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

Cryptol.TypeCheck

Description

 
Synopsis

Documentation

tcModuleInst Source #

Arguments

:: Module

functor

-> Module Name 
-> InferInput

TC settings

-> IO (InferOutput Module)

new version of instance

Check a module instantiation, assuming that the functor has already been checked.

data InferInput Source #

Information needed for type inference.

Constructors

InferInput 

Fields

Instances
Show InferInput Source # 
Instance details

Defined in Cryptol.TypeCheck.Monad

data InferOutput a Source #

The results of type inference.

Constructors

InferFailed [(Range, Warning)] [(Range, Error)]

We found some errors

InferOK [(Range, Warning)] NameSeeds Supply a

Type inference was successful.

Instances
Show a => Show (InferOutput a) Source # 
Instance details

Defined in Cryptol.TypeCheck.Monad

data SolverConfig Source #

Constructors

SolverConfig 

Fields

Instances
Show SolverConfig Source # 
Instance details

Defined in Cryptol.TypeCheck.InferTypes

Generic SolverConfig Source # 
Instance details

Defined in Cryptol.TypeCheck.InferTypes

Associated Types

type Rep SolverConfig :: Type -> Type #

NFData SolverConfig Source # 
Instance details

Defined in Cryptol.TypeCheck.InferTypes

Methods

rnf :: SolverConfig -> () #

type Rep SolverConfig Source # 
Instance details

Defined in Cryptol.TypeCheck.InferTypes

type Rep SolverConfig = D1 (MetaData "SolverConfig" "Cryptol.TypeCheck.InferTypes" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "SolverConfig" PrefixI True) ((S1 (MetaSel (Just "solverPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: S1 (MetaSel (Just "solverArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])) :*: (S1 (MetaSel (Just "solverVerbose") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "solverPreludePath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]))))

data NameSeeds Source #

This is used for generating various names.

Instances
Show NameSeeds Source # 
Instance details

Defined in Cryptol.TypeCheck.Monad

Generic NameSeeds Source # 
Instance details

Defined in Cryptol.TypeCheck.Monad

Associated Types

type Rep NameSeeds :: Type -> Type #

NFData NameSeeds Source # 
Instance details

Defined in Cryptol.TypeCheck.Monad

Methods

rnf :: NameSeeds -> () #

type Rep NameSeeds Source # 
Instance details

Defined in Cryptol.TypeCheck.Monad

type Rep NameSeeds = D1 (MetaData "NameSeeds" "Cryptol.TypeCheck.Monad" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) (C1 (MetaCons "NameSeeds" PrefixI True) (S1 (MetaSel (Just "seedTVar") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "seedGoal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))

nameSeeds :: NameSeeds Source #

The initial seeds, used when checking a fresh program. XXX: why does this start at 10?

data Error Source #

Various errors that might happen during type checking/inference

Constructors

ErrorMsg Doc

Just say this

KindMismatch Kind Kind

Expected kind, inferred kind

TooManyTypeParams Int Kind

Number of extra parameters, kind of result (which should not be of the form _ -> _)

TyVarWithParams

A type variable was applied to some arguments.

TooManyTySynParams Name Int

Type-synonym, number of extra params

TooFewTySynParams Name Int

Type-synonym, number of missing params

RecursiveTypeDecls [Name]

The type synonym declarations are recursive

TypeMismatch Type Type

Expected type, inferred type

RecursiveType Type Type

Unification results in a recursive type

UnsolvedGoals Bool [Goal]

A constraint that we could not solve The boolean indicates if we know that this constraint is impossible.

UnsolvedDelayedCt DelayedCt

A constraint (with context) that we could not solve

UnexpectedTypeWildCard

Type wild cards are not allowed in this context (e.g., definitions of type synonyms).

TypeVariableEscaped Type [TParam]

Unification variable depends on quantified variables that are not in scope.

NotForAll TVar Type

Quantified type variables (of kind *) need to match the given type, so it does not work for all types.

TooManyPositionalTypeParams

Too many positional type arguments, in an explicit type instantiation

CannotMixPositionalAndNamedTypeParams 
UndefinedTypeParameter (Located Ident) 
RepeatedTypeParameter Ident [Range] 
Instances
Show Error Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Generic Error Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

Associated Types

type Rep Error :: Type -> Type #

Methods

from :: Error -> Rep Error x #

to :: Rep Error x -> Error #

NFData Error Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

Methods

rnf :: Error -> () #

PP Error Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

Methods

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

FVS Error Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

Methods

fvs :: Error -> Set TVar Source #

TVars Error Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

Methods

apSubst :: Subst -> Error -> Error Source #

PP (WithNames Error) Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

Methods

ppPrec :: Int -> WithNames Error -> Doc Source #

type Rep Error Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

type Rep Error = D1 (MetaData "Error" "Cryptol.TypeCheck.Error" "cryptol-2.7.0-6VD9sMh08R1JPrYSq7DH8b" False) ((((C1 (MetaCons "ErrorMsg" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Doc)) :+: C1 (MetaCons "KindMismatch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Kind) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Kind))) :+: (C1 (MetaCons "TooManyTypeParams" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Kind)) :+: C1 (MetaCons "TyVarWithParams" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "TooManyTySynParams" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "TooFewTySynParams" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) :+: (C1 (MetaCons "RecursiveTypeDecls" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Name])) :+: (C1 (MetaCons "TypeMismatch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) :+: C1 (MetaCons "RecursiveType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))))) :+: (((C1 (MetaCons "UnsolvedGoals" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Goal])) :+: C1 (MetaCons "UnsolvedDelayedCt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DelayedCt))) :+: (C1 (MetaCons "UnexpectedTypeWildCard" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TypeVariableEscaped" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TParam])))) :+: ((C1 (MetaCons "NotForAll" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TVar) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) :+: C1 (MetaCons "TooManyPositionalTypeParams" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CannotMixPositionalAndNamedTypeParams" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "UndefinedTypeParameter" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Located Ident))) :+: C1 (MetaCons "RepeatedTypeParameter" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Ident) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Range])))))))

data Warning Source #

Instances
Show Warning Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

Generic Warning Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

Associated Types

type Rep Warning :: Type -> Type #

Methods

from :: Warning -> Rep Warning x #

to :: Rep Warning x -> Warning #

NFData Warning Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

Methods

rnf :: Warning -> () #

PP Warning Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

Methods

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

FVS Warning Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

Methods

fvs :: Warning -> Set TVar Source #

TVars Warning Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

PP (WithNames Warning) Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

type Rep Warning Source # 
Instance details

Defined in Cryptol.TypeCheck.Error