cryptol-2.5.0: Cryptol: The Language of Cryptography

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

Cryptol.ModuleSystem.Renamer

Description

 

Synopsis

Documentation

shadowing :: NamingEnv -> NamingEnv -> NamingEnv Source #

Like mappend, but when merging, prefer values on the lhs.

class BindsNames a where Source #

Things that define exported names.

Minimal complete definition

namingEnv

Instances

BindsNames ImportIface Source #

Produce a naming environment from an interface file, that contains a mapping only from unqualified names to qualified ones.

BindsNames NamingEnv Source # 
BindsNames a => BindsNames [a] Source # 

Methods

namingEnv :: [a] -> BuildNamingEnv Source #

BindsNames a => BindsNames (Maybe a) 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 # 

data InModule a Source #

Constructors

InModule !ModName a 

Instances

Functor InModule Source # 

Methods

fmap :: (a -> b) -> InModule a -> InModule b #

(<$) :: a -> InModule b -> InModule a #

Foldable InModule Source # 

Methods

fold :: Monoid m => InModule m -> m #

foldMap :: Monoid m => (a -> m) -> InModule a -> m #

foldr :: (a -> b -> b) -> b -> InModule a -> b #

foldr' :: (a -> b -> b) -> b -> InModule a -> b #

foldl :: (b -> a -> b) -> b -> InModule a -> b #

foldl' :: (b -> a -> b) -> b -> InModule a -> b #

foldr1 :: (a -> a -> a) -> InModule a -> a #

foldl1 :: (a -> a -> a) -> InModule a -> a #

toList :: InModule a -> [a] #

null :: InModule a -> Bool #

length :: InModule a -> Int #

elem :: Eq a => a -> InModule a -> Bool #

maximum :: Ord a => InModule a -> a #

minimum :: Ord a => InModule a -> a #

sum :: Num a => InModule a -> a #

product :: Num a => InModule a -> a #

Traversable InModule Source # 

Methods

traverse :: Applicative f => (a -> f b) -> InModule a -> f (InModule b) #

sequenceA :: Applicative f => InModule (f a) -> f (InModule a) #

mapM :: Monad m => (a -> m b) -> InModule a -> m (InModule b) #

sequence :: Monad m => InModule (m a) -> m (InModule a) #

Show a => Show (InModule a) Source # 

Methods

showsPrec :: Int -> InModule a -> ShowS #

show :: InModule a -> String #

showList :: [InModule a] -> ShowS #

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 # 

namingEnv' :: BindsNames a => a -> Supply -> (NamingEnv, Supply) Source #

Generate a NamingEnv using an explicit supply.

checkNamingEnv :: NamingEnv -> ([RenamerError], [RenamerWarning]) Source #

Throw errors for any names that overlap in a rewrite environment.

shadowNames :: BindsNames env => env -> RenameM a -> RenameM a Source #

Shadow the current naming environment with some more names.

class Rename f where Source #

Minimal complete definition

rename

Methods

rename :: f PName -> RenameM (f Name) Source #

data RenameM a Source #

Instances

Monad RenameM Source # 

Methods

(>>=) :: RenameM a -> (a -> RenameM b) -> RenameM b #

(>>) :: RenameM a -> RenameM b -> RenameM b #

return :: a -> RenameM a #

fail :: String -> RenameM a #

Functor RenameM Source # 

Methods

fmap :: (a -> b) -> RenameM a -> RenameM b #

(<$) :: a -> RenameM b -> RenameM a #

Applicative RenameM Source # 

Methods

pure :: a -> RenameM a #

(<*>) :: RenameM (a -> b) -> RenameM a -> RenameM b #

(*>) :: RenameM a -> RenameM b -> RenameM b #

(<*) :: RenameM a -> RenameM b -> RenameM a #

FreshM RenameM Source # 

Methods

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

Monoid a => Monoid (RenameM a) Source # 

Methods

mempty :: RenameM a #

mappend :: RenameM a -> RenameM a -> RenameM a #

mconcat :: [RenameM a] -> RenameM a #

data RenamerError Source #

Constructors

MultipleSyms (Located PName) [Name] NameDisp

Multiple imported symbols contain this name

UnboundExpr (Located PName) NameDisp

Expression name is not bound to any definition

UnboundType (Located PName) NameDisp

Type name is not bound to any definition

OverlappingSyms [Name] NameDisp

An environment has produced multiple overlapping symbols

ExpectedValue (Located PName) NameDisp

When a value is expected from the naming environment, but one or more types exist instead.

ExpectedType (Located PName) NameDisp

When a type is missing from the naming environment, but one or more values exist with the same name.

FixityError (Located Name) (Located Name) NameDisp

When the fixity of two operators conflict

InvalidConstraint (Type PName) NameDisp

When it's not possible to produce a Prop from a Type.

MalformedBuiltin (Type PName) PName NameDisp

When a builtin type/type-function is used incorrectly.

BoundReservedType PName (Maybe Range) Doc NameDisp

When a builtin type is named in a binder.

Instances

Show RenamerError Source # 
Generic RenamerError Source # 

Associated Types

type Rep RenamerError :: * -> * #

NFData RenamerError Source # 

Methods

rnf :: RenamerError -> () #

PP RenamerError Source # 

Methods

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

type Rep RenamerError Source # 
type Rep RenamerError = D1 (MetaData "RenamerError" "Cryptol.ModuleSystem.Renamer" "cryptol-2.5.0-62ntwDPh16AFY461fF3rK" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "MultipleSyms" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Located PName))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Name])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NameDisp))))) (C1 (MetaCons "UnboundExpr" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Located PName))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NameDisp))))) ((:+:) (C1 (MetaCons "UnboundType" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Located PName))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NameDisp)))) ((:+:) (C1 (MetaCons "OverlappingSyms" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Name])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NameDisp)))) (C1 (MetaCons "ExpectedValue" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Located PName))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NameDisp))))))) ((:+:) ((:+:) (C1 (MetaCons "ExpectedType" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Located PName))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NameDisp)))) (C1 (MetaCons "FixityError" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Located Name))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Located Name))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NameDisp)))))) ((:+:) (C1 (MetaCons "InvalidConstraint" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type PName))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NameDisp)))) ((:+:) (C1 (MetaCons "MalformedBuiltin" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type PName))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NameDisp))))) (C1 (MetaCons "BoundReservedType" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Range)))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Doc)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NameDisp)))))))))

data RenamerWarning Source #