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

Safe HaskellNone
LanguageHaskell2010

Blanks.UnderScope

Description

Internals. You will probably never need these.

Documentation

data BinderScope n e Source #

Constructors

BinderScope 
Instances
Functor (BinderScope n) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

fmap :: (a -> b) -> BinderScope n a -> BinderScope n b #

(<$) :: a -> BinderScope n b -> BinderScope n a #

Foldable (BinderScope n) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

fold :: Monoid m => BinderScope n m -> m #

foldMap :: Monoid m => (a -> m) -> BinderScope n a -> m #

foldr :: (a -> b -> b) -> b -> BinderScope n a -> b #

foldr' :: (a -> b -> b) -> b -> BinderScope n a -> b #

foldl :: (b -> a -> b) -> b -> BinderScope n a -> b #

foldl' :: (b -> a -> b) -> b -> BinderScope n a -> b #

foldr1 :: (a -> a -> a) -> BinderScope n a -> a #

foldl1 :: (a -> a -> a) -> BinderScope n a -> a #

toList :: BinderScope n a -> [a] #

null :: BinderScope n a -> Bool #

length :: BinderScope n a -> Int #

elem :: Eq a => a -> BinderScope n a -> Bool #

maximum :: Ord a => BinderScope n a -> a #

minimum :: Ord a => BinderScope n a -> a #

sum :: Num a => BinderScope n a -> a #

product :: Num a => BinderScope n a -> a #

Traversable (BinderScope n) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

traverse :: Applicative f => (a -> f b) -> BinderScope n a -> f (BinderScope n b) #

sequenceA :: Applicative f => BinderScope n (f a) -> f (BinderScope n a) #

mapM :: Monad m => (a -> m b) -> BinderScope n a -> m (BinderScope n b) #

sequence :: Monad m => BinderScope n (m a) -> m (BinderScope n a) #

(Eq n, Eq e) => Eq (BinderScope n e) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

(==) :: BinderScope n e -> BinderScope n e -> Bool #

(/=) :: BinderScope n e -> BinderScope n e -> Bool #

(Show n, Show e) => Show (BinderScope n e) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

showsPrec :: Int -> BinderScope n e -> ShowS #

show :: BinderScope n e -> String #

showList :: [BinderScope n e] -> ShowS #

Generic (BinderScope n e) Source # 
Instance details

Defined in Blanks.UnderScope

Associated Types

type Rep (BinderScope n e) :: Type -> Type #

Methods

from :: BinderScope n e -> Rep (BinderScope n e) x #

to :: Rep (BinderScope n e) x -> BinderScope n e #

(NFData n, NFData e) => NFData (BinderScope n e) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

rnf :: BinderScope n e -> () #

type Rep (BinderScope n e) Source # 
Instance details

Defined in Blanks.UnderScope

type Rep (BinderScope n e) = D1 (MetaData "BinderScope" "Blanks.UnderScope" "blanks-0.4.1-Scp4rffKsbBwGbu4IFzSt" False) (C1 (MetaCons "BinderScope" PrefixI True) (S1 (MetaSel (Just "binderScopeArity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Just "binderScopeInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 n) :*: S1 (MetaSel (Just "binderScopeBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e))))

newtype BoundScope Source #

Constructors

BoundScope 

Fields

Instances
Eq BoundScope Source # 
Instance details

Defined in Blanks.UnderScope

Show BoundScope Source # 
Instance details

Defined in Blanks.UnderScope

NFData BoundScope Source # 
Instance details

Defined in Blanks.UnderScope

Methods

rnf :: BoundScope -> () #

newtype EmbedScope f e Source #

Constructors

EmbedScope 

Fields

Instances
Functor f => Functor (EmbedScope f) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

fmap :: (a -> b) -> EmbedScope f a -> EmbedScope f b #

(<$) :: a -> EmbedScope f b -> EmbedScope f a #

Eq (f e) => Eq (EmbedScope f e) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

(==) :: EmbedScope f e -> EmbedScope f e -> Bool #

(/=) :: EmbedScope f e -> EmbedScope f e -> Bool #

Show (f e) => Show (EmbedScope f e) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

showsPrec :: Int -> EmbedScope f e -> ShowS #

show :: EmbedScope f e -> String #

showList :: [EmbedScope f e] -> ShowS #

NFData (f e) => NFData (EmbedScope f e) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

rnf :: EmbedScope f e -> () #

newtype FreeScope a Source #

Constructors

FreeScope 

Fields

Instances
Functor FreeScope Source # 
Instance details

Defined in Blanks.UnderScope

Methods

fmap :: (a -> b) -> FreeScope a -> FreeScope b #

(<$) :: a -> FreeScope b -> FreeScope a #

Foldable FreeScope Source # 
Instance details

Defined in Blanks.UnderScope

Methods

fold :: Monoid m => FreeScope m -> m #

foldMap :: Monoid m => (a -> m) -> FreeScope a -> m #

foldr :: (a -> b -> b) -> b -> FreeScope a -> b #

foldr' :: (a -> b -> b) -> b -> FreeScope a -> b #

foldl :: (b -> a -> b) -> b -> FreeScope a -> b #

foldl' :: (b -> a -> b) -> b -> FreeScope a -> b #

foldr1 :: (a -> a -> a) -> FreeScope a -> a #

foldl1 :: (a -> a -> a) -> FreeScope a -> a #

toList :: FreeScope a -> [a] #

null :: FreeScope a -> Bool #

length :: FreeScope a -> Int #

elem :: Eq a => a -> FreeScope a -> Bool #

maximum :: Ord a => FreeScope a -> a #

minimum :: Ord a => FreeScope a -> a #

sum :: Num a => FreeScope a -> a #

product :: Num a => FreeScope a -> a #

Traversable FreeScope Source # 
Instance details

Defined in Blanks.UnderScope

Methods

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

sequenceA :: Applicative f => FreeScope (f a) -> f (FreeScope a) #

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

sequence :: Monad m => FreeScope (m a) -> m (FreeScope a) #

Eq a => Eq (FreeScope a) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

(==) :: FreeScope a -> FreeScope a -> Bool #

(/=) :: FreeScope a -> FreeScope a -> Bool #

Show a => Show (FreeScope a) Source # 
Instance details

Defined in Blanks.UnderScope

NFData a => NFData (FreeScope a) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

rnf :: FreeScope a -> () #

data UnderScope n f e a Source #

Instances
Traversable f => Bitraversable (UnderScope n f) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> UnderScope n f a b -> f0 (UnderScope n f c d) #

Foldable f => Bifoldable (UnderScope n f) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

bifold :: Monoid m => UnderScope n f m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> UnderScope n f a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> UnderScope n f a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> UnderScope n f a b -> c #

Functor f => Bifunctor (UnderScope n f) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

bimap :: (a -> b) -> (c -> d) -> UnderScope n f a c -> UnderScope n f b d #

first :: (a -> b) -> UnderScope n f a c -> UnderScope n f b c #

second :: (b -> c) -> UnderScope n f a b -> UnderScope n f a c #

Functor (UnderScope n f e) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

fmap :: (a -> b) -> UnderScope n f e a -> UnderScope n f e b #

(<$) :: a -> UnderScope n f e b -> UnderScope n f e a #

(Eq a, Eq n, Eq e, Eq (f e)) => Eq (UnderScope n f e a) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

(==) :: UnderScope n f e a -> UnderScope n f e a -> Bool #

(/=) :: UnderScope n f e a -> UnderScope n f e a -> Bool #

(Show a, Show n, Show e, Show (f e)) => Show (UnderScope n f e a) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

showsPrec :: Int -> UnderScope n f e a -> ShowS #

show :: UnderScope n f e a -> String #

showList :: [UnderScope n f e a] -> ShowS #

Generic (UnderScope n f e a) Source # 
Instance details

Defined in Blanks.UnderScope

Associated Types

type Rep (UnderScope n f e a) :: Type -> Type #

Methods

from :: UnderScope n f e a -> Rep (UnderScope n f e a) x #

to :: Rep (UnderScope n f e a) x -> UnderScope n f e a #

(NFData a, NFData n, NFData e, NFData (f e)) => NFData (UnderScope n f e a) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

rnf :: UnderScope n f e a -> () #

type Rep (UnderScope n f e a) Source # 
Instance details

Defined in Blanks.UnderScope

data UnderScopeFold n f e a r Source #

Constructors

UnderScopeFold 

Fields

Instances
Functor (UnderScopeFold n f e a) Source # 
Instance details

Defined in Blanks.UnderScope

Methods

fmap :: (a0 -> b) -> UnderScopeFold n f e a a0 -> UnderScopeFold n f e a b #

(<$) :: a0 -> UnderScopeFold n f e a b -> UnderScopeFold n f e a a0 #

pattern UnderScopeBound :: Int -> UnderScope n f e a Source #

pattern UnderScopeFree :: a -> UnderScope n f e a Source #

pattern UnderScopeBinder :: Int -> n -> e -> UnderScope n f e a Source #

pattern UnderScopeEmbed :: f e -> UnderScope n f e a Source #

underScopeFold :: UnderScopeFold n f e a r -> UnderScope n f e a -> r Source #

underScopeShift :: Functor f => (Int -> Int -> e -> e) -> Int -> Int -> UnderScope n f e a -> UnderScope n f e a Source #