blanks-0.5.0: Fill-in-the-blanks - A library factoring out substitution from ASTs
Safe HaskellNone
LanguageHaskell2010

Blanks.LocScope

Synopsis

Documentation

newtype LocScope l n f a Source #

A Scope annotated with some information between constructors.

Constructors

LocScope 

Fields

Instances

Instances details
(Monoid l, Functor f) => MonadWriter l (LocScope l n f) Source # 
Instance details

Defined in Blanks.LocScope

Methods

writer :: (a, l) -> LocScope l n f a #

tell :: l -> LocScope l n f () #

listen :: LocScope l n f a -> LocScope l n f (a, l) #

pass :: LocScope l n f (a, l -> l) -> LocScope l n f a #

(Monoid l, Functor f) => Monad (LocScope l n f) Source # 
Instance details

Defined in Blanks.LocScope

Methods

(>>=) :: LocScope l n f a -> (a -> LocScope l n f b) -> LocScope l n f b #

(>>) :: LocScope l n f a -> LocScope l n f b -> LocScope l n f b #

return :: a -> LocScope l n f a #

Functor f => Functor (LocScope l n f) Source # 
Instance details

Defined in Blanks.LocScope

Methods

fmap :: (a -> b) -> LocScope l n f a -> LocScope l n f b #

(<$) :: a -> LocScope l n f b -> LocScope l n f a #

(Monoid l, Functor f) => Applicative (LocScope l n f) Source # 
Instance details

Defined in Blanks.LocScope

Methods

pure :: a -> LocScope l n f a #

(<*>) :: LocScope l n f (a -> b) -> LocScope l n f a -> LocScope l n f b #

liftA2 :: (a -> b -> c) -> LocScope l n f a -> LocScope l n f b -> LocScope l n f c #

(*>) :: LocScope l n f a -> LocScope l n f b -> LocScope l n f b #

(<*) :: LocScope l n f a -> LocScope l n f b -> LocScope l n f a #

Foldable f => Foldable (LocScope l n f) Source # 
Instance details

Defined in Blanks.LocScope

Methods

fold :: Monoid m => LocScope l n f m -> m #

foldMap :: Monoid m => (a -> m) -> LocScope l n f a -> m #

foldMap' :: Monoid m => (a -> m) -> LocScope l n f a -> m #

foldr :: (a -> b -> b) -> b -> LocScope l n f a -> b #

foldr' :: (a -> b -> b) -> b -> LocScope l n f a -> b #

foldl :: (b -> a -> b) -> b -> LocScope l n f a -> b #

foldl' :: (b -> a -> b) -> b -> LocScope l n f a -> b #

foldr1 :: (a -> a -> a) -> LocScope l n f a -> a #

foldl1 :: (a -> a -> a) -> LocScope l n f a -> a #

toList :: LocScope l n f a -> [a] #

null :: LocScope l n f a -> Bool #

length :: LocScope l n f a -> Int #

elem :: Eq a => a -> LocScope l n f a -> Bool #

maximum :: Ord a => LocScope l n f a -> a #

minimum :: Ord a => LocScope l n f a -> a #

sum :: Num a => LocScope l n f a -> a #

product :: Num a => LocScope l n f a -> a #

Traversable f => Traversable (LocScope l n f) Source # 
Instance details

Defined in Blanks.LocScope

Methods

traverse :: Applicative f0 => (a -> f0 b) -> LocScope l n f a -> f0 (LocScope l n f b) #

sequenceA :: Applicative f0 => LocScope l n f (f0 a) -> f0 (LocScope l n f a) #

mapM :: Monad m => (a -> m b) -> LocScope l n f a -> m (LocScope l n f b) #

sequence :: Monad m => LocScope l n f (m a) -> m (LocScope l n f a) #

(Eq (f (LocScope l n f a)), Eq l, Eq n, Eq a) => Eq (LocScope l n f a) Source # 
Instance details

Defined in Blanks.LocScope

Methods

(==) :: LocScope l n f a -> LocScope l n f a -> Bool #

(/=) :: LocScope l n f a -> LocScope l n f a -> Bool #

(Show (f (LocScope l n f a)), Show l, Show n, Show a) => Show (LocScope l n f a) Source # 
Instance details

Defined in Blanks.LocScope

Methods

showsPrec :: Int -> LocScope l n f a -> ShowS #

show :: LocScope l n f a -> String #

showList :: [LocScope l n f a] -> ShowS #

(NFData l, NFData n, NFData a, NFData (f (LocScope l n f a))) => NFData (LocScope l n f a) Source # 
Instance details

Defined in Blanks.LocScope

Methods

rnf :: LocScope l n f a -> () #

NatNewtype (ScopeW (Located l) n f (LocScope l n f)) (LocScope l n f) Source # 
Instance details

Defined in Blanks.LocScope

pattern LocScopeBound :: l -> Int -> LocScope l n f a Source #

pattern LocScopeFree :: l -> a -> LocScope l n f a Source #

pattern LocScopeBinder :: l -> Int -> n -> LocScope l n f a -> LocScope l n f a Source #

pattern LocScopeEmbed :: l -> f (LocScope l n f a) -> LocScope l n f a Source #

locScopeLocation :: LocScope l n f a -> l Source #

Extract the location (annotation) from this scope.

locScopeFree :: Functor f => a -> Colocated l (LocScope l n f a) Source #

locScopeEmbed :: Functor f => f (LocScope l n f a) -> Colocated l (LocScope l n f a) Source #

locScopeBind :: Functor f => (a -> Colocated l (LocScope l n f b)) -> LocScope l n f a -> LocScope l n f b Source #

locScopeBindOpt :: Functor f => (a -> Maybe (Colocated l (LocScope l n f a))) -> LocScope l n f a -> LocScope l n f a Source #

locScopeLift :: Traversable f => f a -> Colocated l (LocScope l n f a) Source #

locScopeInnerBinder :: (Functor f, Eq a) => n -> Seq a -> LocScope l n f a -> BinderScope n (LocScope l n f a) Source #

locScopeInnerBinder1 :: (Functor f, Eq a) => n -> a -> LocScope l n f a -> BinderScope n (LocScope l n f a) Source #

locScopeAbstract :: (Functor f, Eq a) => n -> Seq a -> LocScope l n f a -> Colocated l (LocScope l n f a) Source #

locScopeAbstract1 :: (Functor f, Eq a) => n -> a -> LocScope l n f a -> Colocated l (LocScope l n f a) Source #

locScopeUnAbstract :: Functor f => Seq a -> LocScope l n f a -> LocScope l n f a Source #

locScopeUnAbstract1 :: Functor f => a -> LocScope l n f a -> LocScope l n f a Source #

locScopeInstantiate :: Functor f => Seq (Colocated l (LocScope l n f a)) -> LocScope l n f a -> LocScope l n f a Source #

locScopeInstantiate1 :: Functor f => Colocated l (LocScope l n f a) -> LocScope l n f a -> LocScope l n f a Source #

locScopeApply :: Functor f => Seq (Colocated l (LocScope l n f a)) -> LocScope l n f a -> Either SubError (LocScope l n f a) Source #

locScopeApply1 :: Functor f => Colocated l (LocScope l n f a) -> LocScope l n f a -> Either SubError (LocScope l n f a) Source #

locScopeHoistAnno :: Functor f => (l -> x) -> LocScope l n f a -> LocScope x n f a Source #

locScopeMapAnno :: Functor f => (Located l a -> Located l b) -> LocScope l n f a -> LocScope l n f b Source #