Copyright | (C) 2018 Ryan Scott |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Ryan Scott |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | GHC2021 |
Data.Traversable.Singletons
Contents
Description
Defines the promoted and singled versions of the Traversable
type class.
Synopsis
- class PTraversable (t :: Type -> Type) where
- class (SFunctor t, SFoldable t) => STraversable (t :: Type -> Type) where
- sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: t a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2)
- sSequenceA :: forall (f :: Type -> Type) a (t1 :: t (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1)
- sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: t a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2)
- sSequence :: forall (m :: Type -> Type) a (t1 :: t (m a)). SMonad m => Sing t1 -> Sing (Sequence t1)
- type family For (a1 :: t a) (a2 :: a ~> f b) :: f (t b) where ...
- sFor :: forall (t1 :: Type -> Type) a (f :: Type -> Type) b (t2 :: t1 a) (t3 :: a ~> f b). (STraversable t1, SApplicative f) => Sing t2 -> Sing t3 -> Sing (For t2 t3)
- type family ForM (a1 :: t a) (a2 :: a ~> m b) :: m (t b) where ...
- sForM :: forall (t1 :: Type -> Type) a (m :: Type -> Type) b (t2 :: t1 a) (t3 :: a ~> m b). (STraversable t1, SMonad m) => Sing t2 -> Sing t3 -> Sing (ForM t2 t3)
- type family MapAccumL (a1 :: a ~> (b ~> (a, c))) (a2 :: a) (a3 :: t b) :: (a, t c) where ...
- sMapAccumL :: forall (t1 :: Type -> Type) a b c (t2 :: a ~> (b ~> (a, c))) (t3 :: a) (t4 :: t1 b). STraversable t1 => Sing t2 -> Sing t3 -> Sing t4 -> Sing (MapAccumL t2 t3 t4)
- type family MapAccumR (a1 :: a ~> (b ~> (a, c))) (a2 :: a) (a3 :: t b) :: (a, t c) where ...
- sMapAccumR :: forall a b c (t1 :: Type -> Type) (t2 :: a ~> (b ~> (a, c))) (t3 :: a) (t4 :: t1 b). STraversable t1 => Sing t2 -> Sing t3 -> Sing t4 -> Sing (MapAccumR t2 t3 t4)
- type family FmapDefault (a1 :: a ~> b) (a2 :: t a) :: t b where ...
- sFmapDefault :: forall (t1 :: Type -> Type) a b (t2 :: a ~> b) (t3 :: t1 a). STraversable t1 => Sing t2 -> Sing t3 -> Sing (FmapDefault t2 t3)
- type family FoldMapDefault (a1 :: a ~> m) (a2 :: t a) :: m where ...
- sFoldMapDefault :: forall (t1 :: Type -> Type) m a (t2 :: a ~> m) (t3 :: t1 a). (STraversable t1, SMonoid m) => Sing t2 -> Sing t3 -> Sing (FoldMapDefault t2 t3)
- data TraverseSym0 (a1 :: TyFun (a ~> f b) (t a ~> f (t b)))
- data TraverseSym1 (a6989586621680096860 :: a ~> f b) (b1 :: TyFun (t a) (f (t b)))
- type family TraverseSym2 (a6989586621680096860 :: a ~> f b) (a6989586621680096861 :: t a) :: f (t b) where ...
- data SequenceASym0 (a1 :: TyFun (t (f a)) (f (t a)))
- type family SequenceASym1 (a6989586621680096864 :: t (f a)) :: f (t a) where ...
- data MapMSym0 (a1 :: TyFun (a ~> m b) (t a ~> m (t b)))
- data MapMSym1 (a6989586621680096868 :: a ~> m b) (b1 :: TyFun (t a) (m (t b)))
- type family MapMSym2 (a6989586621680096868 :: a ~> m b) (a6989586621680096869 :: t a) :: m (t b) where ...
- data SequenceSym0 (a1 :: TyFun (t (m a)) (m (t a)))
- type family SequenceSym1 (a6989586621680096872 :: t (m a)) :: m (t a) where ...
- data ForSym0 (a1 :: TyFun (t a) ((a ~> f b) ~> f (t b)))
- data ForSym1 (a6989586621680103106 :: t a) (b1 :: TyFun (a ~> f b) (f (t b)))
- type family ForSym2 (a6989586621680103106 :: t a) (a6989586621680103107 :: a ~> f b) :: f (t b) where ...
- data ForMSym0 (a1 :: TyFun (t a) ((a ~> m b) ~> m (t b)))
- data ForMSym1 (a6989586621680103095 :: t a) (b1 :: TyFun (a ~> m b) (m (t b)))
- type family ForMSym2 (a6989586621680103095 :: t a) (a6989586621680103096 :: a ~> m b) :: m (t b) where ...
- data MapAccumLSym0 (a1 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))))
- data MapAccumLSym1 (a6989586621680103082 :: a ~> (b ~> (a, c))) (b1 :: TyFun a (t b ~> (a, t c)))
- data MapAccumLSym2 (a6989586621680103082 :: a ~> (b ~> (a, c))) (a6989586621680103083 :: a) (c1 :: TyFun (t b) (a, t c))
- type family MapAccumLSym3 (a6989586621680103082 :: a ~> (b ~> (a, c))) (a6989586621680103083 :: a) (a6989586621680103084 :: t b) :: (a, t c) where ...
- data MapAccumRSym0 (a1 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))))
- data MapAccumRSym1 (a6989586621680103072 :: a ~> (b ~> (a, c))) (b1 :: TyFun a (t b ~> (a, t c)))
- data MapAccumRSym2 (a6989586621680103072 :: a ~> (b ~> (a, c))) (a6989586621680103073 :: a) (c1 :: TyFun (t b) (a, t c))
- type family MapAccumRSym3 (a6989586621680103072 :: a ~> (b ~> (a, c))) (a6989586621680103073 :: a) (a6989586621680103074 :: t b) :: (a, t c) where ...
- data FmapDefaultSym0 (a1 :: TyFun (a ~> b) (t a ~> t b))
- data FmapDefaultSym1 (a6989586621680103058 :: a ~> b) (b1 :: TyFun (t a) (t b))
- type family FmapDefaultSym2 (a6989586621680103058 :: a ~> b) (a6989586621680103059 :: t a) :: t b where ...
- data FoldMapDefaultSym0 (a1 :: TyFun (a ~> m) (t a ~> m))
- data FoldMapDefaultSym1 (a6989586621680103039 :: a ~> m) (b :: TyFun (t a) m)
- type family FoldMapDefaultSym2 (a6989586621680103039 :: a ~> m) (a6989586621680103040 :: t a) :: m where ...
Documentation
class PTraversable (t :: Type -> Type) Source #
Associated Types
type Traverse (arg :: a ~> f b) (arg1 :: t a) :: f (t b) Source #
type SequenceA (arg :: t (f a)) :: f (t a) Source #
type SequenceA (arg :: t (f a)) = SequenceA_6989586621680096887 arg
type MapM (arg :: a ~> m b) (arg1 :: t a) :: m (t b) Source #
type Sequence (arg :: t (m a)) :: m (t a) Source #
type Sequence (arg :: t (m a)) = Sequence_6989586621680096911 arg
Instances
class (SFunctor t, SFoldable t) => STraversable (t :: Type -> Type) where Source #
Minimal complete definition
Nothing
Methods
sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: t a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #
default sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: t a). (Traverse t1 t2 ~ Traverse_6989586621680096875 t1 t2, SApplicative f) => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #
sSequenceA :: forall (f :: Type -> Type) a (t1 :: t (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #
default sSequenceA :: forall (f :: Type -> Type) a (t1 :: t (f a)). (SequenceA t1 ~ SequenceA_6989586621680096887 t1, SApplicative f) => Sing t1 -> Sing (SequenceA t1) Source #
sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: t a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #
default sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: t a). (MapM t1 t2 ~ MapM_6989586621680096897 t1 t2, SMonad m) => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #
sSequence :: forall (m :: Type -> Type) a (t1 :: t (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #
Instances
STraversable First Source # | |
Defined in Data.Semigroup.Singletons Methods sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: First a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a (t1 :: First (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: First a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: First (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable Last Source # | |
Defined in Data.Semigroup.Singletons Methods sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Last a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a (t1 :: Last (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Last a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: Last (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable Max Source # | |
Defined in Data.Semigroup.Singletons Methods sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Max a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a (t1 :: Max (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Max a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: Max (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable Min Source # | |
Defined in Data.Semigroup.Singletons Methods sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Min a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a (t1 :: Min (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Min a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: Min (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable NonEmpty Source # | |
Defined in Data.Traversable.Singletons Methods sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: NonEmpty a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a (t1 :: NonEmpty (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: NonEmpty a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: NonEmpty (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable Identity Source # | |
Defined in Data.Traversable.Singletons Methods sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Identity a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a (t1 :: Identity (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Identity a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: Identity (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable First Source # | |
Defined in Data.Traversable.Singletons Methods sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: First a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a (t1 :: First (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: First a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: First (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable Last Source # | |
Defined in Data.Traversable.Singletons Methods sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Last a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a (t1 :: Last (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Last a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: Last (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable Dual Source # | |
Defined in Data.Traversable.Singletons Methods sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Dual a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a (t1 :: Dual (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Dual a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: Dual (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable Product Source # | |
Defined in Data.Traversable.Singletons Methods sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Product a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a (t1 :: Product (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Product a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: Product (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable Sum Source # | |
Defined in Data.Traversable.Singletons Methods sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Sum a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a (t1 :: Sum (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Sum a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: Sum (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable Maybe Source # | |
Defined in Data.Traversable.Singletons Methods sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Maybe a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a (t1 :: Maybe (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Maybe a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: Maybe (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable [] Source # | |
Defined in Data.Traversable.Singletons Methods sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: [a]). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a (t1 :: [f a]). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: [a]). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: [m a]). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable (Arg a) Source # | |
Defined in Data.Semigroup.Singletons Methods sTraverse :: forall a0 (f :: Type -> Type) b (t1 :: a0 ~> f b) (t2 :: Arg a a0). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a0 (t1 :: Arg a (f a0)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a0 (m :: Type -> Type) b (t1 :: a0 ~> m b) (t2 :: Arg a a0). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a0 (t1 :: Arg a (m a0)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable (Either a) Source # | |
Defined in Data.Traversable.Singletons Methods sTraverse :: forall a0 (f :: Type -> Type) b (t1 :: a0 ~> f b) (t2 :: Either a a0). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a0 (t1 :: Either a (f a0)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a0 (m :: Type -> Type) b (t1 :: a0 ~> m b) (t2 :: Either a a0). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a0 (t1 :: Either a (m a0)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable (Proxy :: Type -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Proxy a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a (t1 :: Proxy (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Proxy a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: Proxy (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable ((,) a) Source # | |
Defined in Data.Traversable.Singletons Methods sTraverse :: forall a0 (f :: Type -> Type) b (t1 :: a0 ~> f b) (t2 :: (a, a0)). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a0 (t1 :: (a, f a0)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a0 (m :: Type -> Type) b (t1 :: a0 ~> m b) (t2 :: (a, a0)). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a0 (t1 :: (a, m a0)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
STraversable (Const m :: Type -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Const m a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f :: Type -> Type) a (t1 :: Const m (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m0 :: Type -> Type) b (t1 :: a ~> m0 b) (t2 :: Const m a). SMonad m0 => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m0 :: Type -> Type) a (t1 :: Const m (m0 a)). SMonad m0 => Sing t1 -> Sing (Sequence t1) Source # | |
(STraversable f, STraversable g) => STraversable (Product f g) Source # | |
Defined in Data.Functor.Product.Singletons Methods sTraverse :: forall a (f0 :: Type -> Type) b (t1 :: a ~> f0 b) (t2 :: Product f g a). SApplicative f0 => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f0 :: Type -> Type) a (t1 :: Product f g (f0 a)). SApplicative f0 => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Product f g a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: Product f g (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
(STraversable f, STraversable g) => STraversable (Sum f g) Source # | |
Defined in Data.Functor.Sum.Singletons Methods sTraverse :: forall a (f0 :: Type -> Type) b (t1 :: a ~> f0 b) (t2 :: Sum f g a). SApplicative f0 => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f0 :: Type -> Type) a (t1 :: Sum f g (f0 a)). SApplicative f0 => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Sum f g a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: Sum f g (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # | |
(STraversable f, STraversable g) => STraversable (Compose f g) Source # | |
Defined in Data.Functor.Compose.Singletons Methods sTraverse :: forall a (f0 :: Type -> Type) b (t1 :: a ~> f0 b) (t2 :: Compose f g a). SApplicative f0 => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source # sSequenceA :: forall (f0 :: Type -> Type) a (t1 :: Compose f g (f0 a)). SApplicative f0 => Sing t1 -> Sing (SequenceA t1) Source # sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Compose f g a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source # sSequence :: forall (m :: Type -> Type) a (t1 :: Compose f g (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source # |
type family For (a1 :: t a) (a2 :: a ~> f b) :: f (t b) where ... Source #
Equations
For (a_6989586621680103099 :: t a) (a_6989586621680103101 :: a ~> f b) = Apply (Apply (Apply (FlipSym0 :: TyFun ((a ~> f b) ~> (t a ~> f (t b))) (t a ~> ((a ~> f b) ~> f (t b))) -> Type) (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type)) a_6989586621680103099) a_6989586621680103101 |
sFor :: forall (t1 :: Type -> Type) a (f :: Type -> Type) b (t2 :: t1 a) (t3 :: a ~> f b). (STraversable t1, SApplicative f) => Sing t2 -> Sing t3 -> Sing (For t2 t3) Source #
sForM :: forall (t1 :: Type -> Type) a (m :: Type -> Type) b (t2 :: t1 a) (t3 :: a ~> m b). (STraversable t1, SMonad m) => Sing t2 -> Sing t3 -> Sing (ForM t2 t3) Source #
type family MapAccumL (a1 :: a ~> (b ~> (a, c))) (a2 :: a) (a3 :: t b) :: (a, t c) where ... Source #
Equations
MapAccumL (f :: a ~> (b ~> (a, c))) (s :: a) (t2 :: t1 b) = Apply (Apply (RunStateLSym0 :: TyFun (StateL a (t1 c)) (a ~> (a, t1 c)) -> Type) (Apply (Apply (TraverseSym0 :: TyFun (b ~> StateL a c) (t1 b ~> StateL a (t1 c)) -> Type) (Apply (Apply ((.@#@$) :: TyFun ((a ~> (a, c)) ~> StateL a c) ((b ~> (a ~> (a, c))) ~> (b ~> StateL a c)) -> Type) (StateLSym0 :: TyFun (a ~> (a, c)) (StateL a c) -> Type)) (Apply (FlipSym0 :: TyFun (a ~> (b ~> (a, c))) (b ~> (a ~> (a, c))) -> Type) f))) t2)) s |
sMapAccumL :: forall (t1 :: Type -> Type) a b c (t2 :: a ~> (b ~> (a, c))) (t3 :: a) (t4 :: t1 b). STraversable t1 => Sing t2 -> Sing t3 -> Sing t4 -> Sing (MapAccumL t2 t3 t4) Source #
type family MapAccumR (a1 :: a ~> (b ~> (a, c))) (a2 :: a) (a3 :: t b) :: (a, t c) where ... Source #
Equations
MapAccumR (f :: k1 ~> (a ~> (k1, b))) (s :: k1) (t2 :: t1 a) = Apply (Apply (RunStateRSym0 :: TyFun (StateR k1 (t1 b)) (k1 ~> (k1, t1 b)) -> Type) (Apply (Apply (TraverseSym0 :: TyFun (a ~> StateR k1 b) (t1 a ~> StateR k1 (t1 b)) -> Type) (Apply (Apply ((.@#@$) :: TyFun ((k1 ~> (k1, b)) ~> StateR k1 b) ((a ~> (k1 ~> (k1, b))) ~> (a ~> StateR k1 b)) -> Type) (StateRSym0 :: TyFun (k1 ~> (k1, b)) (StateR k1 b) -> Type)) (Apply (FlipSym0 :: TyFun (k1 ~> (a ~> (k1, b))) (a ~> (k1 ~> (k1, b))) -> Type) f))) t2)) s |
sMapAccumR :: forall a b c (t1 :: Type -> Type) (t2 :: a ~> (b ~> (a, c))) (t3 :: a) (t4 :: t1 b). STraversable t1 => Sing t2 -> Sing t3 -> Sing t4 -> Sing (MapAccumR t2 t3 t4) Source #
type family FmapDefault (a1 :: a ~> b) (a2 :: t a) :: t b where ... Source #
Equations
FmapDefault (f :: a ~> b) (x :: t a) = Apply (LamCases_6989586621680103062Sym0 t a b f x :: TyFun (Identity (t b)) (t b) -> Type) (Apply (Apply (TraverseSym0 :: TyFun (a ~> Identity b) (t a ~> Identity (t b)) -> Type) (Apply (Apply ((.@#@$) :: TyFun (b ~> Identity b) ((a ~> b) ~> (a ~> Identity b)) -> Type) (IdentitySym0 :: TyFun b (Identity b) -> Type)) f)) x) |
sFmapDefault :: forall (t1 :: Type -> Type) a b (t2 :: a ~> b) (t3 :: t1 a). STraversable t1 => Sing t2 -> Sing t3 -> Sing (FmapDefault t2 t3) Source #
type family FoldMapDefault (a1 :: a ~> m) (a2 :: t a) :: m where ... Source #
Equations
FoldMapDefault (f :: a ~> m) (x :: t a) = Apply (LamCases_6989586621680103049Sym0 t m a f x :: TyFun (Const m (t ())) m -> Type) (Apply (Apply (TraverseSym0 :: TyFun (a ~> Const m ()) (t a ~> Const m (t ())) -> Type) (Apply (Apply ((.@#@$) :: TyFun (m ~> Const m ()) ((a ~> m) ~> (a ~> Const m ())) -> Type) (Let6989586621680103043MkConstSym0 t m a f x)) f)) x) |
sFoldMapDefault :: forall (t1 :: Type -> Type) m a (t2 :: a ~> m) (t3 :: t1 a). (STraversable t1, SMonoid m) => Sing t2 -> Sing t3 -> Sing (FoldMapDefault t2 t3) Source #
Defunctionalization symbols
data TraverseSym0 (a1 :: TyFun (a ~> f b) (t a ~> f (t b))) Source #
Instances
(STraversable t, SApplicative f) => SingI (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
SuppressUnusedWarnings (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) (a6989586621680096860 :: a ~> f b) Source # | |
Defined in Data.Traversable.Singletons type Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) (a6989586621680096860 :: a ~> f b) = TraverseSym1 a6989586621680096860 :: TyFun (t a) (f (t b)) -> Type |
data TraverseSym1 (a6989586621680096860 :: a ~> f b) (b1 :: TyFun (t a) (f (t b))) Source #
Instances
(STraversable t, SApplicative f) => SingI1 (TraverseSym1 :: (a ~> f b) -> TyFun (t a) (f (t b)) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
(STraversable t, SApplicative f, SingI d) => SingI (TraverseSym1 d :: TyFun (t a) (f (t b)) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
SuppressUnusedWarnings (TraverseSym1 a6989586621680096860 :: TyFun (t a) (f (t b)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (TraverseSym1 a6989586621680096860 :: TyFun (t a) (f (t b)) -> Type) (a6989586621680096861 :: t a) Source # | |
Defined in Data.Traversable.Singletons type Apply (TraverseSym1 a6989586621680096860 :: TyFun (t a) (f (t b)) -> Type) (a6989586621680096861 :: t a) = Traverse a6989586621680096860 a6989586621680096861 |
type family TraverseSym2 (a6989586621680096860 :: a ~> f b) (a6989586621680096861 :: t a) :: f (t b) where ... Source #
Equations
TraverseSym2 (a6989586621680096860 :: a ~> f b) (a6989586621680096861 :: t a) = Traverse a6989586621680096860 a6989586621680096861 |
data SequenceASym0 (a1 :: TyFun (t (f a)) (f (t a))) Source #
Instances
(STraversable t, SApplicative f) => SingI (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
SuppressUnusedWarnings (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) (a6989586621680096864 :: t (f a)) Source # | |
Defined in Data.Traversable.Singletons type Apply (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) (a6989586621680096864 :: t (f a)) = SequenceA a6989586621680096864 |
type family SequenceASym1 (a6989586621680096864 :: t (f a)) :: f (t a) where ... Source #
Equations
SequenceASym1 (a6989586621680096864 :: t (f a)) = SequenceA a6989586621680096864 |
data MapMSym0 (a1 :: TyFun (a ~> m b) (t a ~> m (t b))) Source #
Instances
(STraversable t, SMonad m) => SingI (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) Source # | |
SuppressUnusedWarnings (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) (a6989586621680096868 :: a ~> m b) Source # | |
data MapMSym1 (a6989586621680096868 :: a ~> m b) (b1 :: TyFun (t a) (m (t b))) Source #
Instances
(STraversable t, SMonad m) => SingI1 (MapMSym1 :: (a ~> m b) -> TyFun (t a) (m (t b)) -> Type) Source # | |
(STraversable t, SMonad m, SingI d) => SingI (MapMSym1 d :: TyFun (t a) (m (t b)) -> Type) Source # | |
SuppressUnusedWarnings (MapMSym1 a6989586621680096868 :: TyFun (t a) (m (t b)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (MapMSym1 a6989586621680096868 :: TyFun (t a) (m (t b)) -> Type) (a6989586621680096869 :: t a) Source # | |
type family MapMSym2 (a6989586621680096868 :: a ~> m b) (a6989586621680096869 :: t a) :: m (t b) where ... Source #
data SequenceSym0 (a1 :: TyFun (t (m a)) (m (t a))) Source #
Instances
(STraversable t, SMonad m) => SingI (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
SuppressUnusedWarnings (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) (a6989586621680096872 :: t (m a)) Source # | |
Defined in Data.Traversable.Singletons type Apply (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) (a6989586621680096872 :: t (m a)) = Sequence a6989586621680096872 |
type family SequenceSym1 (a6989586621680096872 :: t (m a)) :: m (t a) where ... Source #
Equations
SequenceSym1 (a6989586621680096872 :: t (m a)) = Sequence a6989586621680096872 |
data ForSym0 (a1 :: TyFun (t a) ((a ~> f b) ~> f (t b))) Source #
Instances
(STraversable t, SApplicative f) => SingI (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) Source # | |
SuppressUnusedWarnings (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) (a6989586621680103106 :: t a) Source # | |
data ForSym1 (a6989586621680103106 :: t a) (b1 :: TyFun (a ~> f b) (f (t b))) Source #
Instances
(STraversable t, SApplicative f) => SingI1 (ForSym1 :: t a -> TyFun (a ~> f b) (f (t b)) -> Type) Source # | |
(STraversable t, SApplicative f, SingI d) => SingI (ForSym1 d :: TyFun (a ~> f b) (f (t b)) -> Type) Source # | |
SuppressUnusedWarnings (ForSym1 a6989586621680103106 :: TyFun (a ~> f b) (f (t b)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ForSym1 a6989586621680103106 :: TyFun (a ~> f b) (f (t b)) -> Type) (a6989586621680103107 :: a ~> f b) Source # | |
type family ForSym2 (a6989586621680103106 :: t a) (a6989586621680103107 :: a ~> f b) :: f (t b) where ... Source #
data ForMSym0 (a1 :: TyFun (t a) ((a ~> m b) ~> m (t b))) Source #
Instances
(STraversable t, SMonad m) => SingI (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) Source # | |
SuppressUnusedWarnings (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) (a6989586621680103095 :: t a) Source # | |
data ForMSym1 (a6989586621680103095 :: t a) (b1 :: TyFun (a ~> m b) (m (t b))) Source #
Instances
(STraversable t, SMonad m) => SingI1 (ForMSym1 :: t a -> TyFun (a ~> m b) (m (t b)) -> Type) Source # | |
(STraversable t, SMonad m, SingI d) => SingI (ForMSym1 d :: TyFun (a ~> m b) (m (t b)) -> Type) Source # | |
SuppressUnusedWarnings (ForMSym1 a6989586621680103095 :: TyFun (a ~> m b) (m (t b)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ForMSym1 a6989586621680103095 :: TyFun (a ~> m b) (m (t b)) -> Type) (a6989586621680103096 :: a ~> m b) Source # | |
type family ForMSym2 (a6989586621680103095 :: t a) (a6989586621680103096 :: a ~> m b) :: m (t b) where ... Source #
data MapAccumLSym0 (a1 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c)))) Source #
Instances
STraversable t => SingI (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
SuppressUnusedWarnings (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680103082 :: a ~> (b ~> (a, c))) Source # | |
Defined in Data.Traversable.Singletons |
data MapAccumLSym1 (a6989586621680103082 :: a ~> (b ~> (a, c))) (b1 :: TyFun a (t b ~> (a, t c))) Source #
Instances
STraversable t => SingI1 (MapAccumLSym1 :: (a ~> (b ~> (a, c))) -> TyFun a (t b ~> (a, t c)) -> Type) Source # | |
(STraversable t, SingI d) => SingI (MapAccumLSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
SuppressUnusedWarnings (MapAccumLSym1 a6989586621680103082 :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (MapAccumLSym1 a6989586621680103082 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680103083 :: a) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumLSym1 a6989586621680103082 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680103083 :: a) = MapAccumLSym2 a6989586621680103082 a6989586621680103083 :: TyFun (t b) (a, t c) -> Type |
data MapAccumLSym2 (a6989586621680103082 :: a ~> (b ~> (a, c))) (a6989586621680103083 :: a) (c1 :: TyFun (t b) (a, t c)) Source #
Instances
(STraversable t, SingI d) => SingI1 (MapAccumLSym2 d :: a -> TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
STraversable t => SingI2 (MapAccumLSym2 :: (a ~> (b ~> (a, c))) -> a -> TyFun (t b) (a, t c) -> Type) Source # | |
(STraversable t, SingI d1, SingI d2) => SingI (MapAccumLSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
SuppressUnusedWarnings (MapAccumLSym2 a6989586621680103082 a6989586621680103083 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (MapAccumLSym2 a6989586621680103082 a6989586621680103083 :: TyFun (t b) (a, t c) -> Type) (a6989586621680103084 :: t b) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumLSym2 a6989586621680103082 a6989586621680103083 :: TyFun (t b) (a, t c) -> Type) (a6989586621680103084 :: t b) = MapAccumL a6989586621680103082 a6989586621680103083 a6989586621680103084 |
type family MapAccumLSym3 (a6989586621680103082 :: a ~> (b ~> (a, c))) (a6989586621680103083 :: a) (a6989586621680103084 :: t b) :: (a, t c) where ... Source #
Equations
MapAccumLSym3 (a6989586621680103082 :: a ~> (b ~> (a, c))) (a6989586621680103083 :: a) (a6989586621680103084 :: t b) = MapAccumL a6989586621680103082 a6989586621680103083 a6989586621680103084 |
data MapAccumRSym0 (a1 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c)))) Source #
Instances
STraversable t => SingI (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
SuppressUnusedWarnings (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680103072 :: a ~> (b ~> (a, c))) Source # | |
Defined in Data.Traversable.Singletons |
data MapAccumRSym1 (a6989586621680103072 :: a ~> (b ~> (a, c))) (b1 :: TyFun a (t b ~> (a, t c))) Source #
Instances
STraversable t => SingI1 (MapAccumRSym1 :: (a ~> (b ~> (a, c))) -> TyFun a (t b ~> (a, t c)) -> Type) Source # | |
(STraversable t, SingI d) => SingI (MapAccumRSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
SuppressUnusedWarnings (MapAccumRSym1 a6989586621680103072 :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (MapAccumRSym1 a6989586621680103072 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680103073 :: a) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumRSym1 a6989586621680103072 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680103073 :: a) = MapAccumRSym2 a6989586621680103072 a6989586621680103073 :: TyFun (t b) (a, t c) -> Type |
data MapAccumRSym2 (a6989586621680103072 :: a ~> (b ~> (a, c))) (a6989586621680103073 :: a) (c1 :: TyFun (t b) (a, t c)) Source #
Instances
(STraversable t, SingI d) => SingI1 (MapAccumRSym2 d :: a -> TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
STraversable t => SingI2 (MapAccumRSym2 :: (a ~> (b ~> (a, c))) -> a -> TyFun (t b) (a, t c) -> Type) Source # | |
(STraversable t, SingI d1, SingI d2) => SingI (MapAccumRSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
SuppressUnusedWarnings (MapAccumRSym2 a6989586621680103072 a6989586621680103073 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (MapAccumRSym2 a6989586621680103072 a6989586621680103073 :: TyFun (t b) (a, t c) -> Type) (a6989586621680103074 :: t b) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumRSym2 a6989586621680103072 a6989586621680103073 :: TyFun (t b) (a, t c) -> Type) (a6989586621680103074 :: t b) = MapAccumR a6989586621680103072 a6989586621680103073 a6989586621680103074 |
type family MapAccumRSym3 (a6989586621680103072 :: a ~> (b ~> (a, c))) (a6989586621680103073 :: a) (a6989586621680103074 :: t b) :: (a, t c) where ... Source #
Equations
MapAccumRSym3 (a6989586621680103072 :: a ~> (b ~> (a, c))) (a6989586621680103073 :: a) (a6989586621680103074 :: t b) = MapAccumR a6989586621680103072 a6989586621680103073 a6989586621680103074 |
data FmapDefaultSym0 (a1 :: TyFun (a ~> b) (t a ~> t b)) Source #
Instances
STraversable t => SingI (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
SuppressUnusedWarnings (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) (a6989586621680103058 :: a ~> b) Source # | |
Defined in Data.Traversable.Singletons type Apply (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) (a6989586621680103058 :: a ~> b) = FmapDefaultSym1 a6989586621680103058 :: TyFun (t a) (t b) -> Type |
data FmapDefaultSym1 (a6989586621680103058 :: a ~> b) (b1 :: TyFun (t a) (t b)) Source #
Instances
STraversable t => SingI1 (FmapDefaultSym1 :: (a ~> b) -> TyFun (t a) (t b) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
(STraversable t, SingI d) => SingI (FmapDefaultSym1 d :: TyFun (t a) (t b) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
SuppressUnusedWarnings (FmapDefaultSym1 a6989586621680103058 :: TyFun (t a) (t b) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (FmapDefaultSym1 a6989586621680103058 :: TyFun (t a) (t b) -> Type) (a6989586621680103059 :: t a) Source # | |
Defined in Data.Traversable.Singletons type Apply (FmapDefaultSym1 a6989586621680103058 :: TyFun (t a) (t b) -> Type) (a6989586621680103059 :: t a) = FmapDefault a6989586621680103058 a6989586621680103059 |
type family FmapDefaultSym2 (a6989586621680103058 :: a ~> b) (a6989586621680103059 :: t a) :: t b where ... Source #
Equations
FmapDefaultSym2 (a6989586621680103058 :: a ~> b) (a6989586621680103059 :: t a) = FmapDefault a6989586621680103058 a6989586621680103059 |
data FoldMapDefaultSym0 (a1 :: TyFun (a ~> m) (t a ~> m)) Source #
Instances
(STraversable t, SMonoid m) => SingI (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
SuppressUnusedWarnings (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680103039 :: a ~> m) Source # | |
Defined in Data.Traversable.Singletons type Apply (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680103039 :: a ~> m) = FoldMapDefaultSym1 a6989586621680103039 :: TyFun (t a) m -> Type |
data FoldMapDefaultSym1 (a6989586621680103039 :: a ~> m) (b :: TyFun (t a) m) Source #
Instances
(STraversable t, SMonoid m) => SingI1 (FoldMapDefaultSym1 :: (a ~> m) -> TyFun (t a) m -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
(STraversable t, SMonoid m, SingI d) => SingI (FoldMapDefaultSym1 d :: TyFun (t a) m -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
SuppressUnusedWarnings (FoldMapDefaultSym1 a6989586621680103039 :: TyFun (t a) m -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (FoldMapDefaultSym1 a6989586621680103039 :: TyFun (t a) m -> Type) (a6989586621680103040 :: t a) Source # | |
Defined in Data.Traversable.Singletons type Apply (FoldMapDefaultSym1 a6989586621680103039 :: TyFun (t a) m -> Type) (a6989586621680103040 :: t a) = FoldMapDefault a6989586621680103039 a6989586621680103040 |
type family FoldMapDefaultSym2 (a6989586621680103039 :: a ~> m) (a6989586621680103040 :: t a) :: m where ... Source #
Equations
FoldMapDefaultSym2 (a6989586621680103039 :: a ~> m) (a6989586621680103040 :: t a) = FoldMapDefault a6989586621680103039 a6989586621680103040 |