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.Eval.Type

Description

 
Synopsis

Documentation

data TValue Source #

An evaluated type of kind *. These types do not contain type variables, type synonyms, or type functions.

Constructors

TVBit
 Bit
TVInteger
 Integer
TVIntMod Integer
 Z n
TVSeq Integer TValue
 [n]a
TVStream TValue
 [inf]t
TVTuple [TValue]
 (a, b, c )
TVRec [(Ident, TValue)]
 { x : a, y : b, z : c }
TVFun TValue TValue
 a -> b
Instances
Show TValue Source # 
Instance details

Defined in Cryptol.Eval.Type

Generic TValue Source # 
Instance details

Defined in Cryptol.Eval.Type

Associated Types

type Rep TValue :: Type -> Type #

Methods

from :: TValue -> Rep TValue x #

to :: Rep TValue x -> TValue #

NFData TValue Source # 
Instance details

Defined in Cryptol.Eval.Type

Methods

rnf :: TValue -> () #

type Rep TValue Source # 
Instance details

Defined in Cryptol.Eval.Type

tValTy :: TValue -> Type Source #

Convert a type value back into a regular type

isTBit :: TValue -> Bool Source #

True if the evaluated value is Bit

tvSeq :: Nat' -> TValue -> TValue Source #

Produce a sequence type value

finNat' :: Nat' -> Integer Source #

Coerce an extended natural into an integer, for values known to be finite

evalType :: HasCallStack => TypeEnv -> Type -> Either Nat' TValue Source #

Evaluation for types (kind * or #).

evalValType :: HasCallStack => TypeEnv -> Type -> TValue Source #

Evaluation for value types (kind *).

evalNumType :: HasCallStack => TypeEnv -> Type -> Nat' Source #

Evaluation for number types (kind #).

evalTF :: HasCallStack => TFun -> [Nat'] -> Nat' Source #

Reduce type functions, raising an exception for undefined values.