futhark-0.19.5: An optimising compiler for a functional, array-oriented language.
Safe HaskellTrustworthy
LanguageHaskell2010

Futhark.IR.Prop.Scope

Description

The core Futhark AST does not contain type information when we use a variable. Therefore, most transformations expect to be able to access some kind of symbol table that maps names to their types.

This module defines the concept of a type environment as a mapping from variable names to NameInfos. Convenience facilities are also provided to communicate that some monad or applicative functor maintains type information.

Synopsis

Documentation

class (Applicative m, Decorations lore) => HasScope lore m | m -> lore where Source #

The class of applicative functors (or more common in practice: monads) that permit the lookup of variable types. A default method for lookupType exists, which is sufficient (if not always maximally efficient, and using error to fail) when askScope is defined.

Minimal complete definition

askScope

Methods

lookupType :: VName -> m Type Source #

Return the type of the given variable, or fail if it is not in the type environment.

lookupInfo :: VName -> m (NameInfo lore) Source #

Return the info of the given variable, or fail if it is not in the type environment.

askScope :: m (Scope lore) Source #

Return the type environment contained in the applicative functor.

asksScope :: (Scope lore -> a) -> m a Source #

Return the result of applying some function to the type environment.

Instances

Instances details
HasScope SOACS InternaliseM Source # 
Instance details

Defined in Futhark.Internalise.Monad

ASTLore lore => HasScope lore (RuleM lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Rule

Methods

lookupType :: VName -> RuleM lore Type Source #

lookupInfo :: VName -> RuleM lore (NameInfo lore) Source #

askScope :: RuleM lore (Scope lore) Source #

asksScope :: (Scope lore -> a) -> RuleM lore a Source #

(HasScope lore m, Monad m) => HasScope lore (ExtendedScope lore m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

lookupType :: VName -> ExtendedScope lore m Type Source #

lookupInfo :: VName -> ExtendedScope lore m (NameInfo lore) Source #

askScope :: ExtendedScope lore m (Scope lore) Source #

asksScope :: (Scope lore -> a) -> ExtendedScope lore m a Source #

(Monad m, HasScope lore m) => HasScope lore (ExceptT e m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

lookupType :: VName -> ExceptT e m Type Source #

lookupInfo :: VName -> ExceptT e m (NameInfo lore) Source #

askScope :: ExceptT e m (Scope lore) Source #

asksScope :: (Scope lore -> a) -> ExceptT e m a Source #

(Applicative m, Monad m, Decorations lore) => HasScope lore (ReaderT (Scope lore) m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

lookupType :: VName -> ReaderT (Scope lore) m Type Source #

lookupInfo :: VName -> ReaderT (Scope lore) m (NameInfo lore) Source #

askScope :: ReaderT (Scope lore) m (Scope lore) Source #

asksScope :: (Scope lore -> a) -> ReaderT (Scope lore) m a Source #

(ASTLore lore, Monad m) => HasScope lore (BinderT lore m) Source # 
Instance details

Defined in Futhark.Binder

Methods

lookupType :: VName -> BinderT lore m Type Source #

lookupInfo :: VName -> BinderT lore m (NameInfo lore) Source #

askScope :: BinderT lore m (Scope lore) Source #

asksScope :: (Scope lore -> a) -> BinderT lore m a Source #

ASTLore tolore => HasScope tolore (AllocM fromlore tolore) Source # 
Instance details

Defined in Futhark.Pass.ExplicitAllocations

Methods

lookupType :: VName -> AllocM fromlore tolore Type Source #

lookupInfo :: VName -> AllocM fromlore tolore (NameInfo tolore) Source #

askScope :: AllocM fromlore tolore (Scope tolore) Source #

asksScope :: (Scope tolore -> a) -> AllocM fromlore tolore a Source #

(Monad m, ASTLore lore) => HasScope lore (DistNestT lore m) Source # 
Instance details

Defined in Futhark.Pass.ExtractKernels.DistributeNests

Methods

lookupType :: VName -> DistNestT lore m Type Source #

lookupInfo :: VName -> DistNestT lore m (NameInfo lore) Source #

askScope :: DistNestT lore m (Scope lore) Source #

asksScope :: (Scope lore -> a) -> DistNestT lore m a Source #

HasScope SOACS (ImpM lore r op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

lookupType :: VName -> ImpM lore r op Type Source #

lookupInfo :: VName -> ImpM lore r op (NameInfo SOACS) Source #

askScope :: ImpM lore r op (Scope SOACS) Source #

asksScope :: (Scope SOACS -> a) -> ImpM lore r op a Source #

(Applicative m, Monad m, Monoid w, Decorations lore) => HasScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

lookupType :: VName -> RWST (Scope lore) w s m Type Source #

lookupInfo :: VName -> RWST (Scope lore) w s m (NameInfo lore) Source #

askScope :: RWST (Scope lore) w s m (Scope lore) Source #

asksScope :: (Scope lore -> a) -> RWST (Scope lore) w s m a Source #

(Applicative m, Monad m, Monoid w, Decorations lore) => HasScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

lookupType :: VName -> RWST (Scope lore) w s m Type Source #

lookupInfo :: VName -> RWST (Scope lore) w s m (NameInfo lore) Source #

askScope :: RWST (Scope lore) w s m (Scope lore) Source #

asksScope :: (Scope lore -> a) -> RWST (Scope lore) w s m a Source #

Checkable lore => HasScope (Aliases lore) (TypeM lore) Source # 
Instance details

Defined in Futhark.TypeCheck

Methods

lookupType :: VName -> TypeM lore Type Source #

lookupInfo :: VName -> TypeM lore (NameInfo (Aliases lore)) Source #

askScope :: TypeM lore (Scope (Aliases lore)) Source #

asksScope :: (Scope (Aliases lore) -> a) -> TypeM lore a Source #

SimplifiableLore lore => HasScope (Wise lore) (SimpleM lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

lookupType :: VName -> SimpleM lore Type Source #

lookupInfo :: VName -> SimpleM lore (NameInfo (Wise lore)) Source #

askScope :: SimpleM lore (Scope (Wise lore)) Source #

asksScope :: (Scope (Wise lore) -> a) -> SimpleM lore a Source #

data NameInfo lore Source #

How some name in scope was bound.

Instances

Instances details
Scoped lore (VName, NameInfo lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: (VName, NameInfo lore) -> Scope lore Source #

(Applicative m, Monad m, Decorations lore) => LocalScope lore (ReaderT (Scope lore) m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

localScope :: Scope lore -> ReaderT (Scope lore) m a -> ReaderT (Scope lore) m a Source #

(Applicative m, Monad m, Decorations lore) => HasScope lore (ReaderT (Scope lore) m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

lookupType :: VName -> ReaderT (Scope lore) m Type Source #

lookupInfo :: VName -> ReaderT (Scope lore) m (NameInfo lore) Source #

askScope :: ReaderT (Scope lore) m (Scope lore) Source #

asksScope :: (Scope lore -> a) -> ReaderT (Scope lore) m a Source #

(Applicative m, Monad m, Monoid w, Decorations lore) => LocalScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

localScope :: Scope lore -> RWST (Scope lore) w s m a -> RWST (Scope lore) w s m a Source #

(Applicative m, Monad m, Monoid w, Decorations lore) => LocalScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

localScope :: Scope lore -> RWST (Scope lore) w s m a -> RWST (Scope lore) w s m a Source #

(Applicative m, Monad m, Monoid w, Decorations lore) => HasScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

lookupType :: VName -> RWST (Scope lore) w s m Type Source #

lookupInfo :: VName -> RWST (Scope lore) w s m (NameInfo lore) Source #

askScope :: RWST (Scope lore) w s m (Scope lore) Source #

asksScope :: (Scope lore -> a) -> RWST (Scope lore) w s m a Source #

(Applicative m, Monad m, Monoid w, Decorations lore) => HasScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

lookupType :: VName -> RWST (Scope lore) w s m Type Source #

lookupInfo :: VName -> RWST (Scope lore) w s m (NameInfo lore) Source #

askScope :: RWST (Scope lore) w s m (Scope lore) Source #

asksScope :: (Scope lore -> a) -> RWST (Scope lore) w s m a Source #

Decorations lore => Show (NameInfo lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

showsPrec :: Int -> NameInfo lore -> ShowS #

show :: NameInfo lore -> String #

showList :: [NameInfo lore] -> ShowS #

Decorations lore => Typed (NameInfo lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

typeOf :: NameInfo lore -> Type Source #

Substitutable lore => Substitute (NameInfo lore) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Monad m => MonadReader (Scope lore) (ExtendedScope lore m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

ask :: ExtendedScope lore m (Scope lore) #

local :: (Scope lore -> Scope lore) -> ExtendedScope lore m a -> ExtendedScope lore m a #

reader :: (Scope lore -> a) -> ExtendedScope lore m a #

class (HasScope lore m, Monad m) => LocalScope lore m where Source #

The class of monads that not only provide a Scope, but also the ability to locally extend it. A Reader containing a Scope is the prototypical example of such a monad.

Methods

localScope :: Scope lore -> m a -> m a Source #

Run a computation with an extended type environment. Note that this is intended to *add* to the current type environment, it does not replace it.

Instances

Instances details
LocalScope SOACS InternaliseM Source # 
Instance details

Defined in Futhark.Internalise.Monad

ASTLore lore => LocalScope lore (RuleM lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Rule

Methods

localScope :: Scope lore -> RuleM lore a -> RuleM lore a Source #

(Applicative m, Monad m, Decorations lore) => LocalScope lore (ReaderT (Scope lore) m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

localScope :: Scope lore -> ReaderT (Scope lore) m a -> ReaderT (Scope lore) m a Source #

(Monad m, LocalScope lore m) => LocalScope lore (ExceptT e m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

localScope :: Scope lore -> ExceptT e m a -> ExceptT e m a Source #

(ASTLore lore, Monad m) => LocalScope lore (BinderT lore m) Source # 
Instance details

Defined in Futhark.Binder

Methods

localScope :: Scope lore -> BinderT lore m a -> BinderT lore m a Source #

ASTLore tolore => LocalScope tolore (AllocM fromlore tolore) Source # 
Instance details

Defined in Futhark.Pass.ExplicitAllocations

Methods

localScope :: Scope tolore -> AllocM fromlore tolore a -> AllocM fromlore tolore a Source #

(Monad m, ASTLore lore) => LocalScope lore (DistNestT lore m) Source # 
Instance details

Defined in Futhark.Pass.ExtractKernels.DistributeNests

Methods

localScope :: Scope lore -> DistNestT lore m a -> DistNestT lore m a Source #

(Applicative m, Monad m, Monoid w, Decorations lore) => LocalScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

localScope :: Scope lore -> RWST (Scope lore) w s m a -> RWST (Scope lore) w s m a Source #

(Applicative m, Monad m, Monoid w, Decorations lore) => LocalScope lore (RWST (Scope lore) w s m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

localScope :: Scope lore -> RWST (Scope lore) w s m a -> RWST (Scope lore) w s m a Source #

SimplifiableLore lore => LocalScope (Wise lore) (SimpleM lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

localScope :: Scope (Wise lore) -> SimpleM lore a -> SimpleM lore a Source #

type Scope lore = Map VName (NameInfo lore) Source #

A scope is a mapping from variable names to information about that name.

class Scoped lore a | a -> lore where Source #

The class of things that can provide a scope. There is no overarching rule for what this means. For a Stm, it is the corresponding pattern. For a Lambda, is is the parameters.

Methods

scopeOf :: a -> Scope lore Source #

Instances

Instances details
Scoped lore (Lambda lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: Lambda lore -> Scope lore Source #

Scoped lore (LoopForm lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: LoopForm lore -> Scope lore Source #

Scoped lore (FunDef lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: FunDef lore -> Scope lore Source #

Scoped lore (Stm lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: Stm lore -> Scope lore Source #

Scoped lore (Stms lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: Stms lore -> Scope lore Source #

Scoped lore a => Scoped lore [a] Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: [a] -> Scope lore Source #

Scoped lore (VName, NameInfo lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: (VName, NameInfo lore) -> Scope lore Source #

inScopeOf :: (Scoped lore a, LocalScope lore m) => a -> m b -> m b Source #

Extend the monadic scope with the scopeOf the given value.

scopeOfLParams :: LParamInfo lore ~ dec => [Param dec] -> Scope lore Source #

The scope of some lambda parameters.

scopeOfFParams :: FParamInfo lore ~ dec => [Param dec] -> Scope lore Source #

The scope of some function or loop parameters.

scopeOfPattern :: LetDec lore ~ dec => PatternT dec -> Scope lore Source #

The scope of a pattern.

scopeOfPatElem :: LetDec lore ~ dec => PatElemT dec -> Scope lore Source #

The scope of a pattern element.

type SameScope lore1 lore2 = (LetDec lore1 ~ LetDec lore2, FParamInfo lore1 ~ FParamInfo lore2, LParamInfo lore1 ~ LParamInfo lore2) Source #

A constraint that indicates two lores have the same NameInfo representation.

castScope :: SameScope fromlore tolore => Scope fromlore -> Scope tolore Source #

If two scopes are really the same, then you can convert one to the other.

Extended type environment

data ExtendedScope lore m a Source #

A monad transformer that carries around an extended Scope. Its lookupType method will first look in the extended Scope, and then use the lookupType method of the underlying monad.

Instances

Instances details
(HasScope lore m, Monad m) => HasScope lore (ExtendedScope lore m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

lookupType :: VName -> ExtendedScope lore m Type Source #

lookupInfo :: VName -> ExtendedScope lore m (NameInfo lore) Source #

askScope :: ExtendedScope lore m (Scope lore) Source #

asksScope :: (Scope lore -> a) -> ExtendedScope lore m a Source #

Monad m => MonadReader (Scope lore) (ExtendedScope lore m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

ask :: ExtendedScope lore m (Scope lore) #

local :: (Scope lore -> Scope lore) -> ExtendedScope lore m a -> ExtendedScope lore m a #

reader :: (Scope lore -> a) -> ExtendedScope lore m a #

Monad m => Monad (ExtendedScope lore m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

(>>=) :: ExtendedScope lore m a -> (a -> ExtendedScope lore m b) -> ExtendedScope lore m b #

(>>) :: ExtendedScope lore m a -> ExtendedScope lore m b -> ExtendedScope lore m b #

return :: a -> ExtendedScope lore m a #

Functor m => Functor (ExtendedScope lore m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

fmap :: (a -> b) -> ExtendedScope lore m a -> ExtendedScope lore m b #

(<$) :: a -> ExtendedScope lore m b -> ExtendedScope lore m a #

Applicative m => Applicative (ExtendedScope lore m) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

pure :: a -> ExtendedScope lore m a #

(<*>) :: ExtendedScope lore m (a -> b) -> ExtendedScope lore m a -> ExtendedScope lore m b #

liftA2 :: (a -> b -> c) -> ExtendedScope lore m a -> ExtendedScope lore m b -> ExtendedScope lore m c #

(*>) :: ExtendedScope lore m a -> ExtendedScope lore m b -> ExtendedScope lore m b #

(<*) :: ExtendedScope lore m a -> ExtendedScope lore m b -> ExtendedScope lore m a #

extendedScope :: ExtendedScope lore m a -> Scope lore -> m a Source #

Run a computation in the extended type environment.