blanks-0.4.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. See Blank for usage, and see the patterns in this module for easy manipulation and inspection.

Constructors

LocScope 

Fields

Instances
(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 #

fail :: String -> 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 #

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) #

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

Defined in Blanks.LocScope

(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 #

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

Defined in Blanks.LocScope

type BlankFunctor (LocScope l n f) Source # 
Instance details

Defined in Blanks.LocScope

type BlankFunctor (LocScope l n f) = f
type BlankInfo (LocScope l n f) Source # 
Instance details

Defined in Blanks.LocScope

type BlankInfo (LocScope l n f) = n
type BlankRight (LocScope l n f) Source # 
Instance details

Defined in Blanks.LocScope

type BlankRight (LocScope l n f) = Colocated l
type BlankLeft (LocScope l n f) Source # 
Instance details

Defined in Blanks.LocScope

type BlankLeft (LocScope l n f) = Located l

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.

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

Forget all the annotations and yield a plain Scope.