Safe Haskell | None |
---|---|
Language | Haskell2010 |
Blanks.Under
Description
Internals.
Documentation
data UnderScope n f e a Source #
Constructors
UnderBoundScope !BoundScope | |
UnderFreeScope !(FreeScope a) | |
UnderBinderScope !(BinderScope n e) | |
UnderEmbedScope !(EmbedScope f e) |
Instances
Traversable f => Bitraversable (UnderScope n f) Source # | |
Defined in Blanks.Under 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 # | |
Defined in Blanks.Under 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 # | |
Defined in Blanks.Under 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 # | |
Defined in Blanks.Under 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 # | |
Defined in Blanks.Under 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 # | |
Defined in Blanks.Under 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 # | |
Defined in Blanks.Under 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 # | |
Defined in Blanks.Under Methods rnf :: UnderScope n f e a -> () # | |
type Rep (UnderScope n f e a) Source # | |
Defined in Blanks.Under type Rep (UnderScope n f e a) = D1 ('MetaData "UnderScope" "Blanks.Under" "blanks-0.5.0-inplace" 'False) ((C1 ('MetaCons "UnderBoundScope" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BoundScope)) :+: C1 ('MetaCons "UnderFreeScope" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (FreeScope a)))) :+: (C1 ('MetaCons "UnderBinderScope" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BinderScope n e))) :+: C1 ('MetaCons "UnderEmbedScope" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EmbedScope f e))))) |
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 #
underScopeShift :: Functor f => (Int -> Int -> e -> e) -> Int -> Int -> UnderScope n f e a -> UnderScope n f e a Source #