blanks-0.3.0: Fill-in-the-blanks - A library factoring out substitution from ASTs

Safe HaskellNone
LanguageHaskell2010

Blanks.LocScope

Documentation

newtype Colocated l a Source #

Constructors

Colocated 

Fields

Instances
MonadReader l (Colocated l) Source # 
Instance details

Defined in Blanks.LocScope

Methods

ask :: Colocated l l #

local :: (l -> l) -> Colocated l a -> Colocated l a #

reader :: (l -> a) -> Colocated l a #

Monad (Colocated l) Source # 
Instance details

Defined in Blanks.LocScope

Methods

(>>=) :: Colocated l a -> (a -> Colocated l b) -> Colocated l b #

(>>) :: Colocated l a -> Colocated l b -> Colocated l b #

return :: a -> Colocated l a #

fail :: String -> Colocated l a #

Functor (Colocated l) Source # 
Instance details

Defined in Blanks.LocScope

Methods

fmap :: (a -> b) -> Colocated l a -> Colocated l b #

(<$) :: a -> Colocated l b -> Colocated l a #

Applicative (Colocated l) Source # 
Instance details

Defined in Blanks.LocScope

Methods

pure :: a -> Colocated l a #

(<*>) :: Colocated l (a -> b) -> Colocated l a -> Colocated l b #

liftA2 :: (a -> b -> c) -> Colocated l a -> Colocated l b -> Colocated l c #

(*>) :: Colocated l a -> Colocated l b -> Colocated l b #

(<*) :: Colocated l a -> Colocated l b -> Colocated l a #

Distributive (Colocated l) Source # 
Instance details

Defined in Blanks.LocScope

Methods

distribute :: Functor f => f (Colocated l a) -> Colocated l (f a) #

collect :: Functor f => (a -> Colocated l b) -> f a -> Colocated l (f b) #

distributeM :: Monad m => m (Colocated l a) -> Colocated l (m a) #

collectM :: Monad m => (a -> Colocated l b) -> m a -> Colocated l (m b) #

Representable (Colocated l) Source # 
Instance details

Defined in Blanks.LocScope

Associated Types

type Rep (Colocated l) :: Type #

Methods

tabulate :: (Rep (Colocated l) -> a) -> Colocated l a #

index :: Colocated l a -> Rep (Colocated l) -> a #

Adjunction (Located l) (Colocated l) Source # 
Instance details

Defined in Blanks.LocScope

Methods

unit :: a -> Colocated l (Located l a) #

counit :: Located l (Colocated l a) -> a #

leftAdjunct :: (Located l a -> b) -> a -> Colocated l b #

rightAdjunct :: (a -> Colocated l b) -> Located l a -> b #

type Rep (Colocated l) Source # 
Instance details

Defined in Blanks.LocScope

data Located l a Source #

Constructors

Located 

Fields

Instances
Monoid l => Monad (Located l) Source # 
Instance details

Defined in Blanks.LocScope

Methods

(>>=) :: Located l a -> (a -> Located l b) -> Located l b #

(>>) :: Located l a -> Located l b -> Located l b #

return :: a -> Located l a #

fail :: String -> Located l a #

Functor (Located l) Source # 
Instance details

Defined in Blanks.LocScope

Methods

fmap :: (a -> b) -> Located l a -> Located l b #

(<$) :: a -> Located l b -> Located l a #

Monoid l => Applicative (Located l) Source # 
Instance details

Defined in Blanks.LocScope

Methods

pure :: a -> Located l a #

(<*>) :: Located l (a -> b) -> Located l a -> Located l b #

liftA2 :: (a -> b -> c) -> Located l a -> Located l b -> Located l c #

(*>) :: Located l a -> Located l b -> Located l b #

(<*) :: Located l a -> Located l b -> Located l a #

Foldable (Located l) Source # 
Instance details

Defined in Blanks.LocScope

Methods

fold :: Monoid m => Located l m -> m #

foldMap :: Monoid m => (a -> m) -> Located l a -> m #

foldr :: (a -> b -> b) -> b -> Located l a -> b #

foldr' :: (a -> b -> b) -> b -> Located l a -> b #

foldl :: (b -> a -> b) -> b -> Located l a -> b #

foldl' :: (b -> a -> b) -> b -> Located l a -> b #

foldr1 :: (a -> a -> a) -> Located l a -> a #

foldl1 :: (a -> a -> a) -> Located l a -> a #

toList :: Located l a -> [a] #

null :: Located l a -> Bool #

length :: Located l a -> Int #

elem :: Eq a => a -> Located l a -> Bool #

maximum :: Ord a => Located l a -> a #

minimum :: Ord a => Located l a -> a #

sum :: Num a => Located l a -> a #

product :: Num a => Located l a -> a #

Traversable (Located l) Source # 
Instance details

Defined in Blanks.LocScope

Methods

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

sequenceA :: Applicative f => Located l (f a) -> f (Located l a) #

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

sequence :: Monad m => Located l (m a) -> m (Located l a) #

Adjunction (Located l) (Colocated l) Source # 
Instance details

Defined in Blanks.LocScope

Methods

unit :: a -> Colocated l (Located l a) #

counit :: Located l (Colocated l a) -> a #

leftAdjunct :: (Located l a -> b) -> a -> Colocated l b #

rightAdjunct :: (a -> Colocated l b) -> Located l a -> b #

(Eq l, Eq a) => Eq (Located l a) Source # 
Instance details

Defined in Blanks.LocScope

Methods

(==) :: Located l a -> Located l a -> Bool #

(/=) :: Located l a -> Located l a -> Bool #

(Show l, Show a) => Show (Located l a) Source # 
Instance details

Defined in Blanks.LocScope

Methods

showsPrec :: Int -> Located l a -> ShowS #

show :: Located l a -> String #

showList :: [Located l a] -> ShowS #

type RightAdjunct (Located l) Source # 
Instance details

Defined in Blanks.LocScope

newtype LocScope l n f a Source #

Constructors

LocScope 

Fields

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

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 => BlankAbstract (LocScope l n f) Source # 
Instance details

Defined in Blanks.LocScope

Methods

blankFree :: a -> BlankCodomain (LocScope l n f) (LocScope l n f a) Source #

blankAbstract :: Eq a => BlankInfo (LocScope l n f) -> Seq a -> LocScope l n f a -> BlankCodomain (LocScope l n f) (LocScope l n f a) Source #

blankAbstract1 :: Eq a => BlankInfo (LocScope l n f) -> a -> LocScope l n f a -> BlankCodomain (LocScope l n f) (LocScope l n f a) Source #

blankUnAbstract :: Seq a -> LocScope l n f a -> LocScope l n f a Source #

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

blankInstantiate :: Seq (BlankCodomain (LocScope l n f) (LocScope l n f a)) -> LocScope l n f a -> LocScope l n f a Source #

blankInstantiate1 :: BlankCodomain (LocScope l n f) (LocScope l n f a) -> LocScope l n f a -> LocScope l n f a Source #

blankApply :: Seq (BlankCodomain (LocScope l n f) (LocScope l n f a)) -> LocScope l n f a -> Either SubError (LocScope l n f a) Source #

blankApply1 :: BlankCodomain (LocScope l n f) (LocScope l n f a) -> LocScope l n f a -> Either SubError (LocScope l n f a) Source #

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

Defined in Blanks.LocScope

Methods

blankEmbed :: BlankFunctor (LocScope l n f) (LocScope l n f a) -> BlankCodomain (LocScope l n f) (LocScope l n f a) Source #

(Eq (f (ScopeT (Located 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 (ScopeT (Located 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 #

type BlankCodomain (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 LocScopeRawFold l n f a r = UnderScopeFold n f (LocScope l n f a) a r Source #

type LocScopeFold l n f a r = LocScopeRawFold l n f a (Colocated l r) Source #

colocated :: (l -> a) -> Colocated l a Source #

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

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

locScopeRawFold :: Functor f => LocScopeRawFold l n f a r -> LocScope l n f a -> Located l r Source #

locScopeFold :: Functor f => LocScopeFold l n f a r -> LocScope l n f a -> r Source #

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

runColocated :: Colocated l a -> l -> a Source #