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.Monad

Description

 
Synopsis

Documentation

data NameType Source #

Indicates if a name is in a binding poisition or a use site

Constructors

NameBind 
NameUse 

data RenamerInfo Source #

Information needed to do some renaming.

Constructors

RenamerInfo 

Fields

newtype RenameM a Source #

Constructors

RenameM 

Fields

Instances

Instances details
Applicative RenameM Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Monad

Methods

pure :: a -> RenameM a #

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

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

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

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

Functor RenameM Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Monad

Methods

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

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

Monad RenameM Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Monad

Methods

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

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

return :: a -> RenameM a #

FreshM RenameM Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Monad

Methods

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

(Semigroup a, Monoid a) => Monoid (RenameM a) Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Monad

Methods

mempty :: RenameM a #

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

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

Semigroup a => Semigroup (RenameM a) Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Monad

Methods

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

sconcat :: NonEmpty (RenameM a) -> RenameM a #

stimes :: Integral b => b -> RenameM a -> RenameM a #

data RO Source #

Constructors

RO 

Fields

data RW Source #

Constructors

RW 

Fields

data RenModParam Source #

Constructors

RenModParam 

Fields

foldLoop :: [a] -> b -> (a -> b -> b) -> b Source #

recordError :: RenamerError -> RenameM () Source #

Record an error.

depsOf :: DepName -> RenameM a -> RenameM a Source #

Rename something. All name uses in the sub-computation are assumed to be dependenices of the thing.

depGroup :: RenameM a -> RenameM (a, Map DepName (Set Name)) Source #

This is used when renaming a group of things. The result contains dependencies between names defined in the group, and is intended to be used to order the group members in dependency order.

curLoc :: RenameM Range Source #

Get the source range for wahtever we are currently renaming.

located :: a -> RenameM (Located a) Source #

Annotate something with the current range.

withLoc :: HasLoc loc => loc -> RenameM a -> RenameM a Source #

Do the given computation using the source code range from loc if any.

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

Shadow the current naming environment with some more names.

data EnvCheck Source #

Constructors

CheckAll

Check for overlap and shadowing

CheckOverlap

Only check for overlap

CheckNone

Don't check the environment

Instances

Instances details
Show EnvCheck Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Monad

Eq EnvCheck Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer.Monad

checkOverlap :: NamingEnv -> RenameM NamingEnv Source #

Report errors if the given naming environemnt contains multiple definitions for the same symbol

checkShadowing :: NamingEnv -> NamingEnv -> RenameM () Source #

Issue warnings if entries in the first environment would shadow something in the second.

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

Shadow the current naming environment with some more names. XXX: The checks are really confusing

addDep :: Name -> RenameM () Source #

Mark something as a dependency. This is similar but different from recordUse, in particular: * We only record use sites, not bindings * We record all namespaces, not just types * We only keep track of actual uses mentioned in the code. Otoh, recordUse also considers exported entities to be used. * If we depend on a name from a sibling submodule we add a dependency on the module in our common ancestor. Examples: - A::B::x depends on A::B::C::D::y, x depends on A::B::C - A::B::x depends on A::P::Q::y, x depends on A::P@

getTopModuleIface :: ImpName Name -> RenameM (Maybe Iface) Source #

Returns Nothing if the name does not refer to a module (i.e., it is a sig)

recordImport :: Range -> ImpName Name -> RenameM () Source #

Record an import: * record external dependency if the name refers to an external import * record an error if the imported thing is a functor

lookupModuleThing :: ImpName Name -> RenameM (Either ResolvedLocal (Mod ())) Source #

Lookup a name either in the locally resolved thing or in an external module