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

Blanks.Core

Description

Internals.

Documentation

newtype BoundScope Source #

Constructors

BoundScope 

Fields

Instances

Instances details
Eq BoundScope Source # 
Instance details

Defined in Blanks.Core

Show BoundScope Source # 
Instance details

Defined in Blanks.Core

NFData BoundScope Source # 
Instance details

Defined in Blanks.Core

Methods

rnf :: BoundScope -> () #

newtype FreeScope a Source #

Constructors

FreeScope 

Fields

Instances

Instances details
Functor FreeScope Source # 
Instance details

Defined in Blanks.Core

Methods

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

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

Foldable FreeScope Source # 
Instance details

Defined in Blanks.Core

Methods

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

foldMap :: Monoid m => (a -> m) -> FreeScope a -> 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.Core

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.Core

Methods

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

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

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

Defined in Blanks.Core

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

Defined in Blanks.Core

Methods

rnf :: FreeScope a -> () #

data BinderScope n e Source #

Constructors

BinderScope 

Instances

Instances details
Functor (BinderScope n) Source # 
Instance details

Defined in Blanks.Core

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.Core

Methods

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

foldMap :: Monoid m => (a -> m) -> BinderScope n a -> 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.Core

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.Core

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.Core

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.Core

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.Core

Methods

rnf :: BinderScope n e -> () #

type Rep (BinderScope n e) Source # 
Instance details

Defined in Blanks.Core

type Rep (BinderScope n e) = D1 ('MetaData "BinderScope" "Blanks.Core" "blanks-0.5.0-inplace" '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 EmbedScope f e Source #

Constructors

EmbedScope 

Fields

Instances

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

Defined in Blanks.Core

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.Core

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.Core

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.Core

Methods

rnf :: EmbedScope f e -> () #