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

Blanks.ScopeW

Description

Internals.

Synopsis

Documentation

type ScopeWC t u n f g = (Adjunction t u, Applicative u, Functor f, NatNewtype (ScopeW t n f g) g) Source #

newtype ScopeW t n f g a Source #

The core internal scope type. (The "w" comes from "wrapper".) We wrap up an UnderScope in some functor and demand that we unwrap it in an adjoint context. In the first case, these functors will be Identity, yielding the Scope newtype. In the second case, these functors will be Located and Colocated, yielding the LocScope newtype.

Constructors

ScopeW 

Fields

Instances

Instances details
(Functor t, Functor f, Functor g) => Functor (ScopeW t n f g) Source # 
Instance details

Defined in Blanks.ScopeW

Methods

fmap :: (a -> b) -> ScopeW t n f g a -> ScopeW t n f g b #

(<$) :: a -> ScopeW t n f g b -> ScopeW t n f g a #

(Foldable t, Foldable f, Foldable g) => Foldable (ScopeW t n f g) Source # 
Instance details

Defined in Blanks.ScopeW

Methods

fold :: Monoid m => ScopeW t n f g m -> m #

foldMap :: Monoid m => (a -> m) -> ScopeW t n f g a -> m #

foldMap' :: Monoid m => (a -> m) -> ScopeW t n f g a -> m #

foldr :: (a -> b -> b) -> b -> ScopeW t n f g a -> b #

foldr' :: (a -> b -> b) -> b -> ScopeW t n f g a -> b #

foldl :: (b -> a -> b) -> b -> ScopeW t n f g a -> b #

foldl' :: (b -> a -> b) -> b -> ScopeW t n f g a -> b #

foldr1 :: (a -> a -> a) -> ScopeW t n f g a -> a #

foldl1 :: (a -> a -> a) -> ScopeW t n f g a -> a #

toList :: ScopeW t n f g a -> [a] #

null :: ScopeW t n f g a -> Bool #

length :: ScopeW t n f g a -> Int #

elem :: Eq a => a -> ScopeW t n f g a -> Bool #

maximum :: Ord a => ScopeW t n f g a -> a #

minimum :: Ord a => ScopeW t n f g a -> a #

sum :: Num a => ScopeW t n f g a -> a #

product :: Num a => ScopeW t n f g a -> a #

(Traversable t, Traversable f, Traversable g) => Traversable (ScopeW t n f g) Source # 
Instance details

Defined in Blanks.ScopeW

Methods

traverse :: Applicative f0 => (a -> f0 b) -> ScopeW t n f g a -> f0 (ScopeW t n f g b) #

sequenceA :: Applicative f0 => ScopeW t n f g (f0 a) -> f0 (ScopeW t n f g a) #

mapM :: Monad m => (a -> m b) -> ScopeW t n f g a -> m (ScopeW t n f g b) #

sequence :: Monad m => ScopeW t n f g (m a) -> m (ScopeW t n f g a) #

NatNewtype (ScopeW Identity n f (Scope n f)) (Scope n f) Source # 
Instance details

Defined in Blanks.Scope

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

Defined in Blanks.LocScope

Eq (t (UnderScope n f (g a) a)) => Eq (ScopeW t n f g a) Source # 
Instance details

Defined in Blanks.ScopeW

Methods

(==) :: ScopeW t n f g a -> ScopeW t n f g a -> Bool #

(/=) :: ScopeW t n f g a -> ScopeW t n f g a -> Bool #

Show (t (UnderScope n f (g a) a)) => Show (ScopeW t n f g a) Source # 
Instance details

Defined in Blanks.ScopeW

Methods

showsPrec :: Int -> ScopeW t n f g a -> ShowS #

show :: ScopeW t n f g a -> String #

showList :: [ScopeW t n f g a] -> ShowS #

NFData (t (UnderScope n f (g a) a)) => NFData (ScopeW t n f g a) Source # 
Instance details

Defined in Blanks.ScopeW

Methods

rnf :: ScopeW t n f g a -> () #

scopeWFree :: ScopeWC t u n f g => a -> u (g a) Source #

scopeWEmbed :: ScopeWC t u n f g => f (g a) -> u (g a) Source #

scopeWFromInnerBinder :: ScopeWC t u n f g => BinderScope n (g a) -> u (g a) Source #

scopeWInnerBinder :: (ScopeWC t u n f g, Eq a) => n -> Seq a -> g a -> BinderScope n (g a) Source #

scopeWInnerBinder1 :: (ScopeWC t u n f g, Eq a) => n -> a -> g a -> BinderScope n (g a) Source #

scopeWAbstract :: (ScopeWC t u n f g, Eq a) => n -> Seq a -> g a -> u (g a) Source #

scopeWAbstract1 :: (ScopeWC t u n f g, Eq a) => n -> a -> g a -> u (g a) Source #

scopeWUnAbstract :: ScopeWC t u n f g => Seq a -> g a -> g a Source #

scopeWUnAbstract1 :: ScopeWC t u n f g => a -> g a -> g a Source #

scopeWInstantiate :: ScopeWC t u n f g => Seq (u (g a)) -> g a -> g a Source #

scopeWInstantiate1 :: ScopeWC t u n f g => u (g a) -> g a -> g a Source #

scopeWApply :: ScopeWC t u n f g => Seq (u (g a)) -> g a -> Either SubError (g a) Source #

scopeWApply1 :: ScopeWC t u n f g => u (g a) -> g a -> Either SubError (g a) Source #

scopeWBind :: ScopeWC t u n f g => (a -> u (g b)) -> g a -> g b Source #

scopeWBindOpt :: ScopeWC t u n f g => (a -> Maybe (u (g a))) -> g a -> g a Source #

scopeWLift :: (ScopeWC t u n f g, Monad u, Traversable f) => f a -> u (g a) Source #

scopeWLiftAnno :: (NatNewtype (ScopeW t n f g) g, Functor t) => t a -> g a Source #

scopeWHoistAnno :: (NatNewtype (ScopeW t n f g) g, NatNewtype (ScopeW w n f h) h, Functor t, Functor w, Functor f) => (forall x. t x -> w x) -> g a -> h a Source #

scopeWMapAnno :: ScopeWC t u n f g => (t a -> t b) -> g a -> g b Source #