cryptol-2.5.0: Cryptol: The Language of Cryptography

Copyright(c) 2015-2016 Galois Inc.
LicenseBSD3
Maintainercryptol@galois.com
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell98

Cryptol.ModuleSystem.Name

Contents

Description

 

Synopsis

Names

data Name Source #

Instances

Eq Name Source # 

Methods

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

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

Ord Name Source # 

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Generic Name Source # 

Associated Types

type Rep Name :: * -> * #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

NFData Name Source # 

Methods

rnf :: Name -> () #

PPName Name Source # 
PP Name Source # 

Methods

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

FromDecl (Decl Name) Source # 
FromDecl (TopDecl Name) Source # 
type Rep Name Source # 

data NameInfo Source #

Information about the binding site of the name.

Constructors

Declared !ModName

This name refers to a declaration from this module

Parameter

This name is a parameter (function or type)

Instances

Eq NameInfo Source # 
Show NameInfo Source # 
Generic NameInfo Source # 

Associated Types

type Rep NameInfo :: * -> * #

Methods

from :: NameInfo -> Rep NameInfo x #

to :: Rep NameInfo x -> NameInfo #

NFData NameInfo Source # 

Methods

rnf :: NameInfo -> () #

type Rep NameInfo Source # 
type Rep NameInfo = D1 (MetaData "NameInfo" "Cryptol.ModuleSystem.Name" "cryptol-2.5.0-62ntwDPh16AFY461fF3rK" False) ((:+:) (C1 (MetaCons "Declared" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ModName))) (C1 (MetaCons "Parameter" PrefixI False) U1))

cmpNameLexical :: Name -> Name -> Ordering Source #

Compare two names lexically.

cmpNameDisplay :: NameDisp -> Name -> Name -> Ordering Source #

Compare two names by the way they would be displayed.

ppLocName :: Name -> Doc Source #

Pretty-print a name with its source location information.

Creation

mkDeclared :: ModName -> Ident -> Maybe Fixity -> Range -> Supply -> (Name, Supply) Source #

Make a new name for a declaration.

mkParameter :: Ident -> Range -> Supply -> (Name, Supply) Source #

Make a new parameter name.

Unique Supply

class Monad m => FreshM m where Source #

Minimal complete definition

liftSupply

Methods

liftSupply :: (Supply -> (a, Supply)) -> m a Source #

Instances

FreshM InferM Source # 

Methods

liftSupply :: (Supply -> (a, Supply)) -> InferM a Source #

FreshM RenameM Source # 

Methods

liftSupply :: (Supply -> (a, Supply)) -> RenameM a Source #

FreshM REPL Source # 

Methods

liftSupply :: (Supply -> (a, Supply)) -> REPL a Source #

Monad m => FreshM (SupplyT m) Source # 

Methods

liftSupply :: (Supply -> (a, Supply)) -> SupplyT m a Source #

Monad m => FreshM (ModuleT m) Source # 

Methods

liftSupply :: (Supply -> (a, Supply)) -> ModuleT m a Source #

FreshM m => FreshM (ReaderT i m) Source # 

Methods

liftSupply :: (Supply -> (a, Supply)) -> ReaderT i m a Source #

(Monoid i, FreshM m) => FreshM (WriterT i m) Source # 

Methods

liftSupply :: (Supply -> (a, Supply)) -> WriterT i m a Source #

FreshM m => FreshM (StateT i m) Source # 

Methods

liftSupply :: (Supply -> (a, Supply)) -> StateT i m a Source #

FreshM m => FreshM (ExceptionT i m) Source # 

Methods

liftSupply :: (Supply -> (a, Supply)) -> ExceptionT i m a Source #

nextUniqueM :: FreshM m => m Int Source #

Retrieve the next unique from the supply.

data SupplyT m a Source #

A monad for easing the use of the supply.

Instances

MonadT SupplyT Source # 

Methods

lift :: Monad m => m a -> SupplyT m a #

Monad m => Monad (SupplyT m) Source # 

Methods

(>>=) :: SupplyT m a -> (a -> SupplyT m b) -> SupplyT m b #

(>>) :: SupplyT m a -> SupplyT m b -> SupplyT m b #

return :: a -> SupplyT m a #

fail :: String -> SupplyT m a #

Monad m => Functor (SupplyT m) Source # 

Methods

fmap :: (a -> b) -> SupplyT m a -> SupplyT m b #

(<$) :: a -> SupplyT m b -> SupplyT m a #

MonadFix m => MonadFix (SupplyT m) Source # 

Methods

mfix :: (a -> SupplyT m a) -> SupplyT m a #

Monad m => Applicative (SupplyT m) Source # 

Methods

pure :: a -> SupplyT m a #

(<*>) :: SupplyT m (a -> b) -> SupplyT m a -> SupplyT m b #

(*>) :: SupplyT m a -> SupplyT m b -> SupplyT m b #

(<*) :: SupplyT m a -> SupplyT m b -> SupplyT m a #

Monad m => FreshM (SupplyT m) Source # 

Methods

liftSupply :: (Supply -> (a, Supply)) -> SupplyT m a Source #

BaseM m n => BaseM (SupplyT m) n Source # 

Methods

inBase :: n a -> SupplyT m a #

RunM m (a, Supply) r => RunM (SupplyT m) a (Supply -> r) Source # 

Methods

runM :: SupplyT m a -> Supply -> r #

runSupplyT :: Monad m => Supply -> SupplyT m a -> m (a, Supply) Source #

data Supply Source #

Instances

Show Supply Source # 
Generic Supply Source # 

Associated Types

type Rep Supply :: * -> * #

Methods

from :: Supply -> Rep Supply x #

to :: Rep Supply x -> Supply #

NFData Supply Source # 

Methods

rnf :: Supply -> () #

RunM m (a, Supply) r => RunM (SupplyT m) a (Supply -> r) Source # 

Methods

runM :: SupplyT m a -> Supply -> r #

type Rep Supply Source # 
type Rep Supply = D1 (MetaData "Supply" "Cryptol.ModuleSystem.Name" "cryptol-2.5.0-62ntwDPh16AFY461fF3rK" False) (C1 (MetaCons "Supply" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int)))

emptySupply :: Supply Source #

This should only be used once at library initialization, and threaded through the rest of the session. The supply is started at 0x1000 to leave us plenty of room for names that the compiler needs to know about (wired-in constants).

PrimMap

data PrimMap Source #

A mapping from an identifier defined in some module to its real name.

Constructors

PrimMap 

Instances

Show PrimMap Source # 
Generic PrimMap Source # 

Associated Types

type Rep PrimMap :: * -> * #

Methods

from :: PrimMap -> Rep PrimMap x #

to :: Rep PrimMap x -> PrimMap #

NFData PrimMap Source # 

Methods

rnf :: PrimMap -> () #

type Rep PrimMap Source # 
type Rep PrimMap = D1 (MetaData "PrimMap" "Cryptol.ModuleSystem.Name" "cryptol-2.5.0-62ntwDPh16AFY461fF3rK" False) (C1 (MetaCons "PrimMap" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "primDecls") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Ident Name))) (S1 (MetaSel (Just Symbol "primTypes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Ident Name)))))

lookupPrimDecl :: Ident -> PrimMap -> Name Source #

It's assumed that we're looking things up that we know already exist, so this will panic if it doesn't find the name.

lookupPrimType :: Ident -> PrimMap -> Name Source #

It's assumed that we're looking things up that we know already exist, so this will panic if it doesn't find the name.