Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- class HBound k where
- data BV g f a where
- foldBV :: (w a -> r) -> (v a -> r) -> BV w v a -> r
- hbitraverseBV :: Functor t => (g a -> t (g' b)) -> (f a -> t (f' b)) -> BV g f a -> t (BV g' f' b)
- hbimapBV :: (g a -> g' b) -> (f a -> f' b) -> BV g f a -> BV g' f' b
- newtype Scope g h f a = Scope {}
- _Scope :: Iso (Scope g h f a) (Scope g' h' f' a') (h (BV g (h f)) a) (h' (BV g' (h' f')) a')
- hbitraverseScope :: (Applicative t, HTraversable h) => (forall b. g b -> t (g' b)) -> (forall b. f b -> t (f' b)) -> Scope g h f a -> t (Scope g' h f' a)
- freeVar :: HPointed h => f a -> Scope g h f a
- boundVar :: HPointed h => g a -> Scope g h f a
- liftScope :: (HFunctor h, HPointed h) => h f a -> Scope g h f a
- abstractTraverse :: (HMonad h, HTraversable h, Applicative t) => (forall b. f b -> t (Maybe (g b))) -> h f a -> t (Scope g h f a)
- abstract :: HMonad h => (forall b. f b -> Maybe (g b)) -> h f a -> Scope g h f a
- newtype Scoped h f g a = Scoped {}
- _Scoped :: Iso (Scoped h f g a) (Scoped h' f' g' a') (Scope g h f a) (Scope g' h' f' a')
- data SFree h f a
Documentation
hbitraverseBV :: Functor t => (g a -> t (g' b)) -> (f a -> t (f' b)) -> BV g f a -> t (BV g' f' b) Source #
newtype Scope g h f a Source #
HDuofoldableAt k1 k2 (Scope k1 k2) Source # | |
HBound k k (Scope k g) Source # | |
(Pretty2 k k h, Pretty1 k t) => Pretty2 k k (Scope k t h) Source # | |
HDuotraversable u (Scope u g) Source # | |
HDuofunctor u (Scope u g) Source # | |
HTraversable u h => HTraversable u (Scope u g h) Source # | |
HPointed k h => HPointed k (Scope k g h) Source # | |
HFunctor u h => HFunctor u (Scope u g h) Source # | |
_Scope :: Iso (Scope g h f a) (Scope g' h' f' a') (h (BV g (h f)) a) (h' (BV g' (h' f')) a') Source #
hbitraverseScope :: (Applicative t, HTraversable h) => (forall b. g b -> t (g' b)) -> (forall b. f b -> t (f' b)) -> Scope g h f a -> t (Scope g' h f' a) Source #
abstractTraverse :: (HMonad h, HTraversable h, Applicative t) => (forall b. f b -> t (Maybe (g b))) -> h f a -> t (Scope g h f a) Source #
newtype Scoped h f g a Source #
Sometimes it's convenient to move around the type arguments to Scope
.
(HFunctor k1 h, HFoldableAt k1 k2 h) => HBifoldableAt k1 k2 (Scoped k1 h) Source # | |
(Pretty2 k k h, Pretty1 k t) => Pretty2 k k (Scoped k h t) Source # | |
HTraversable k h => HBitraversable k (Scoped k h) Source # | |
HFunctor k h => HBifunctor k (Scoped k h) Source # | |
HTraversable u h => HTraversable u (Scoped u h f) Source # | |
HFunctor u h => HFunctor u (Scoped u h f) Source # | |
(HDuotraversable k1 h, HDuofoldableAt k1 k2 h) => HFoldableAt k1 k2 (SFree k1 h) Source # | |
Pretty3 k k k k h => Pretty2 k k (SFree k h) Source # | |
HDuotraversable u h => HTraversable u (SFree u h) Source # | |
HDuofunctor k h => HMonad k (SFree k h) Source # | |
HDuofunctor k h => HBind k (SFree k h) Source # | |
HPointed k (SFree k h) Source # | |
HDuofunctor u h => HFunctor u (SFree u h) Source # | |