singletons-2.5: A framework for generating singleton types

Copyright(C) 2018 Ryan Scott
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Singletons.Prelude.Foldable

Contents

Description

Defines the promoted and singled versions of the Foldable type class.

Synopsis
  • class PFoldable (t :: Type -> Type) where
  • class SFoldable (t :: Type -> Type) where
  • type family FoldrM (a :: (~>) a ((~>) b (m b))) (a :: b) (a :: t a) :: m b where ...
  • sFoldrM :: forall t m a b (t :: (~>) a ((~>) b (m b))) (t :: b) (t :: t a). (SFoldable t, SMonad m) => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrMSym0 t) t) t :: m b)
  • type family FoldlM (a :: (~>) b ((~>) a (m b))) (a :: b) (a :: t a) :: m b where ...
  • sFoldlM :: forall t m b a (t :: (~>) b ((~>) a (m b))) (t :: b) (t :: t a). (SFoldable t, SMonad m) => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlMSym0 t) t) t :: m b)
  • type family Traverse_ (a :: (~>) a (f b)) (a :: t a) :: f () where ...
  • sTraverse_ :: forall t f a b (t :: (~>) a (f b)) (t :: t a). (SFoldable t, SApplicative f) => Sing t -> Sing t -> Sing (Apply (Apply Traverse_Sym0 t) t :: f ())
  • type family For_ (a :: t a) (a :: (~>) a (f b)) :: f () where ...
  • sFor_ :: forall t f a b (t :: t a) (t :: (~>) a (f b)). (SFoldable t, SApplicative f) => Sing t -> Sing t -> Sing (Apply (Apply For_Sym0 t) t :: f ())
  • type family SequenceA_ (a :: t (f a)) :: f () where ...
  • sSequenceA_ :: forall t f a (t :: t (f a)). (SFoldable t, SApplicative f) => Sing t -> Sing (Apply SequenceA_Sym0 t :: f ())
  • type family Asum (a :: t (f a)) :: f a where ...
  • sAsum :: forall t f a (t :: t (f a)). (SFoldable t, SAlternative f) => Sing t -> Sing (Apply AsumSym0 t :: f a)
  • type family MapM_ (a :: (~>) a (m b)) (a :: t a) :: m () where ...
  • sMapM_ :: forall t m a b (t :: (~>) a (m b)) (t :: t a). (SFoldable t, SMonad m) => Sing t -> Sing t -> Sing (Apply (Apply MapM_Sym0 t) t :: m ())
  • type family ForM_ (a :: t a) (a :: (~>) a (m b)) :: m () where ...
  • sForM_ :: forall t m a b (t :: t a) (t :: (~>) a (m b)). (SFoldable t, SMonad m) => Sing t -> Sing t -> Sing (Apply (Apply ForM_Sym0 t) t :: m ())
  • type family Sequence_ (a :: t (m a)) :: m () where ...
  • sSequence_ :: forall t m a (t :: t (m a)). (SFoldable t, SMonad m) => Sing t -> Sing (Apply Sequence_Sym0 t :: m ())
  • type family Msum (a :: t (m a)) :: m a where ...
  • sMsum :: forall t m a (t :: t (m a)). (SFoldable t, SMonadPlus m) => Sing t -> Sing (Apply MsumSym0 t :: m a)
  • type family Concat (a :: t [a]) :: [a] where ...
  • sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a])
  • type family ConcatMap (a :: (~>) a [b]) (a :: t a) :: [b] where ...
  • sConcatMap :: forall t a b (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b])
  • type family And (a :: t Bool) :: Bool where ...
  • sAnd :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply AndSym0 t :: Bool)
  • type family Or (a :: t Bool) :: Bool where ...
  • sOr :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply OrSym0 t :: Bool)
  • type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ...
  • sAny :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool)
  • type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ...
  • sAll :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool)
  • type family MaximumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
  • sMaximumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a)
  • type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
  • sMinimumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a)
  • type family NotElem (a :: a) (a :: t a) :: Bool where ...
  • sNotElem :: forall t a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool)
  • type family Find (a :: (~>) a Bool) (a :: t a) :: Maybe a where ...
  • sFind :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a)
  • data FoldSym0 :: forall m6989586621680452724 t6989586621680452723. (~>) (t6989586621680452723 m6989586621680452724) m6989586621680452724
  • type FoldSym1 (arg6989586621680453346 :: t6989586621680452723 m6989586621680452724) = Fold arg6989586621680453346
  • data FoldMapSym0 :: forall a6989586621680452726 m6989586621680452725 t6989586621680452723. (~>) ((~>) a6989586621680452726 m6989586621680452725) ((~>) (t6989586621680452723 a6989586621680452726) m6989586621680452725)
  • data FoldMapSym1 (arg6989586621680453348 :: (~>) a6989586621680452726 m6989586621680452725) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452726) m6989586621680452725
  • type FoldMapSym2 (arg6989586621680453348 :: (~>) a6989586621680452726 m6989586621680452725) (arg6989586621680453349 :: t6989586621680452723 a6989586621680452726) = FoldMap arg6989586621680453348 arg6989586621680453349
  • data FoldrSym0 :: forall a6989586621680452727 b6989586621680452728 t6989586621680452723. (~>) ((~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) ((~>) b6989586621680452728 ((~>) (t6989586621680452723 a6989586621680452727) b6989586621680452728))
  • data FoldrSym1 (arg6989586621680453352 :: (~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) :: forall t6989586621680452723. (~>) b6989586621680452728 ((~>) (t6989586621680452723 a6989586621680452727) b6989586621680452728)
  • data FoldrSym2 (arg6989586621680453352 :: (~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) (arg6989586621680453353 :: b6989586621680452728) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452727) b6989586621680452728
  • type FoldrSym3 (arg6989586621680453352 :: (~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) (arg6989586621680453353 :: b6989586621680452728) (arg6989586621680453354 :: t6989586621680452723 a6989586621680452727) = Foldr arg6989586621680453352 arg6989586621680453353 arg6989586621680453354
  • data Foldr'Sym0 :: forall a6989586621680452729 b6989586621680452730 t6989586621680452723. (~>) ((~>) a6989586621680452729 ((~>) b6989586621680452730 b6989586621680452730)) ((~>) b6989586621680452730 ((~>) (t6989586621680452723 a6989586621680452729) b6989586621680452730))
  • data Foldr'Sym1 (arg6989586621680453358 :: (~>) a6989586621680452729 ((~>) b6989586621680452730 b6989586621680452730)) :: forall t6989586621680452723. (~>) b6989586621680452730 ((~>) (t6989586621680452723 a6989586621680452729) b6989586621680452730)
  • data Foldr'Sym2 (arg6989586621680453358 :: (~>) a6989586621680452729 ((~>) b6989586621680452730 b6989586621680452730)) (arg6989586621680453359 :: b6989586621680452730) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452729) b6989586621680452730
  • type Foldr'Sym3 (arg6989586621680453358 :: (~>) a6989586621680452729 ((~>) b6989586621680452730 b6989586621680452730)) (arg6989586621680453359 :: b6989586621680452730) (arg6989586621680453360 :: t6989586621680452723 a6989586621680452729) = Foldr' arg6989586621680453358 arg6989586621680453359 arg6989586621680453360
  • data FoldlSym0 :: forall a6989586621680452732 b6989586621680452731 t6989586621680452723. (~>) ((~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) ((~>) b6989586621680452731 ((~>) (t6989586621680452723 a6989586621680452732) b6989586621680452731))
  • data FoldlSym1 (arg6989586621680453364 :: (~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) :: forall t6989586621680452723. (~>) b6989586621680452731 ((~>) (t6989586621680452723 a6989586621680452732) b6989586621680452731)
  • data FoldlSym2 (arg6989586621680453364 :: (~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) (arg6989586621680453365 :: b6989586621680452731) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452732) b6989586621680452731
  • type FoldlSym3 (arg6989586621680453364 :: (~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) (arg6989586621680453365 :: b6989586621680452731) (arg6989586621680453366 :: t6989586621680452723 a6989586621680452732) = Foldl arg6989586621680453364 arg6989586621680453365 arg6989586621680453366
  • data Foldl'Sym0 :: forall a6989586621680452734 b6989586621680452733 t6989586621680452723. (~>) ((~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) ((~>) b6989586621680452733 ((~>) (t6989586621680452723 a6989586621680452734) b6989586621680452733))
  • data Foldl'Sym1 (arg6989586621680453370 :: (~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) :: forall t6989586621680452723. (~>) b6989586621680452733 ((~>) (t6989586621680452723 a6989586621680452734) b6989586621680452733)
  • data Foldl'Sym2 (arg6989586621680453370 :: (~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) (arg6989586621680453371 :: b6989586621680452733) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452734) b6989586621680452733
  • type Foldl'Sym3 (arg6989586621680453370 :: (~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) (arg6989586621680453371 :: b6989586621680452733) (arg6989586621680453372 :: t6989586621680452723 a6989586621680452734) = Foldl' arg6989586621680453370 arg6989586621680453371 arg6989586621680453372
  • data Foldr1Sym0 :: forall a6989586621680452735 t6989586621680452723. (~>) ((~>) a6989586621680452735 ((~>) a6989586621680452735 a6989586621680452735)) ((~>) (t6989586621680452723 a6989586621680452735) a6989586621680452735)
  • data Foldr1Sym1 (arg6989586621680453376 :: (~>) a6989586621680452735 ((~>) a6989586621680452735 a6989586621680452735)) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452735) a6989586621680452735
  • type Foldr1Sym2 (arg6989586621680453376 :: (~>) a6989586621680452735 ((~>) a6989586621680452735 a6989586621680452735)) (arg6989586621680453377 :: t6989586621680452723 a6989586621680452735) = Foldr1 arg6989586621680453376 arg6989586621680453377
  • data Foldl1Sym0 :: forall a6989586621680452736 t6989586621680452723. (~>) ((~>) a6989586621680452736 ((~>) a6989586621680452736 a6989586621680452736)) ((~>) (t6989586621680452723 a6989586621680452736) a6989586621680452736)
  • data Foldl1Sym1 (arg6989586621680453380 :: (~>) a6989586621680452736 ((~>) a6989586621680452736 a6989586621680452736)) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452736) a6989586621680452736
  • type Foldl1Sym2 (arg6989586621680453380 :: (~>) a6989586621680452736 ((~>) a6989586621680452736 a6989586621680452736)) (arg6989586621680453381 :: t6989586621680452723 a6989586621680452736) = Foldl1 arg6989586621680453380 arg6989586621680453381
  • data ToListSym0 :: forall a6989586621680452737 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452737) [a6989586621680452737]
  • type ToListSym1 (arg6989586621680453384 :: t6989586621680452723 a6989586621680452737) = ToList arg6989586621680453384
  • data NullSym0 :: forall a6989586621680452738 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452738) Bool
  • type NullSym1 (arg6989586621680453386 :: t6989586621680452723 a6989586621680452738) = Null arg6989586621680453386
  • data LengthSym0 :: forall a6989586621680452739 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452739) Nat
  • type LengthSym1 (arg6989586621680453388 :: t6989586621680452723 a6989586621680452739) = Length arg6989586621680453388
  • data ElemSym0 :: forall a6989586621680452740 t6989586621680452723. (~>) a6989586621680452740 ((~>) (t6989586621680452723 a6989586621680452740) Bool)
  • data ElemSym1 (arg6989586621680453390 :: a6989586621680452740) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452740) Bool
  • type ElemSym2 (arg6989586621680453390 :: a6989586621680452740) (arg6989586621680453391 :: t6989586621680452723 a6989586621680452740) = Elem arg6989586621680453390 arg6989586621680453391
  • data MaximumSym0 :: forall a6989586621680452741 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452741) a6989586621680452741
  • type MaximumSym1 (arg6989586621680453394 :: t6989586621680452723 a6989586621680452741) = Maximum arg6989586621680453394
  • data MinimumSym0 :: forall a6989586621680452742 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452742) a6989586621680452742
  • type MinimumSym1 (arg6989586621680453396 :: t6989586621680452723 a6989586621680452742) = Minimum arg6989586621680453396
  • data SumSym0 :: forall a6989586621680452743 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452743) a6989586621680452743
  • type SumSym1 (arg6989586621680453398 :: t6989586621680452723 a6989586621680452743) = Sum arg6989586621680453398
  • data ProductSym0 :: forall a6989586621680452744 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452744) a6989586621680452744
  • type ProductSym1 (arg6989586621680453400 :: t6989586621680452723 a6989586621680452744) = Product arg6989586621680453400
  • data FoldrMSym0 :: forall a6989586621680452684 b6989586621680452685 m6989586621680452683 t6989586621680452682. (~>) ((~>) a6989586621680452684 ((~>) b6989586621680452685 (m6989586621680452683 b6989586621680452685))) ((~>) b6989586621680452685 ((~>) (t6989586621680452682 a6989586621680452684) (m6989586621680452683 b6989586621680452685)))
  • data FoldrMSym1 (a6989586621680453324 :: (~>) a6989586621680452684 ((~>) b6989586621680452685 (m6989586621680452683 b6989586621680452685))) :: forall t6989586621680452682. (~>) b6989586621680452685 ((~>) (t6989586621680452682 a6989586621680452684) (m6989586621680452683 b6989586621680452685))
  • data FoldrMSym2 (a6989586621680453324 :: (~>) a6989586621680452684 ((~>) b6989586621680452685 (m6989586621680452683 b6989586621680452685))) (a6989586621680453325 :: b6989586621680452685) :: forall t6989586621680452682. (~>) (t6989586621680452682 a6989586621680452684) (m6989586621680452683 b6989586621680452685)
  • type FoldrMSym3 (a6989586621680453324 :: (~>) a6989586621680452684 ((~>) b6989586621680452685 (m6989586621680452683 b6989586621680452685))) (a6989586621680453325 :: b6989586621680452685) (a6989586621680453326 :: t6989586621680452682 a6989586621680452684) = FoldrM a6989586621680453324 a6989586621680453325 a6989586621680453326
  • data FoldlMSym0 :: forall a6989586621680452681 b6989586621680452680 m6989586621680452679 t6989586621680452678. (~>) ((~>) b6989586621680452680 ((~>) a6989586621680452681 (m6989586621680452679 b6989586621680452680))) ((~>) b6989586621680452680 ((~>) (t6989586621680452678 a6989586621680452681) (m6989586621680452679 b6989586621680452680)))
  • data FoldlMSym1 (a6989586621680453302 :: (~>) b6989586621680452680 ((~>) a6989586621680452681 (m6989586621680452679 b6989586621680452680))) :: forall t6989586621680452678. (~>) b6989586621680452680 ((~>) (t6989586621680452678 a6989586621680452681) (m6989586621680452679 b6989586621680452680))
  • data FoldlMSym2 (a6989586621680453302 :: (~>) b6989586621680452680 ((~>) a6989586621680452681 (m6989586621680452679 b6989586621680452680))) (a6989586621680453303 :: b6989586621680452680) :: forall t6989586621680452678. (~>) (t6989586621680452678 a6989586621680452681) (m6989586621680452679 b6989586621680452680)
  • type FoldlMSym3 (a6989586621680453302 :: (~>) b6989586621680452680 ((~>) a6989586621680452681 (m6989586621680452679 b6989586621680452680))) (a6989586621680453303 :: b6989586621680452680) (a6989586621680453304 :: t6989586621680452678 a6989586621680452681) = FoldlM a6989586621680453302 a6989586621680453303 a6989586621680453304
  • data Traverse_Sym0 :: forall a6989586621680452676 b6989586621680452677 f6989586621680452675 t6989586621680452674. (~>) ((~>) a6989586621680452676 (f6989586621680452675 b6989586621680452677)) ((~>) (t6989586621680452674 a6989586621680452676) (f6989586621680452675 ()))
  • data Traverse_Sym1 (a6989586621680453284 :: (~>) a6989586621680452676 (f6989586621680452675 b6989586621680452677)) :: forall t6989586621680452674. (~>) (t6989586621680452674 a6989586621680452676) (f6989586621680452675 ())
  • type Traverse_Sym2 (a6989586621680453284 :: (~>) a6989586621680452676 (f6989586621680452675 b6989586621680452677)) (a6989586621680453285 :: t6989586621680452674 a6989586621680452676) = Traverse_ a6989586621680453284 a6989586621680453285
  • data For_Sym0 :: forall a6989586621680452672 b6989586621680452673 f6989586621680452671 t6989586621680452670. (~>) (t6989586621680452670 a6989586621680452672) ((~>) ((~>) a6989586621680452672 (f6989586621680452671 b6989586621680452673)) (f6989586621680452671 ()))
  • data For_Sym1 (a6989586621680453296 :: t6989586621680452670 a6989586621680452672) :: forall b6989586621680452673 f6989586621680452671. (~>) ((~>) a6989586621680452672 (f6989586621680452671 b6989586621680452673)) (f6989586621680452671 ())
  • type For_Sym2 (a6989586621680453296 :: t6989586621680452670 a6989586621680452672) (a6989586621680453297 :: (~>) a6989586621680452672 (f6989586621680452671 b6989586621680452673)) = For_ a6989586621680453296 a6989586621680453297
  • data SequenceA_Sym0 :: forall a6989586621680452661 f6989586621680452660 t6989586621680452659. (~>) (t6989586621680452659 (f6989586621680452660 a6989586621680452661)) (f6989586621680452660 ())
  • type SequenceA_Sym1 (a6989586621680453263 :: t6989586621680452659 (f6989586621680452660 a6989586621680452661)) = SequenceA_ a6989586621680453263
  • data AsumSym0 :: forall a6989586621680452655 f6989586621680452654 t6989586621680452653. (~>) (t6989586621680452653 (f6989586621680452654 a6989586621680452655)) (f6989586621680452654 a6989586621680452655)
  • type AsumSym1 (a6989586621680453248 :: t6989586621680452653 (f6989586621680452654 a6989586621680452655)) = Asum a6989586621680453248
  • data MapM_Sym0 :: forall a6989586621680452668 b6989586621680452669 m6989586621680452667 t6989586621680452666. (~>) ((~>) a6989586621680452668 (m6989586621680452667 b6989586621680452669)) ((~>) (t6989586621680452666 a6989586621680452668) (m6989586621680452667 ()))
  • data MapM_Sym1 (a6989586621680453266 :: (~>) a6989586621680452668 (m6989586621680452667 b6989586621680452669)) :: forall t6989586621680452666. (~>) (t6989586621680452666 a6989586621680452668) (m6989586621680452667 ())
  • type MapM_Sym2 (a6989586621680453266 :: (~>) a6989586621680452668 (m6989586621680452667 b6989586621680452669)) (a6989586621680453267 :: t6989586621680452666 a6989586621680452668) = MapM_ a6989586621680453266 a6989586621680453267
  • data ForM_Sym0 :: forall a6989586621680452664 b6989586621680452665 m6989586621680452663 t6989586621680452662. (~>) (t6989586621680452662 a6989586621680452664) ((~>) ((~>) a6989586621680452664 (m6989586621680452663 b6989586621680452665)) (m6989586621680452663 ()))
  • data ForM_Sym1 (a6989586621680453278 :: t6989586621680452662 a6989586621680452664) :: forall b6989586621680452665 m6989586621680452663. (~>) ((~>) a6989586621680452664 (m6989586621680452663 b6989586621680452665)) (m6989586621680452663 ())
  • type ForM_Sym2 (a6989586621680453278 :: t6989586621680452662 a6989586621680452664) (a6989586621680453279 :: (~>) a6989586621680452664 (m6989586621680452663 b6989586621680452665)) = ForM_ a6989586621680453278 a6989586621680453279
  • data Sequence_Sym0 :: forall a6989586621680452658 m6989586621680452657 t6989586621680452656. (~>) (t6989586621680452656 (m6989586621680452657 a6989586621680452658)) (m6989586621680452657 ())
  • type Sequence_Sym1 (a6989586621680453258 :: t6989586621680452656 (m6989586621680452657 a6989586621680452658)) = Sequence_ a6989586621680453258
  • data MsumSym0 :: forall a6989586621680452652 m6989586621680452651 t6989586621680452650. (~>) (t6989586621680452650 (m6989586621680452651 a6989586621680452652)) (m6989586621680452651 a6989586621680452652)
  • type MsumSym1 (a6989586621680453253 :: t6989586621680452650 (m6989586621680452651 a6989586621680452652)) = Msum a6989586621680453253
  • data ConcatSym0 :: forall a6989586621680452649 t6989586621680452648. (~>) (t6989586621680452648 [a6989586621680452649]) [a6989586621680452649]
  • type ConcatSym1 (a6989586621680453234 :: t6989586621680452648 [a6989586621680452649]) = Concat a6989586621680453234
  • data ConcatMapSym0 :: forall a6989586621680452646 b6989586621680452647 t6989586621680452645. (~>) ((~>) a6989586621680452646 [b6989586621680452647]) ((~>) (t6989586621680452645 a6989586621680452646) [b6989586621680452647])
  • data ConcatMapSym1 (a6989586621680453218 :: (~>) a6989586621680452646 [b6989586621680452647]) :: forall t6989586621680452645. (~>) (t6989586621680452645 a6989586621680452646) [b6989586621680452647]
  • type ConcatMapSym2 (a6989586621680453218 :: (~>) a6989586621680452646 [b6989586621680452647]) (a6989586621680453219 :: t6989586621680452645 a6989586621680452646) = ConcatMap a6989586621680453218 a6989586621680453219
  • data AndSym0 :: forall t6989586621680452644. (~>) (t6989586621680452644 Bool) Bool
  • type AndSym1 (a6989586621680453209 :: t6989586621680452644 Bool) = And a6989586621680453209
  • data OrSym0 :: forall t6989586621680452643. (~>) (t6989586621680452643 Bool) Bool
  • type OrSym1 (a6989586621680453200 :: t6989586621680452643 Bool) = Or a6989586621680453200
  • data AnySym0 :: forall a6989586621680452642 t6989586621680452641. (~>) ((~>) a6989586621680452642 Bool) ((~>) (t6989586621680452641 a6989586621680452642) Bool)
  • data AnySym1 (a6989586621680453187 :: (~>) a6989586621680452642 Bool) :: forall t6989586621680452641. (~>) (t6989586621680452641 a6989586621680452642) Bool
  • type AnySym2 (a6989586621680453187 :: (~>) a6989586621680452642 Bool) (a6989586621680453188 :: t6989586621680452641 a6989586621680452642) = Any a6989586621680453187 a6989586621680453188
  • data AllSym0 :: forall a6989586621680452640 t6989586621680452639. (~>) ((~>) a6989586621680452640 Bool) ((~>) (t6989586621680452639 a6989586621680452640) Bool)
  • data AllSym1 (a6989586621680453174 :: (~>) a6989586621680452640 Bool) :: forall t6989586621680452639. (~>) (t6989586621680452639 a6989586621680452640) Bool
  • type AllSym2 (a6989586621680453174 :: (~>) a6989586621680452640 Bool) (a6989586621680453175 :: t6989586621680452639 a6989586621680452640) = All a6989586621680453174 a6989586621680453175
  • data MaximumBySym0 :: forall a6989586621680452638 t6989586621680452637. (~>) ((~>) a6989586621680452638 ((~>) a6989586621680452638 Ordering)) ((~>) (t6989586621680452637 a6989586621680452638) a6989586621680452638)
  • data MaximumBySym1 (a6989586621680453149 :: (~>) a6989586621680452638 ((~>) a6989586621680452638 Ordering)) :: forall t6989586621680452637. (~>) (t6989586621680452637 a6989586621680452638) a6989586621680452638
  • type MaximumBySym2 (a6989586621680453149 :: (~>) a6989586621680452638 ((~>) a6989586621680452638 Ordering)) (a6989586621680453150 :: t6989586621680452637 a6989586621680452638) = MaximumBy a6989586621680453149 a6989586621680453150
  • data MinimumBySym0 :: forall a6989586621680452636 t6989586621680452635. (~>) ((~>) a6989586621680452636 ((~>) a6989586621680452636 Ordering)) ((~>) (t6989586621680452635 a6989586621680452636) a6989586621680452636)
  • data MinimumBySym1 (a6989586621680453124 :: (~>) a6989586621680452636 ((~>) a6989586621680452636 Ordering)) :: forall t6989586621680452635. (~>) (t6989586621680452635 a6989586621680452636) a6989586621680452636
  • type MinimumBySym2 (a6989586621680453124 :: (~>) a6989586621680452636 ((~>) a6989586621680452636 Ordering)) (a6989586621680453125 :: t6989586621680452635 a6989586621680452636) = MinimumBy a6989586621680453124 a6989586621680453125
  • data NotElemSym0 :: forall a6989586621680452634 t6989586621680452633. (~>) a6989586621680452634 ((~>) (t6989586621680452633 a6989586621680452634) Bool)
  • data NotElemSym1 (a6989586621680453116 :: a6989586621680452634) :: forall t6989586621680452633. (~>) (t6989586621680452633 a6989586621680452634) Bool
  • type NotElemSym2 (a6989586621680453116 :: a6989586621680452634) (a6989586621680453117 :: t6989586621680452633 a6989586621680452634) = NotElem a6989586621680453116 a6989586621680453117
  • data FindSym0 :: forall a6989586621680452632 t6989586621680452631. (~>) ((~>) a6989586621680452632 Bool) ((~>) (t6989586621680452631 a6989586621680452632) (Maybe a6989586621680452632))
  • data FindSym1 (a6989586621680453089 :: (~>) a6989586621680452632 Bool) :: forall t6989586621680452631. (~>) (t6989586621680452631 a6989586621680452632) (Maybe a6989586621680452632)
  • type FindSym2 (a6989586621680453089 :: (~>) a6989586621680452632 Bool) (a6989586621680453090 :: t6989586621680452631 a6989586621680452632) = Find a6989586621680453089 a6989586621680453090

Documentation

class PFoldable (t :: Type -> Type) Source #

Associated Types

type Fold (arg :: t m) :: m Source #

type FoldMap (arg :: (~>) a m) (arg :: t a) :: m Source #

type Foldr (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b Source #

type Foldr' (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b Source #

type Foldl (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b Source #

type Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b Source #

type Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #

type Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #

type ToList (arg :: t a) :: [a] Source #

type Null (arg :: t a) :: Bool Source #

type Length (arg :: t a) :: Nat Source #

type Elem (arg :: a) (arg :: t a) :: Bool Source #

type Maximum (arg :: t a) :: a Source #

type Minimum (arg :: t a) :: a Source #

type Sum (arg :: t a) :: a Source #

type Product (arg :: t a) :: a Source #

Instances
PFoldable [] Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Maybe Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Min Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Max Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable First Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Last Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Option Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Identity Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable First Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Last Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Dual Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Sum Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Product Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable NonEmpty Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable (Either a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable ((,) a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable (Arg a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable (Const m :: Type -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

class SFoldable (t :: Type -> Type) where Source #

Minimal complete definition

Nothing

Methods

sFold :: forall m (t :: t m). SMonoid m => Sing t -> Sing (Apply FoldSym0 t :: m) Source #

sFoldMap :: forall m a (t :: (~>) a m) (t :: t a). SMonoid m => Sing t -> Sing t -> Sing (Apply (Apply FoldMapSym0 t) t :: m) Source #

sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) Source #

sFoldr' :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldr'Sym0 t) t) t :: b) Source #

sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) Source #

sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) Source #

sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a) Source #

sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a) Source #

sToList :: forall a (t :: t a). Sing t -> Sing (Apply ToListSym0 t :: [a]) Source #

sNull :: forall a (t :: t a). Sing t -> Sing (Apply NullSym0 t :: Bool) Source #

sLength :: forall a (t :: t a). Sing t -> Sing (Apply LengthSym0 t :: Nat) Source #

sElem :: forall a (t :: a) (t :: t a). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool) Source #

sMaximum :: forall a (t :: t a). SOrd a => Sing t -> Sing (Apply MaximumSym0 t :: a) Source #

sMinimum :: forall a (t :: t a). SOrd a => Sing t -> Sing (Apply MinimumSym0 t :: a) Source #

sSum :: forall a (t :: t a). SNum a => Sing t -> Sing (Apply SumSym0 t :: a) Source #

sProduct :: forall a (t :: t a). SNum a => Sing t -> Sing (Apply ProductSym0 t :: a) Source #

sFold :: forall m (t :: t m). ((Apply FoldSym0 t :: m) ~ Apply Fold_6989586621680453408Sym0 t, SMonoid m) => Sing t -> Sing (Apply FoldSym0 t :: m) Source #

sFoldMap :: forall m a (t :: (~>) a m) (t :: t a). ((Apply (Apply FoldMapSym0 t) t :: m) ~ Apply (Apply FoldMap_6989586621680453421Sym0 t) t, SMonoid m) => Sing t -> Sing t -> Sing (Apply (Apply FoldMapSym0 t) t :: m) Source #

sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). (Apply (Apply (Apply FoldrSym0 t) t) t :: b) ~ Apply (Apply (Apply Foldr_6989586621680453445Sym0 t) t) t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) Source #

sFoldr' :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). (Apply (Apply (Apply Foldr'Sym0 t) t) t :: b) ~ Apply (Apply (Apply Foldr'_6989586621680453475Sym0 t) t) t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldr'Sym0 t) t) t :: b) Source #

sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). (Apply (Apply (Apply FoldlSym0 t) t) t :: b) ~ Apply (Apply (Apply Foldl_6989586621680453500Sym0 t) t) t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) Source #

sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) ~ Apply (Apply (Apply Foldl'_6989586621680453530Sym0 t) t) t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) Source #

sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). (Apply (Apply Foldr1Sym0 t) t :: a) ~ Apply (Apply Foldr1_6989586621680453556Sym0 t) t => Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a) Source #

sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). (Apply (Apply Foldl1Sym0 t) t :: a) ~ Apply (Apply Foldl1_6989586621680453581Sym0 t) t => Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a) Source #

sToList :: forall a (t :: t a). (Apply ToListSym0 t :: [a]) ~ Apply ToList_6989586621680453591Sym0 t => Sing t -> Sing (Apply ToListSym0 t :: [a]) Source #

sNull :: forall a (t :: t a). (Apply NullSym0 t :: Bool) ~ Apply Null_6989586621680453612Sym0 t => Sing t -> Sing (Apply NullSym0 t :: Bool) Source #

sLength :: forall a (t :: t a). (Apply LengthSym0 t :: Nat) ~ Apply Length_6989586621680453634Sym0 t => Sing t -> Sing (Apply LengthSym0 t :: Nat) Source #

sElem :: forall a (t :: a) (t :: t a). ((Apply (Apply ElemSym0 t) t :: Bool) ~ Apply (Apply Elem_6989586621680453649Sym0 t) t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool) Source #

sMaximum :: forall a (t :: t a). ((Apply MaximumSym0 t :: a) ~ Apply Maximum_6989586621680453663Sym0 t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a) Source #

sMinimum :: forall a (t :: t a). ((Apply MinimumSym0 t :: a) ~ Apply Minimum_6989586621680453676Sym0 t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a) Source #

sSum :: forall a (t :: t a). ((Apply SumSym0 t :: a) ~ Apply Sum_6989586621680453689Sym0 t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a) Source #

sProduct :: forall a (t :: t a). ((Apply ProductSym0 t :: a) ~ Apply Product_6989586621680453702Sym0 t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a) Source #

Instances
SFoldable [] Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SFoldable Maybe Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SFoldable Min Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

SFoldable Max Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

SFoldable First Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

SFoldable Last Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

SFoldable Option Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

SFoldable Identity Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

SFoldable First Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SFoldable Last Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SFoldable Dual Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SFoldable Sum Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SFoldable Product Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SFoldable NonEmpty Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SFoldable (Either a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SFoldable ((,) a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SFoldable (Arg a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

SFoldable (Const m :: Type -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type family FoldrM (a :: (~>) a ((~>) b (m b))) (a :: b) (a :: t a) :: m b where ... Source #

Equations

FoldrM f z0 xs = Apply (Apply (Apply (Apply FoldlSym0 (Let6989586621680453333F'Sym3 f z0 xs)) ReturnSym0) xs) z0 

sFoldrM :: forall t m a b (t :: (~>) a ((~>) b (m b))) (t :: b) (t :: t a). (SFoldable t, SMonad m) => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrMSym0 t) t) t :: m b) Source #

type family FoldlM (a :: (~>) b ((~>) a (m b))) (a :: b) (a :: t a) :: m b where ... Source #

Equations

FoldlM f z0 xs = Apply (Apply (Apply (Apply FoldrSym0 (Let6989586621680453311F'Sym3 f z0 xs)) ReturnSym0) xs) z0 

sFoldlM :: forall t m b a (t :: (~>) b ((~>) a (m b))) (t :: b) (t :: t a). (SFoldable t, SMonad m) => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlMSym0 t) t) t :: m b) Source #

type family Traverse_ (a :: (~>) a (f b)) (a :: t a) :: f () where ... Source #

Equations

Traverse_ f a_6989586621680453288 = Apply (Apply (Apply FoldrSym0 (Apply (Apply (.@#@$) (*>@#@$)) f)) (Apply PureSym0 Tuple0Sym0)) a_6989586621680453288 

sTraverse_ :: forall t f a b (t :: (~>) a (f b)) (t :: t a). (SFoldable t, SApplicative f) => Sing t -> Sing t -> Sing (Apply (Apply Traverse_Sym0 t) t :: f ()) Source #

type family For_ (a :: t a) (a :: (~>) a (f b)) :: f () where ... Source #

Equations

For_ a_6989586621680453292 a_6989586621680453294 = Apply (Apply (Apply FlipSym0 Traverse_Sym0) a_6989586621680453292) a_6989586621680453294 

sFor_ :: forall t f a b (t :: t a) (t :: (~>) a (f b)). (SFoldable t, SApplicative f) => Sing t -> Sing t -> Sing (Apply (Apply For_Sym0 t) t :: f ()) Source #

type family SequenceA_ (a :: t (f a)) :: f () where ... Source #

Equations

SequenceA_ a_6989586621680453261 = Apply (Apply (Apply FoldrSym0 (*>@#@$)) (Apply PureSym0 Tuple0Sym0)) a_6989586621680453261 

sSequenceA_ :: forall t f a (t :: t (f a)). (SFoldable t, SApplicative f) => Sing t -> Sing (Apply SequenceA_Sym0 t :: f ()) Source #

type family Asum (a :: t (f a)) :: f a where ... Source #

Equations

Asum a_6989586621680453246 = Apply (Apply (Apply FoldrSym0 (<|>@#@$)) EmptySym0) a_6989586621680453246 

sAsum :: forall t f a (t :: t (f a)). (SFoldable t, SAlternative f) => Sing t -> Sing (Apply AsumSym0 t :: f a) Source #

type family MapM_ (a :: (~>) a (m b)) (a :: t a) :: m () where ... Source #

Equations

MapM_ f a_6989586621680453270 = Apply (Apply (Apply FoldrSym0 (Apply (Apply (.@#@$) (>>@#@$)) f)) (Apply ReturnSym0 Tuple0Sym0)) a_6989586621680453270 

sMapM_ :: forall t m a b (t :: (~>) a (m b)) (t :: t a). (SFoldable t, SMonad m) => Sing t -> Sing t -> Sing (Apply (Apply MapM_Sym0 t) t :: m ()) Source #

type family ForM_ (a :: t a) (a :: (~>) a (m b)) :: m () where ... Source #

Equations

ForM_ a_6989586621680453274 a_6989586621680453276 = Apply (Apply (Apply FlipSym0 MapM_Sym0) a_6989586621680453274) a_6989586621680453276 

sForM_ :: forall t m a b (t :: t a) (t :: (~>) a (m b)). (SFoldable t, SMonad m) => Sing t -> Sing t -> Sing (Apply (Apply ForM_Sym0 t) t :: m ()) Source #

type family Sequence_ (a :: t (m a)) :: m () where ... Source #

Equations

Sequence_ a_6989586621680453256 = Apply (Apply (Apply FoldrSym0 (>>@#@$)) (Apply ReturnSym0 Tuple0Sym0)) a_6989586621680453256 

sSequence_ :: forall t m a (t :: t (m a)). (SFoldable t, SMonad m) => Sing t -> Sing (Apply Sequence_Sym0 t :: m ()) Source #

type family Msum (a :: t (m a)) :: m a where ... Source #

Equations

Msum a_6989586621680453251 = Apply AsumSym0 a_6989586621680453251 

sMsum :: forall t m a (t :: t (m a)). (SFoldable t, SMonadPlus m) => Sing t -> Sing (Apply MsumSym0 t :: m a) Source #

type family Concat (a :: t [a]) :: [a] where ... Source #

Equations

Concat xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621680453237Sym0 xs)) '[]) xs 

sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a]) Source #

type family ConcatMap (a :: (~>) a [b]) (a :: t a) :: [b] where ... Source #

Equations

ConcatMap f xs = Apply (Apply (Apply FoldrSym0 (Apply (Apply Lambda_6989586621680453224Sym0 f) xs)) '[]) xs 

sConcatMap :: forall t a b (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) Source #

type family And (a :: t Bool) :: Bool where ... Source #

Equations

And x = Case_6989586621680453214 x (Let6989586621680453212Scrutinee_6989586621680452970Sym1 x) 

sAnd :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply AndSym0 t :: Bool) Source #

type family Or (a :: t Bool) :: Bool where ... Source #

Equations

Or x = Case_6989586621680453205 x (Let6989586621680453203Scrutinee_6989586621680452972Sym1 x) 

sOr :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply OrSym0 t :: Bool) Source #

type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #

Equations

Any p x = Case_6989586621680453196 p x (Let6989586621680453193Scrutinee_6989586621680452974Sym2 p x) 

sAny :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool) Source #

type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #

Equations

All p x = Case_6989586621680453183 p x (Let6989586621680453180Scrutinee_6989586621680452976Sym2 p x) 

sAll :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool) Source #

type family MaximumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ... Source #

Equations

MaximumBy cmp a_6989586621680453153 = Apply (Apply Foldl1Sym0 (Let6989586621680453157Max'Sym2 cmp a_6989586621680453153)) a_6989586621680453153 

sMaximumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a) Source #

type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ... Source #

Equations

MinimumBy cmp a_6989586621680453128 = Apply (Apply Foldl1Sym0 (Let6989586621680453132Min'Sym2 cmp a_6989586621680453128)) a_6989586621680453128 

sMinimumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a) Source #

type family NotElem (a :: a) (a :: t a) :: Bool where ... Source #

Equations

NotElem x a_6989586621680453120 = Apply (Apply (Apply (.@#@$) NotSym0) (Apply ElemSym0 x)) a_6989586621680453120 

sNotElem :: forall t a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool) Source #

type family Find (a :: (~>) a Bool) (a :: t a) :: Maybe a where ... Source #

Equations

Find p y = Case_6989586621680453112 p y (Let6989586621680453095Scrutinee_6989586621680452982Sym2 p y) 

sFind :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a) Source #

Defunctionalization symbols

data FoldSym0 :: forall m6989586621680452724 t6989586621680452723. (~>) (t6989586621680452723 m6989586621680452724) m6989586621680452724 Source #

Instances
(SFoldable t, SMonoid m) => SingI (FoldSym0 :: TyFun (t m) m -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FoldSym0 :: TyFun (t6989586621680452723 m6989586621680452724) m6989586621680452724 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldSym0 :: TyFun (t m) m -> Type) (arg6989586621680453346 :: t m) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldSym0 :: TyFun (t m) m -> Type) (arg6989586621680453346 :: t m) = Fold arg6989586621680453346

type FoldSym1 (arg6989586621680453346 :: t6989586621680452723 m6989586621680452724) = Fold arg6989586621680453346 Source #

data FoldMapSym0 :: forall a6989586621680452726 m6989586621680452725 t6989586621680452723. (~>) ((~>) a6989586621680452726 m6989586621680452725) ((~>) (t6989586621680452723 a6989586621680452726) m6989586621680452725) Source #

Instances
(SFoldable t, SMonoid m) => SingI (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FoldMapSym0 :: TyFun (a6989586621680452726 ~> m6989586621680452725) (t6989586621680452723 a6989586621680452726 ~> m6989586621680452725) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldMapSym0 :: TyFun (a6989586621680452726 ~> m6989586621680452725) (t6989586621680452723 a6989586621680452726 ~> m6989586621680452725) -> Type) (arg6989586621680453348 :: a6989586621680452726 ~> m6989586621680452725) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldMapSym0 :: TyFun (a6989586621680452726 ~> m6989586621680452725) (t6989586621680452723 a6989586621680452726 ~> m6989586621680452725) -> Type) (arg6989586621680453348 :: a6989586621680452726 ~> m6989586621680452725) = (FoldMapSym1 arg6989586621680453348 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452726) m6989586621680452725 -> Type)

data FoldMapSym1 (arg6989586621680453348 :: (~>) a6989586621680452726 m6989586621680452725) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452726) m6989586621680452725 Source #

Instances
(SFoldable t, SMonoid m, SingI d) => SingI (FoldMapSym1 d t :: TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FoldMapSym1 d t) Source #

SuppressUnusedWarnings (FoldMapSym1 arg6989586621680453348 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452726) m6989586621680452725 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldMapSym1 arg6989586621680453348 t :: TyFun (t a) m -> Type) (arg6989586621680453349 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldMapSym1 arg6989586621680453348 t :: TyFun (t a) m -> Type) (arg6989586621680453349 :: t a) = FoldMap arg6989586621680453348 arg6989586621680453349

type FoldMapSym2 (arg6989586621680453348 :: (~>) a6989586621680452726 m6989586621680452725) (arg6989586621680453349 :: t6989586621680452723 a6989586621680452726) = FoldMap arg6989586621680453348 arg6989586621680453349 Source #

data FoldrSym0 :: forall a6989586621680452727 b6989586621680452728 t6989586621680452723. (~>) ((~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) ((~>) b6989586621680452728 ((~>) (t6989586621680452723 a6989586621680452727) b6989586621680452728)) Source #

Instances
SFoldable t => SingI (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FoldrSym0 :: TyFun (a6989586621680452727 ~> (b6989586621680452728 ~> b6989586621680452728)) (b6989586621680452728 ~> (t6989586621680452723 a6989586621680452727 ~> b6989586621680452728)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym0 :: TyFun (a6989586621680452727 ~> (b6989586621680452728 ~> b6989586621680452728)) (b6989586621680452728 ~> (t6989586621680452723 a6989586621680452727 ~> b6989586621680452728)) -> Type) (arg6989586621680453352 :: a6989586621680452727 ~> (b6989586621680452728 ~> b6989586621680452728)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym0 :: TyFun (a6989586621680452727 ~> (b6989586621680452728 ~> b6989586621680452728)) (b6989586621680452728 ~> (t6989586621680452723 a6989586621680452727 ~> b6989586621680452728)) -> Type) (arg6989586621680453352 :: a6989586621680452727 ~> (b6989586621680452728 ~> b6989586621680452728)) = (FoldrSym1 arg6989586621680453352 t6989586621680452723 :: TyFun b6989586621680452728 (t6989586621680452723 a6989586621680452727 ~> b6989586621680452728) -> Type)

data FoldrSym1 (arg6989586621680453352 :: (~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) :: forall t6989586621680452723. (~>) b6989586621680452728 ((~>) (t6989586621680452723 a6989586621680452727) b6989586621680452728) Source #

Instances
(SFoldable t, SingI d) => SingI (FoldrSym1 d t :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FoldrSym1 d t) Source #

SuppressUnusedWarnings (FoldrSym1 arg6989586621680453352 t6989586621680452723 :: TyFun b6989586621680452728 (t6989586621680452723 a6989586621680452727 ~> b6989586621680452728) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym1 arg6989586621680453352 t6989586621680452723 :: TyFun b6989586621680452728 (t6989586621680452723 a6989586621680452727 ~> b6989586621680452728) -> Type) (arg6989586621680453353 :: b6989586621680452728) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym1 arg6989586621680453352 t6989586621680452723 :: TyFun b6989586621680452728 (t6989586621680452723 a6989586621680452727 ~> b6989586621680452728) -> Type) (arg6989586621680453353 :: b6989586621680452728) = (FoldrSym2 arg6989586621680453352 arg6989586621680453353 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452727) b6989586621680452728 -> Type)

data FoldrSym2 (arg6989586621680453352 :: (~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) (arg6989586621680453353 :: b6989586621680452728) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452727) b6989586621680452728 Source #

Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldrSym2 d1 d2 t :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FoldrSym2 d1 d2 t) Source #

SuppressUnusedWarnings (FoldrSym2 arg6989586621680453353 arg6989586621680453352 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452727) b6989586621680452728 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym2 arg6989586621680453353 arg6989586621680453352 t :: TyFun (t a) b -> Type) (arg6989586621680453354 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym2 arg6989586621680453353 arg6989586621680453352 t :: TyFun (t a) b -> Type) (arg6989586621680453354 :: t a) = Foldr arg6989586621680453353 arg6989586621680453352 arg6989586621680453354

type FoldrSym3 (arg6989586621680453352 :: (~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) (arg6989586621680453353 :: b6989586621680452728) (arg6989586621680453354 :: t6989586621680452723 a6989586621680452727) = Foldr arg6989586621680453352 arg6989586621680453353 arg6989586621680453354 Source #

data Foldr'Sym0 :: forall a6989586621680452729 b6989586621680452730 t6989586621680452723. (~>) ((~>) a6989586621680452729 ((~>) b6989586621680452730 b6989586621680452730)) ((~>) b6989586621680452730 ((~>) (t6989586621680452723 a6989586621680452729) b6989586621680452730)) Source #

Instances
SFoldable t => SingI (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Foldr'Sym0 :: TyFun (a6989586621680452729 ~> (b6989586621680452730 ~> b6989586621680452730)) (b6989586621680452730 ~> (t6989586621680452723 a6989586621680452729 ~> b6989586621680452730)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr'Sym0 :: TyFun (a6989586621680452729 ~> (b6989586621680452730 ~> b6989586621680452730)) (b6989586621680452730 ~> (t6989586621680452723 a6989586621680452729 ~> b6989586621680452730)) -> Type) (arg6989586621680453358 :: a6989586621680452729 ~> (b6989586621680452730 ~> b6989586621680452730)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr'Sym0 :: TyFun (a6989586621680452729 ~> (b6989586621680452730 ~> b6989586621680452730)) (b6989586621680452730 ~> (t6989586621680452723 a6989586621680452729 ~> b6989586621680452730)) -> Type) (arg6989586621680453358 :: a6989586621680452729 ~> (b6989586621680452730 ~> b6989586621680452730)) = (Foldr'Sym1 arg6989586621680453358 t6989586621680452723 :: TyFun b6989586621680452730 (t6989586621680452723 a6989586621680452729 ~> b6989586621680452730) -> Type)

data Foldr'Sym1 (arg6989586621680453358 :: (~>) a6989586621680452729 ((~>) b6989586621680452730 b6989586621680452730)) :: forall t6989586621680452723. (~>) b6989586621680452730 ((~>) (t6989586621680452723 a6989586621680452729) b6989586621680452730) Source #

Instances
(SFoldable t, SingI d) => SingI (Foldr'Sym1 d t :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (Foldr'Sym1 d t) Source #

SuppressUnusedWarnings (Foldr'Sym1 arg6989586621680453358 t6989586621680452723 :: TyFun b6989586621680452730 (t6989586621680452723 a6989586621680452729 ~> b6989586621680452730) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr'Sym1 arg6989586621680453358 t6989586621680452723 :: TyFun b6989586621680452730 (t6989586621680452723 a6989586621680452729 ~> b6989586621680452730) -> Type) (arg6989586621680453359 :: b6989586621680452730) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr'Sym1 arg6989586621680453358 t6989586621680452723 :: TyFun b6989586621680452730 (t6989586621680452723 a6989586621680452729 ~> b6989586621680452730) -> Type) (arg6989586621680453359 :: b6989586621680452730) = (Foldr'Sym2 arg6989586621680453358 arg6989586621680453359 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452729) b6989586621680452730 -> Type)

data Foldr'Sym2 (arg6989586621680453358 :: (~>) a6989586621680452729 ((~>) b6989586621680452730 b6989586621680452730)) (arg6989586621680453359 :: b6989586621680452730) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452729) b6989586621680452730 Source #

Instances
(SFoldable t, SingI d1, SingI d2) => SingI (Foldr'Sym2 d1 d2 t :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (Foldr'Sym2 d1 d2 t) Source #

SuppressUnusedWarnings (Foldr'Sym2 arg6989586621680453359 arg6989586621680453358 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452729) b6989586621680452730 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr'Sym2 arg6989586621680453359 arg6989586621680453358 t :: TyFun (t a) b -> Type) (arg6989586621680453360 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr'Sym2 arg6989586621680453359 arg6989586621680453358 t :: TyFun (t a) b -> Type) (arg6989586621680453360 :: t a) = Foldr' arg6989586621680453359 arg6989586621680453358 arg6989586621680453360

type Foldr'Sym3 (arg6989586621680453358 :: (~>) a6989586621680452729 ((~>) b6989586621680452730 b6989586621680452730)) (arg6989586621680453359 :: b6989586621680452730) (arg6989586621680453360 :: t6989586621680452723 a6989586621680452729) = Foldr' arg6989586621680453358 arg6989586621680453359 arg6989586621680453360 Source #

data FoldlSym0 :: forall a6989586621680452732 b6989586621680452731 t6989586621680452723. (~>) ((~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) ((~>) b6989586621680452731 ((~>) (t6989586621680452723 a6989586621680452732) b6989586621680452731)) Source #

Instances
SFoldable t => SingI (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FoldlSym0 :: TyFun (b6989586621680452731 ~> (a6989586621680452732 ~> b6989586621680452731)) (b6989586621680452731 ~> (t6989586621680452723 a6989586621680452732 ~> b6989586621680452731)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym0 :: TyFun (b6989586621680452731 ~> (a6989586621680452732 ~> b6989586621680452731)) (b6989586621680452731 ~> (t6989586621680452723 a6989586621680452732 ~> b6989586621680452731)) -> Type) (arg6989586621680453364 :: b6989586621680452731 ~> (a6989586621680452732 ~> b6989586621680452731)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym0 :: TyFun (b6989586621680452731 ~> (a6989586621680452732 ~> b6989586621680452731)) (b6989586621680452731 ~> (t6989586621680452723 a6989586621680452732 ~> b6989586621680452731)) -> Type) (arg6989586621680453364 :: b6989586621680452731 ~> (a6989586621680452732 ~> b6989586621680452731)) = (FoldlSym1 arg6989586621680453364 t6989586621680452723 :: TyFun b6989586621680452731 (t6989586621680452723 a6989586621680452732 ~> b6989586621680452731) -> Type)

data FoldlSym1 (arg6989586621680453364 :: (~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) :: forall t6989586621680452723. (~>) b6989586621680452731 ((~>) (t6989586621680452723 a6989586621680452732) b6989586621680452731) Source #

Instances
(SFoldable t, SingI d) => SingI (FoldlSym1 d t :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FoldlSym1 d t) Source #

SuppressUnusedWarnings (FoldlSym1 arg6989586621680453364 t6989586621680452723 :: TyFun b6989586621680452731 (t6989586621680452723 a6989586621680452732 ~> b6989586621680452731) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym1 arg6989586621680453364 t6989586621680452723 :: TyFun b6989586621680452731 (t6989586621680452723 a6989586621680452732 ~> b6989586621680452731) -> Type) (arg6989586621680453365 :: b6989586621680452731) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym1 arg6989586621680453364 t6989586621680452723 :: TyFun b6989586621680452731 (t6989586621680452723 a6989586621680452732 ~> b6989586621680452731) -> Type) (arg6989586621680453365 :: b6989586621680452731) = (FoldlSym2 arg6989586621680453364 arg6989586621680453365 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452732) b6989586621680452731 -> Type)

data FoldlSym2 (arg6989586621680453364 :: (~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) (arg6989586621680453365 :: b6989586621680452731) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452732) b6989586621680452731 Source #

Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldlSym2 d1 d2 t :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FoldlSym2 d1 d2 t) Source #

SuppressUnusedWarnings (FoldlSym2 arg6989586621680453365 arg6989586621680453364 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452732) b6989586621680452731 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym2 arg6989586621680453365 arg6989586621680453364 t :: TyFun (t a) b -> Type) (arg6989586621680453366 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym2 arg6989586621680453365 arg6989586621680453364 t :: TyFun (t a) b -> Type) (arg6989586621680453366 :: t a) = Foldl arg6989586621680453365 arg6989586621680453364 arg6989586621680453366

type FoldlSym3 (arg6989586621680453364 :: (~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) (arg6989586621680453365 :: b6989586621680452731) (arg6989586621680453366 :: t6989586621680452723 a6989586621680452732) = Foldl arg6989586621680453364 arg6989586621680453365 arg6989586621680453366 Source #

data Foldl'Sym0 :: forall a6989586621680452734 b6989586621680452733 t6989586621680452723. (~>) ((~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) ((~>) b6989586621680452733 ((~>) (t6989586621680452723 a6989586621680452734) b6989586621680452733)) Source #

Instances
SFoldable t => SingI (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Foldl'Sym0 :: TyFun (b6989586621680452733 ~> (a6989586621680452734 ~> b6989586621680452733)) (b6989586621680452733 ~> (t6989586621680452723 a6989586621680452734 ~> b6989586621680452733)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym0 :: TyFun (b6989586621680452733 ~> (a6989586621680452734 ~> b6989586621680452733)) (b6989586621680452733 ~> (t6989586621680452723 a6989586621680452734 ~> b6989586621680452733)) -> Type) (arg6989586621680453370 :: b6989586621680452733 ~> (a6989586621680452734 ~> b6989586621680452733)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym0 :: TyFun (b6989586621680452733 ~> (a6989586621680452734 ~> b6989586621680452733)) (b6989586621680452733 ~> (t6989586621680452723 a6989586621680452734 ~> b6989586621680452733)) -> Type) (arg6989586621680453370 :: b6989586621680452733 ~> (a6989586621680452734 ~> b6989586621680452733)) = (Foldl'Sym1 arg6989586621680453370 t6989586621680452723 :: TyFun b6989586621680452733 (t6989586621680452723 a6989586621680452734 ~> b6989586621680452733) -> Type)

data Foldl'Sym1 (arg6989586621680453370 :: (~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) :: forall t6989586621680452723. (~>) b6989586621680452733 ((~>) (t6989586621680452723 a6989586621680452734) b6989586621680452733) Source #

Instances
(SFoldable t, SingI d) => SingI (Foldl'Sym1 d t :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (Foldl'Sym1 d t) Source #

SuppressUnusedWarnings (Foldl'Sym1 arg6989586621680453370 t6989586621680452723 :: TyFun b6989586621680452733 (t6989586621680452723 a6989586621680452734 ~> b6989586621680452733) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym1 arg6989586621680453370 t6989586621680452723 :: TyFun b6989586621680452733 (t6989586621680452723 a6989586621680452734 ~> b6989586621680452733) -> Type) (arg6989586621680453371 :: b6989586621680452733) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym1 arg6989586621680453370 t6989586621680452723 :: TyFun b6989586621680452733 (t6989586621680452723 a6989586621680452734 ~> b6989586621680452733) -> Type) (arg6989586621680453371 :: b6989586621680452733) = (Foldl'Sym2 arg6989586621680453370 arg6989586621680453371 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452734) b6989586621680452733 -> Type)

data Foldl'Sym2 (arg6989586621680453370 :: (~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) (arg6989586621680453371 :: b6989586621680452733) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452734) b6989586621680452733 Source #

Instances
(SFoldable t, SingI d1, SingI d2) => SingI (Foldl'Sym2 d1 d2 t :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (Foldl'Sym2 d1 d2 t) Source #

SuppressUnusedWarnings (Foldl'Sym2 arg6989586621680453371 arg6989586621680453370 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452734) b6989586621680452733 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym2 arg6989586621680453371 arg6989586621680453370 t :: TyFun (t a) b -> Type) (arg6989586621680453372 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym2 arg6989586621680453371 arg6989586621680453370 t :: TyFun (t a) b -> Type) (arg6989586621680453372 :: t a) = Foldl' arg6989586621680453371 arg6989586621680453370 arg6989586621680453372

type Foldl'Sym3 (arg6989586621680453370 :: (~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) (arg6989586621680453371 :: b6989586621680452733) (arg6989586621680453372 :: t6989586621680452723 a6989586621680452734) = Foldl' arg6989586621680453370 arg6989586621680453371 arg6989586621680453372 Source #

data Foldr1Sym0 :: forall a6989586621680452735 t6989586621680452723. (~>) ((~>) a6989586621680452735 ((~>) a6989586621680452735 a6989586621680452735)) ((~>) (t6989586621680452723 a6989586621680452735) a6989586621680452735) Source #

Instances
SFoldable t => SingI (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Foldr1Sym0 :: TyFun (a6989586621680452735 ~> (a6989586621680452735 ~> a6989586621680452735)) (t6989586621680452723 a6989586621680452735 ~> a6989586621680452735) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr1Sym0 :: TyFun (a6989586621680452735 ~> (a6989586621680452735 ~> a6989586621680452735)) (t6989586621680452723 a6989586621680452735 ~> a6989586621680452735) -> Type) (arg6989586621680453376 :: a6989586621680452735 ~> (a6989586621680452735 ~> a6989586621680452735)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr1Sym0 :: TyFun (a6989586621680452735 ~> (a6989586621680452735 ~> a6989586621680452735)) (t6989586621680452723 a6989586621680452735 ~> a6989586621680452735) -> Type) (arg6989586621680453376 :: a6989586621680452735 ~> (a6989586621680452735 ~> a6989586621680452735)) = (Foldr1Sym1 arg6989586621680453376 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452735) a6989586621680452735 -> Type)

data Foldr1Sym1 (arg6989586621680453376 :: (~>) a6989586621680452735 ((~>) a6989586621680452735 a6989586621680452735)) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452735) a6989586621680452735 Source #

Instances
(SFoldable t, SingI d) => SingI (Foldr1Sym1 d t :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (Foldr1Sym1 d t) Source #

SuppressUnusedWarnings (Foldr1Sym1 arg6989586621680453376 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452735) a6989586621680452735 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr1Sym1 arg6989586621680453376 t :: TyFun (t a) a -> Type) (arg6989586621680453377 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr1Sym1 arg6989586621680453376 t :: TyFun (t a) a -> Type) (arg6989586621680453377 :: t a) = Foldr1 arg6989586621680453376 arg6989586621680453377

type Foldr1Sym2 (arg6989586621680453376 :: (~>) a6989586621680452735 ((~>) a6989586621680452735 a6989586621680452735)) (arg6989586621680453377 :: t6989586621680452723 a6989586621680452735) = Foldr1 arg6989586621680453376 arg6989586621680453377 Source #

data Foldl1Sym0 :: forall a6989586621680452736 t6989586621680452723. (~>) ((~>) a6989586621680452736 ((~>) a6989586621680452736 a6989586621680452736)) ((~>) (t6989586621680452723 a6989586621680452736) a6989586621680452736) Source #

Instances
SFoldable t => SingI (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (a6989586621680452736 ~> (a6989586621680452736 ~> a6989586621680452736)) (t6989586621680452723 a6989586621680452736 ~> a6989586621680452736) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl1Sym0 :: TyFun (a6989586621680452736 ~> (a6989586621680452736 ~> a6989586621680452736)) (t6989586621680452723 a6989586621680452736 ~> a6989586621680452736) -> Type) (arg6989586621680453380 :: a6989586621680452736 ~> (a6989586621680452736 ~> a6989586621680452736)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl1Sym0 :: TyFun (a6989586621680452736 ~> (a6989586621680452736 ~> a6989586621680452736)) (t6989586621680452723 a6989586621680452736 ~> a6989586621680452736) -> Type) (arg6989586621680453380 :: a6989586621680452736 ~> (a6989586621680452736 ~> a6989586621680452736)) = (Foldl1Sym1 arg6989586621680453380 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452736) a6989586621680452736 -> Type)

data Foldl1Sym1 (arg6989586621680453380 :: (~>) a6989586621680452736 ((~>) a6989586621680452736 a6989586621680452736)) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452736) a6989586621680452736 Source #

Instances
(SFoldable t, SingI d) => SingI (Foldl1Sym1 d t :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (Foldl1Sym1 d t) Source #

SuppressUnusedWarnings (Foldl1Sym1 arg6989586621680453380 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452736) a6989586621680452736 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl1Sym1 arg6989586621680453380 t :: TyFun (t a) a -> Type) (arg6989586621680453381 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl1Sym1 arg6989586621680453380 t :: TyFun (t a) a -> Type) (arg6989586621680453381 :: t a) = Foldl1 arg6989586621680453380 arg6989586621680453381

type Foldl1Sym2 (arg6989586621680453380 :: (~>) a6989586621680452736 ((~>) a6989586621680452736 a6989586621680452736)) (arg6989586621680453381 :: t6989586621680452723 a6989586621680452736) = Foldl1 arg6989586621680453380 arg6989586621680453381 Source #

data ToListSym0 :: forall a6989586621680452737 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452737) [a6989586621680452737] Source #

Instances
SFoldable t => SingI (ToListSym0 :: TyFun (t a) [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ToListSym0 :: TyFun (t6989586621680452723 a6989586621680452737) [a6989586621680452737] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ToListSym0 :: TyFun (t a) [a] -> Type) (arg6989586621680453384 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ToListSym0 :: TyFun (t a) [a] -> Type) (arg6989586621680453384 :: t a) = ToList arg6989586621680453384

type ToListSym1 (arg6989586621680453384 :: t6989586621680452723 a6989586621680452737) = ToList arg6989586621680453384 Source #

data NullSym0 :: forall a6989586621680452738 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452738) Bool Source #

Instances
SFoldable t => SingI (NullSym0 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (NullSym0 :: TyFun (t6989586621680452723 a6989586621680452738) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680453386 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680453386 :: t a) = Null arg6989586621680453386

type NullSym1 (arg6989586621680453386 :: t6989586621680452723 a6989586621680452738) = Null arg6989586621680453386 Source #

data LengthSym0 :: forall a6989586621680452739 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452739) Nat Source #

Instances
SFoldable t => SingI (LengthSym0 :: TyFun (t a) Nat -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (LengthSym0 :: TyFun (t6989586621680452723 a6989586621680452739) Nat -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (LengthSym0 :: TyFun (t a) Nat -> Type) (arg6989586621680453388 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (LengthSym0 :: TyFun (t a) Nat -> Type) (arg6989586621680453388 :: t a) = Length arg6989586621680453388

type LengthSym1 (arg6989586621680453388 :: t6989586621680452723 a6989586621680452739) = Length arg6989586621680453388 Source #

data ElemSym0 :: forall a6989586621680452740 t6989586621680452723. (~>) a6989586621680452740 ((~>) (t6989586621680452723 a6989586621680452740) Bool) Source #

Instances
(SFoldable t, SEq a) => SingI (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621680452740 (t6989586621680452723 a6989586621680452740 ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym0 :: TyFun a6989586621680452740 (t6989586621680452723 a6989586621680452740 ~> Bool) -> Type) (arg6989586621680453390 :: a6989586621680452740) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym0 :: TyFun a6989586621680452740 (t6989586621680452723 a6989586621680452740 ~> Bool) -> Type) (arg6989586621680453390 :: a6989586621680452740) = (ElemSym1 arg6989586621680453390 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452740) Bool -> Type)

data ElemSym1 (arg6989586621680453390 :: a6989586621680452740) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452740) Bool Source #

Instances
(SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d t :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (ElemSym1 d t) Source #

SuppressUnusedWarnings (ElemSym1 arg6989586621680453390 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452740) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym1 arg6989586621680453390 t :: TyFun (t a) Bool -> Type) (arg6989586621680453391 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym1 arg6989586621680453390 t :: TyFun (t a) Bool -> Type) (arg6989586621680453391 :: t a) = Elem arg6989586621680453390 arg6989586621680453391

type ElemSym2 (arg6989586621680453390 :: a6989586621680452740) (arg6989586621680453391 :: t6989586621680452723 a6989586621680452740) = Elem arg6989586621680453390 arg6989586621680453391 Source #

data MaximumSym0 :: forall a6989586621680452741 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452741) a6989586621680452741 Source #

Instances
(SFoldable t, SOrd a) => SingI (MaximumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (MaximumSym0 :: TyFun (t6989586621680452723 a6989586621680452741) a6989586621680452741 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (arg6989586621680453394 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (arg6989586621680453394 :: t a) = Maximum arg6989586621680453394

type MaximumSym1 (arg6989586621680453394 :: t6989586621680452723 a6989586621680452741) = Maximum arg6989586621680453394 Source #

data MinimumSym0 :: forall a6989586621680452742 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452742) a6989586621680452742 Source #

Instances
(SFoldable t, SOrd a) => SingI (MinimumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (MinimumSym0 :: TyFun (t6989586621680452723 a6989586621680452742) a6989586621680452742 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (arg6989586621680453396 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (arg6989586621680453396 :: t a) = Minimum arg6989586621680453396

type MinimumSym1 (arg6989586621680453396 :: t6989586621680452723 a6989586621680452742) = Minimum arg6989586621680453396 Source #

data SumSym0 :: forall a6989586621680452743 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452743) a6989586621680452743 Source #

Instances
(SFoldable t, SNum a) => SingI (SumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (SumSym0 :: TyFun (t6989586621680452723 a6989586621680452743) a6989586621680452743 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (SumSym0 :: TyFun (t a) a -> Type) (arg6989586621680453398 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (SumSym0 :: TyFun (t a) a -> Type) (arg6989586621680453398 :: t a) = Sum arg6989586621680453398

type SumSym1 (arg6989586621680453398 :: t6989586621680452723 a6989586621680452743) = Sum arg6989586621680453398 Source #

data ProductSym0 :: forall a6989586621680452744 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452744) a6989586621680452744 Source #

Instances
(SFoldable t, SNum a) => SingI (ProductSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ProductSym0 :: TyFun (t6989586621680452723 a6989586621680452744) a6989586621680452744 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ProductSym0 :: TyFun (t a) a -> Type) (arg6989586621680453400 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ProductSym0 :: TyFun (t a) a -> Type) (arg6989586621680453400 :: t a) = Product arg6989586621680453400

type ProductSym1 (arg6989586621680453400 :: t6989586621680452723 a6989586621680452744) = Product arg6989586621680453400 Source #

data FoldrMSym0 :: forall a6989586621680452684 b6989586621680452685 m6989586621680452683 t6989586621680452682. (~>) ((~>) a6989586621680452684 ((~>) b6989586621680452685 (m6989586621680452683 b6989586621680452685))) ((~>) b6989586621680452685 ((~>) (t6989586621680452682 a6989586621680452684) (m6989586621680452683 b6989586621680452685))) Source #

Instances
(SFoldable t, SMonad m) => SingI (FoldrMSym0 :: TyFun (a ~> (b ~> m b)) (b ~> (t a ~> m b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FoldrMSym0 :: TyFun (a6989586621680452684 ~> (b6989586621680452685 ~> m6989586621680452683 b6989586621680452685)) (b6989586621680452685 ~> (t6989586621680452682 a6989586621680452684 ~> m6989586621680452683 b6989586621680452685)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrMSym0 :: TyFun (a6989586621680452684 ~> (b6989586621680452685 ~> m6989586621680452683 b6989586621680452685)) (b6989586621680452685 ~> (t6989586621680452682 a6989586621680452684 ~> m6989586621680452683 b6989586621680452685)) -> Type) (a6989586621680453324 :: a6989586621680452684 ~> (b6989586621680452685 ~> m6989586621680452683 b6989586621680452685)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrMSym0 :: TyFun (a6989586621680452684 ~> (b6989586621680452685 ~> m6989586621680452683 b6989586621680452685)) (b6989586621680452685 ~> (t6989586621680452682 a6989586621680452684 ~> m6989586621680452683 b6989586621680452685)) -> Type) (a6989586621680453324 :: a6989586621680452684 ~> (b6989586621680452685 ~> m6989586621680452683 b6989586621680452685)) = (FoldrMSym1 a6989586621680453324 t6989586621680452682 :: TyFun b6989586621680452685 (t6989586621680452682 a6989586621680452684 ~> m6989586621680452683 b6989586621680452685) -> Type)

data FoldrMSym1 (a6989586621680453324 :: (~>) a6989586621680452684 ((~>) b6989586621680452685 (m6989586621680452683 b6989586621680452685))) :: forall t6989586621680452682. (~>) b6989586621680452685 ((~>) (t6989586621680452682 a6989586621680452684) (m6989586621680452683 b6989586621680452685)) Source #

Instances
(SFoldable t, SMonad m, SingI d) => SingI (FoldrMSym1 d t :: TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FoldrMSym1 d t) Source #

SuppressUnusedWarnings (FoldrMSym1 a6989586621680453324 t6989586621680452682 :: TyFun b6989586621680452685 (t6989586621680452682 a6989586621680452684 ~> m6989586621680452683 b6989586621680452685) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrMSym1 a6989586621680453324 t6989586621680452682 :: TyFun b6989586621680452685 (t6989586621680452682 a6989586621680452684 ~> m6989586621680452683 b6989586621680452685) -> Type) (a6989586621680453325 :: b6989586621680452685) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrMSym1 a6989586621680453324 t6989586621680452682 :: TyFun b6989586621680452685 (t6989586621680452682 a6989586621680452684 ~> m6989586621680452683 b6989586621680452685) -> Type) (a6989586621680453325 :: b6989586621680452685) = (FoldrMSym2 a6989586621680453324 a6989586621680453325 t6989586621680452682 :: TyFun (t6989586621680452682 a6989586621680452684) (m6989586621680452683 b6989586621680452685) -> Type)

data FoldrMSym2 (a6989586621680453324 :: (~>) a6989586621680452684 ((~>) b6989586621680452685 (m6989586621680452683 b6989586621680452685))) (a6989586621680453325 :: b6989586621680452685) :: forall t6989586621680452682. (~>) (t6989586621680452682 a6989586621680452684) (m6989586621680452683 b6989586621680452685) Source #

Instances
(SFoldable t, SMonad m, SingI d1, SingI d2) => SingI (FoldrMSym2 d1 d2 t :: TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FoldrMSym2 d1 d2 t) Source #

SuppressUnusedWarnings (FoldrMSym2 a6989586621680453325 a6989586621680453324 t6989586621680452682 :: TyFun (t6989586621680452682 a6989586621680452684) (m6989586621680452683 b6989586621680452685) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrMSym2 a6989586621680453325 a6989586621680453324 t :: TyFun (t a) (m b) -> Type) (a6989586621680453326 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrMSym2 a6989586621680453325 a6989586621680453324 t :: TyFun (t a) (m b) -> Type) (a6989586621680453326 :: t a) = FoldrM a6989586621680453325 a6989586621680453324 a6989586621680453326

type FoldrMSym3 (a6989586621680453324 :: (~>) a6989586621680452684 ((~>) b6989586621680452685 (m6989586621680452683 b6989586621680452685))) (a6989586621680453325 :: b6989586621680452685) (a6989586621680453326 :: t6989586621680452682 a6989586621680452684) = FoldrM a6989586621680453324 a6989586621680453325 a6989586621680453326 Source #

data FoldlMSym0 :: forall a6989586621680452681 b6989586621680452680 m6989586621680452679 t6989586621680452678. (~>) ((~>) b6989586621680452680 ((~>) a6989586621680452681 (m6989586621680452679 b6989586621680452680))) ((~>) b6989586621680452680 ((~>) (t6989586621680452678 a6989586621680452681) (m6989586621680452679 b6989586621680452680))) Source #

Instances
(SFoldable t, SMonad m) => SingI (FoldlMSym0 :: TyFun (b ~> (a ~> m b)) (b ~> (t a ~> m b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FoldlMSym0 :: TyFun (b6989586621680452680 ~> (a6989586621680452681 ~> m6989586621680452679 b6989586621680452680)) (b6989586621680452680 ~> (t6989586621680452678 a6989586621680452681 ~> m6989586621680452679 b6989586621680452680)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlMSym0 :: TyFun (b6989586621680452680 ~> (a6989586621680452681 ~> m6989586621680452679 b6989586621680452680)) (b6989586621680452680 ~> (t6989586621680452678 a6989586621680452681 ~> m6989586621680452679 b6989586621680452680)) -> Type) (a6989586621680453302 :: b6989586621680452680 ~> (a6989586621680452681 ~> m6989586621680452679 b6989586621680452680)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlMSym0 :: TyFun (b6989586621680452680 ~> (a6989586621680452681 ~> m6989586621680452679 b6989586621680452680)) (b6989586621680452680 ~> (t6989586621680452678 a6989586621680452681 ~> m6989586621680452679 b6989586621680452680)) -> Type) (a6989586621680453302 :: b6989586621680452680 ~> (a6989586621680452681 ~> m6989586621680452679 b6989586621680452680)) = (FoldlMSym1 a6989586621680453302 t6989586621680452678 :: TyFun b6989586621680452680 (t6989586621680452678 a6989586621680452681 ~> m6989586621680452679 b6989586621680452680) -> Type)

data FoldlMSym1 (a6989586621680453302 :: (~>) b6989586621680452680 ((~>) a6989586621680452681 (m6989586621680452679 b6989586621680452680))) :: forall t6989586621680452678. (~>) b6989586621680452680 ((~>) (t6989586621680452678 a6989586621680452681) (m6989586621680452679 b6989586621680452680)) Source #

Instances
(SFoldable t, SMonad m, SingI d) => SingI (FoldlMSym1 d t :: TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FoldlMSym1 d t) Source #

SuppressUnusedWarnings (FoldlMSym1 a6989586621680453302 t6989586621680452678 :: TyFun b6989586621680452680 (t6989586621680452678 a6989586621680452681 ~> m6989586621680452679 b6989586621680452680) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlMSym1 a6989586621680453302 t6989586621680452678 :: TyFun b6989586621680452680 (t6989586621680452678 a6989586621680452681 ~> m6989586621680452679 b6989586621680452680) -> Type) (a6989586621680453303 :: b6989586621680452680) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlMSym1 a6989586621680453302 t6989586621680452678 :: TyFun b6989586621680452680 (t6989586621680452678 a6989586621680452681 ~> m6989586621680452679 b6989586621680452680) -> Type) (a6989586621680453303 :: b6989586621680452680) = (FoldlMSym2 a6989586621680453302 a6989586621680453303 t6989586621680452678 :: TyFun (t6989586621680452678 a6989586621680452681) (m6989586621680452679 b6989586621680452680) -> Type)

data FoldlMSym2 (a6989586621680453302 :: (~>) b6989586621680452680 ((~>) a6989586621680452681 (m6989586621680452679 b6989586621680452680))) (a6989586621680453303 :: b6989586621680452680) :: forall t6989586621680452678. (~>) (t6989586621680452678 a6989586621680452681) (m6989586621680452679 b6989586621680452680) Source #

Instances
(SFoldable t, SMonad m, SingI d1, SingI d2) => SingI (FoldlMSym2 d1 d2 t :: TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FoldlMSym2 d1 d2 t) Source #

SuppressUnusedWarnings (FoldlMSym2 a6989586621680453303 a6989586621680453302 t6989586621680452678 :: TyFun (t6989586621680452678 a6989586621680452681) (m6989586621680452679 b6989586621680452680) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlMSym2 a6989586621680453303 a6989586621680453302 t :: TyFun (t a) (m b) -> Type) (a6989586621680453304 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlMSym2 a6989586621680453303 a6989586621680453302 t :: TyFun (t a) (m b) -> Type) (a6989586621680453304 :: t a) = FoldlM a6989586621680453303 a6989586621680453302 a6989586621680453304

type FoldlMSym3 (a6989586621680453302 :: (~>) b6989586621680452680 ((~>) a6989586621680452681 (m6989586621680452679 b6989586621680452680))) (a6989586621680453303 :: b6989586621680452680) (a6989586621680453304 :: t6989586621680452678 a6989586621680452681) = FoldlM a6989586621680453302 a6989586621680453303 a6989586621680453304 Source #

data Traverse_Sym0 :: forall a6989586621680452676 b6989586621680452677 f6989586621680452675 t6989586621680452674. (~>) ((~>) a6989586621680452676 (f6989586621680452675 b6989586621680452677)) ((~>) (t6989586621680452674 a6989586621680452676) (f6989586621680452675 ())) Source #

Instances
(SFoldable t, SApplicative f) => SingI (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Traverse_Sym0 :: TyFun (a6989586621680452676 ~> f6989586621680452675 b6989586621680452677) (t6989586621680452674 a6989586621680452676 ~> f6989586621680452675 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Traverse_Sym0 :: TyFun (a6989586621680452676 ~> f6989586621680452675 b6989586621680452677) (t6989586621680452674 a6989586621680452676 ~> f6989586621680452675 ()) -> Type) (a6989586621680453284 :: a6989586621680452676 ~> f6989586621680452675 b6989586621680452677) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Traverse_Sym0 :: TyFun (a6989586621680452676 ~> f6989586621680452675 b6989586621680452677) (t6989586621680452674 a6989586621680452676 ~> f6989586621680452675 ()) -> Type) (a6989586621680453284 :: a6989586621680452676 ~> f6989586621680452675 b6989586621680452677) = (Traverse_Sym1 a6989586621680453284 t6989586621680452674 :: TyFun (t6989586621680452674 a6989586621680452676) (f6989586621680452675 ()) -> Type)

data Traverse_Sym1 (a6989586621680453284 :: (~>) a6989586621680452676 (f6989586621680452675 b6989586621680452677)) :: forall t6989586621680452674. (~>) (t6989586621680452674 a6989586621680452676) (f6989586621680452675 ()) Source #

Instances
(SFoldable t, SApplicative f, SingI d) => SingI (Traverse_Sym1 d t :: TyFun (t a) (f ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (Traverse_Sym1 d t) Source #

SuppressUnusedWarnings (Traverse_Sym1 a6989586621680453284 t6989586621680452674 :: TyFun (t6989586621680452674 a6989586621680452676) (f6989586621680452675 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Traverse_Sym1 a6989586621680453284 t :: TyFun (t a) (f ()) -> Type) (a6989586621680453285 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Traverse_Sym1 a6989586621680453284 t :: TyFun (t a) (f ()) -> Type) (a6989586621680453285 :: t a) = Traverse_ a6989586621680453284 a6989586621680453285

type Traverse_Sym2 (a6989586621680453284 :: (~>) a6989586621680452676 (f6989586621680452675 b6989586621680452677)) (a6989586621680453285 :: t6989586621680452674 a6989586621680452676) = Traverse_ a6989586621680453284 a6989586621680453285 Source #

data For_Sym0 :: forall a6989586621680452672 b6989586621680452673 f6989586621680452671 t6989586621680452670. (~>) (t6989586621680452670 a6989586621680452672) ((~>) ((~>) a6989586621680452672 (f6989586621680452671 b6989586621680452673)) (f6989586621680452671 ())) Source #

Instances
(SFoldable t, SApplicative f) => SingI (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (For_Sym0 :: TyFun (t6989586621680452670 a6989586621680452672) ((a6989586621680452672 ~> f6989586621680452671 b6989586621680452673) ~> f6989586621680452671 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (For_Sym0 :: TyFun (t6989586621680452670 a6989586621680452672) ((a6989586621680452672 ~> f6989586621680452671 b6989586621680452673) ~> f6989586621680452671 ()) -> Type) (a6989586621680453296 :: t6989586621680452670 a6989586621680452672) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (For_Sym0 :: TyFun (t6989586621680452670 a6989586621680452672) ((a6989586621680452672 ~> f6989586621680452671 b6989586621680452673) ~> f6989586621680452671 ()) -> Type) (a6989586621680453296 :: t6989586621680452670 a6989586621680452672) = (For_Sym1 a6989586621680453296 b6989586621680452673 f6989586621680452671 :: TyFun (a6989586621680452672 ~> f6989586621680452671 b6989586621680452673) (f6989586621680452671 ()) -> Type)

data For_Sym1 (a6989586621680453296 :: t6989586621680452670 a6989586621680452672) :: forall b6989586621680452673 f6989586621680452671. (~>) ((~>) a6989586621680452672 (f6989586621680452671 b6989586621680452673)) (f6989586621680452671 ()) Source #

Instances
(SFoldable t, SApplicative f, SingI d) => SingI (For_Sym1 d b f :: TyFun (a ~> f b) (f ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (For_Sym1 d b f) Source #

SuppressUnusedWarnings (For_Sym1 a6989586621680453296 b6989586621680452673 f6989586621680452671 :: TyFun (a6989586621680452672 ~> f6989586621680452671 b6989586621680452673) (f6989586621680452671 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (For_Sym1 a6989586621680453296 b f :: TyFun (a ~> f b) (f ()) -> Type) (a6989586621680453297 :: a ~> f b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (For_Sym1 a6989586621680453296 b f :: TyFun (a ~> f b) (f ()) -> Type) (a6989586621680453297 :: a ~> f b) = For_ a6989586621680453296 a6989586621680453297

type For_Sym2 (a6989586621680453296 :: t6989586621680452670 a6989586621680452672) (a6989586621680453297 :: (~>) a6989586621680452672 (f6989586621680452671 b6989586621680452673)) = For_ a6989586621680453296 a6989586621680453297 Source #

data SequenceA_Sym0 :: forall a6989586621680452661 f6989586621680452660 t6989586621680452659. (~>) (t6989586621680452659 (f6989586621680452660 a6989586621680452661)) (f6989586621680452660 ()) Source #

Instances
(SFoldable t, SApplicative f) => SingI (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (SequenceA_Sym0 :: TyFun (t6989586621680452659 (f6989586621680452660 a6989586621680452661)) (f6989586621680452660 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) (a6989586621680453263 :: t (f a)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) (a6989586621680453263 :: t (f a)) = SequenceA_ a6989586621680453263

type SequenceA_Sym1 (a6989586621680453263 :: t6989586621680452659 (f6989586621680452660 a6989586621680452661)) = SequenceA_ a6989586621680453263 Source #

data AsumSym0 :: forall a6989586621680452655 f6989586621680452654 t6989586621680452653. (~>) (t6989586621680452653 (f6989586621680452654 a6989586621680452655)) (f6989586621680452654 a6989586621680452655) Source #

Instances
(SFoldable t, SAlternative f) => SingI (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AsumSym0 :: TyFun (t6989586621680452653 (f6989586621680452654 a6989586621680452655)) (f6989586621680452654 a6989586621680452655) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) (a6989586621680453248 :: t (f a)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) (a6989586621680453248 :: t (f a)) = Asum a6989586621680453248

type AsumSym1 (a6989586621680453248 :: t6989586621680452653 (f6989586621680452654 a6989586621680452655)) = Asum a6989586621680453248 Source #

data MapM_Sym0 :: forall a6989586621680452668 b6989586621680452669 m6989586621680452667 t6989586621680452666. (~>) ((~>) a6989586621680452668 (m6989586621680452667 b6989586621680452669)) ((~>) (t6989586621680452666 a6989586621680452668) (m6989586621680452667 ())) Source #

Instances
(SFoldable t, SMonad m) => SingI (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (MapM_Sym0 :: TyFun (a6989586621680452668 ~> m6989586621680452667 b6989586621680452669) (t6989586621680452666 a6989586621680452668 ~> m6989586621680452667 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MapM_Sym0 :: TyFun (a6989586621680452668 ~> m6989586621680452667 b6989586621680452669) (t6989586621680452666 a6989586621680452668 ~> m6989586621680452667 ()) -> Type) (a6989586621680453266 :: a6989586621680452668 ~> m6989586621680452667 b6989586621680452669) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MapM_Sym0 :: TyFun (a6989586621680452668 ~> m6989586621680452667 b6989586621680452669) (t6989586621680452666 a6989586621680452668 ~> m6989586621680452667 ()) -> Type) (a6989586621680453266 :: a6989586621680452668 ~> m6989586621680452667 b6989586621680452669) = (MapM_Sym1 a6989586621680453266 t6989586621680452666 :: TyFun (t6989586621680452666 a6989586621680452668) (m6989586621680452667 ()) -> Type)

data MapM_Sym1 (a6989586621680453266 :: (~>) a6989586621680452668 (m6989586621680452667 b6989586621680452669)) :: forall t6989586621680452666. (~>) (t6989586621680452666 a6989586621680452668) (m6989586621680452667 ()) Source #

Instances
(SFoldable t, SMonad m, SingI d) => SingI (MapM_Sym1 d t :: TyFun (t a) (m ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (MapM_Sym1 d t) Source #

SuppressUnusedWarnings (MapM_Sym1 a6989586621680453266 t6989586621680452666 :: TyFun (t6989586621680452666 a6989586621680452668) (m6989586621680452667 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MapM_Sym1 a6989586621680453266 t :: TyFun (t a) (m ()) -> Type) (a6989586621680453267 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MapM_Sym1 a6989586621680453266 t :: TyFun (t a) (m ()) -> Type) (a6989586621680453267 :: t a) = MapM_ a6989586621680453266 a6989586621680453267

type MapM_Sym2 (a6989586621680453266 :: (~>) a6989586621680452668 (m6989586621680452667 b6989586621680452669)) (a6989586621680453267 :: t6989586621680452666 a6989586621680452668) = MapM_ a6989586621680453266 a6989586621680453267 Source #

data ForM_Sym0 :: forall a6989586621680452664 b6989586621680452665 m6989586621680452663 t6989586621680452662. (~>) (t6989586621680452662 a6989586621680452664) ((~>) ((~>) a6989586621680452664 (m6989586621680452663 b6989586621680452665)) (m6989586621680452663 ())) Source #

Instances
(SFoldable t, SMonad m) => SingI (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ForM_Sym0 :: TyFun (t6989586621680452662 a6989586621680452664) ((a6989586621680452664 ~> m6989586621680452663 b6989586621680452665) ~> m6989586621680452663 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ForM_Sym0 :: TyFun (t6989586621680452662 a6989586621680452664) ((a6989586621680452664 ~> m6989586621680452663 b6989586621680452665) ~> m6989586621680452663 ()) -> Type) (a6989586621680453278 :: t6989586621680452662 a6989586621680452664) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ForM_Sym0 :: TyFun (t6989586621680452662 a6989586621680452664) ((a6989586621680452664 ~> m6989586621680452663 b6989586621680452665) ~> m6989586621680452663 ()) -> Type) (a6989586621680453278 :: t6989586621680452662 a6989586621680452664) = (ForM_Sym1 a6989586621680453278 b6989586621680452665 m6989586621680452663 :: TyFun (a6989586621680452664 ~> m6989586621680452663 b6989586621680452665) (m6989586621680452663 ()) -> Type)

data ForM_Sym1 (a6989586621680453278 :: t6989586621680452662 a6989586621680452664) :: forall b6989586621680452665 m6989586621680452663. (~>) ((~>) a6989586621680452664 (m6989586621680452663 b6989586621680452665)) (m6989586621680452663 ()) Source #

Instances
(SFoldable t, SMonad m, SingI d) => SingI (ForM_Sym1 d b m :: TyFun (a ~> m b) (m ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (ForM_Sym1 d b m) Source #

SuppressUnusedWarnings (ForM_Sym1 a6989586621680453278 b6989586621680452665 m6989586621680452663 :: TyFun (a6989586621680452664 ~> m6989586621680452663 b6989586621680452665) (m6989586621680452663 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ForM_Sym1 a6989586621680453278 b m :: TyFun (a ~> m b) (m ()) -> Type) (a6989586621680453279 :: a ~> m b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ForM_Sym1 a6989586621680453278 b m :: TyFun (a ~> m b) (m ()) -> Type) (a6989586621680453279 :: a ~> m b) = ForM_ a6989586621680453278 a6989586621680453279

type ForM_Sym2 (a6989586621680453278 :: t6989586621680452662 a6989586621680452664) (a6989586621680453279 :: (~>) a6989586621680452664 (m6989586621680452663 b6989586621680452665)) = ForM_ a6989586621680453278 a6989586621680453279 Source #

data Sequence_Sym0 :: forall a6989586621680452658 m6989586621680452657 t6989586621680452656. (~>) (t6989586621680452656 (m6989586621680452657 a6989586621680452658)) (m6989586621680452657 ()) Source #

Instances
(SFoldable t, SMonad m) => SingI (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Sequence_Sym0 :: TyFun (t6989586621680452656 (m6989586621680452657 a6989586621680452658)) (m6989586621680452657 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) (a6989586621680453258 :: t (m a)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) (a6989586621680453258 :: t (m a)) = Sequence_ a6989586621680453258

type Sequence_Sym1 (a6989586621680453258 :: t6989586621680452656 (m6989586621680452657 a6989586621680452658)) = Sequence_ a6989586621680453258 Source #

data MsumSym0 :: forall a6989586621680452652 m6989586621680452651 t6989586621680452650. (~>) (t6989586621680452650 (m6989586621680452651 a6989586621680452652)) (m6989586621680452651 a6989586621680452652) Source #

Instances
(SFoldable t, SMonadPlus m) => SingI (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (MsumSym0 :: TyFun (t6989586621680452650 (m6989586621680452651 a6989586621680452652)) (m6989586621680452651 a6989586621680452652) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) (a6989586621680453253 :: t (m a)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) (a6989586621680453253 :: t (m a)) = Msum a6989586621680453253

type MsumSym1 (a6989586621680453253 :: t6989586621680452650 (m6989586621680452651 a6989586621680452652)) = Msum a6989586621680453253 Source #

data ConcatSym0 :: forall a6989586621680452649 t6989586621680452648. (~>) (t6989586621680452648 [a6989586621680452649]) [a6989586621680452649] Source #

Instances
SFoldable t => SingI (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ConcatSym0 :: TyFun (t6989586621680452648 [a6989586621680452649]) [a6989586621680452649] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680453234 :: t [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680453234 :: t [a]) = Concat a6989586621680453234

type ConcatSym1 (a6989586621680453234 :: t6989586621680452648 [a6989586621680452649]) = Concat a6989586621680453234 Source #

data ConcatMapSym0 :: forall a6989586621680452646 b6989586621680452647 t6989586621680452645. (~>) ((~>) a6989586621680452646 [b6989586621680452647]) ((~>) (t6989586621680452645 a6989586621680452646) [b6989586621680452647]) Source #

Instances
SFoldable t => SingI (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ConcatMapSym0 :: TyFun (a6989586621680452646 ~> [b6989586621680452647]) (t6989586621680452645 a6989586621680452646 ~> [b6989586621680452647]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ConcatMapSym0 :: TyFun (a6989586621680452646 ~> [b6989586621680452647]) (t6989586621680452645 a6989586621680452646 ~> [b6989586621680452647]) -> Type) (a6989586621680453218 :: a6989586621680452646 ~> [b6989586621680452647]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ConcatMapSym0 :: TyFun (a6989586621680452646 ~> [b6989586621680452647]) (t6989586621680452645 a6989586621680452646 ~> [b6989586621680452647]) -> Type) (a6989586621680453218 :: a6989586621680452646 ~> [b6989586621680452647]) = (ConcatMapSym1 a6989586621680453218 t6989586621680452645 :: TyFun (t6989586621680452645 a6989586621680452646) [b6989586621680452647] -> Type)

data ConcatMapSym1 (a6989586621680453218 :: (~>) a6989586621680452646 [b6989586621680452647]) :: forall t6989586621680452645. (~>) (t6989586621680452645 a6989586621680452646) [b6989586621680452647] Source #

Instances
(SFoldable t, SingI d) => SingI (ConcatMapSym1 d t :: TyFun (t a) [b] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (ConcatMapSym1 d t) Source #

SuppressUnusedWarnings (ConcatMapSym1 a6989586621680453218 t6989586621680452645 :: TyFun (t6989586621680452645 a6989586621680452646) [b6989586621680452647] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ConcatMapSym1 a6989586621680453218 t :: TyFun (t a) [b] -> Type) (a6989586621680453219 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ConcatMapSym1 a6989586621680453218 t :: TyFun (t a) [b] -> Type) (a6989586621680453219 :: t a) = ConcatMap a6989586621680453218 a6989586621680453219

type ConcatMapSym2 (a6989586621680453218 :: (~>) a6989586621680452646 [b6989586621680452647]) (a6989586621680453219 :: t6989586621680452645 a6989586621680452646) = ConcatMap a6989586621680453218 a6989586621680453219 Source #

data AndSym0 :: forall t6989586621680452644. (~>) (t6989586621680452644 Bool) Bool Source #

Instances
SFoldable t => SingI (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AndSym0 :: TyFun (t6989586621680452644 Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680453209 :: t Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680453209 :: t Bool) = And a6989586621680453209

type AndSym1 (a6989586621680453209 :: t6989586621680452644 Bool) = And a6989586621680453209 Source #

data OrSym0 :: forall t6989586621680452643. (~>) (t6989586621680452643 Bool) Bool Source #

Instances
SFoldable t => SingI (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing OrSym0 Source #

SuppressUnusedWarnings (OrSym0 :: TyFun (t6989586621680452643 Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680453200 :: t Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680453200 :: t Bool) = Or a6989586621680453200

type OrSym1 (a6989586621680453200 :: t6989586621680452643 Bool) = Or a6989586621680453200 Source #

data AnySym0 :: forall a6989586621680452642 t6989586621680452641. (~>) ((~>) a6989586621680452642 Bool) ((~>) (t6989586621680452641 a6989586621680452642) Bool) Source #

Instances
SFoldable t => SingI (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AnySym0 :: TyFun (a6989586621680452642 ~> Bool) (t6989586621680452641 a6989586621680452642 ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym0 :: TyFun (a6989586621680452642 ~> Bool) (t6989586621680452641 a6989586621680452642 ~> Bool) -> Type) (a6989586621680453187 :: a6989586621680452642 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym0 :: TyFun (a6989586621680452642 ~> Bool) (t6989586621680452641 a6989586621680452642 ~> Bool) -> Type) (a6989586621680453187 :: a6989586621680452642 ~> Bool) = (AnySym1 a6989586621680453187 t6989586621680452641 :: TyFun (t6989586621680452641 a6989586621680452642) Bool -> Type)

data AnySym1 (a6989586621680453187 :: (~>) a6989586621680452642 Bool) :: forall t6989586621680452641. (~>) (t6989586621680452641 a6989586621680452642) Bool Source #

Instances
(SFoldable t, SingI d) => SingI (AnySym1 d t :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (AnySym1 d t) Source #

SuppressUnusedWarnings (AnySym1 a6989586621680453187 t6989586621680452641 :: TyFun (t6989586621680452641 a6989586621680452642) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym1 a6989586621680453187 t :: TyFun (t a) Bool -> Type) (a6989586621680453188 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym1 a6989586621680453187 t :: TyFun (t a) Bool -> Type) (a6989586621680453188 :: t a) = Any a6989586621680453187 a6989586621680453188

type AnySym2 (a6989586621680453187 :: (~>) a6989586621680452642 Bool) (a6989586621680453188 :: t6989586621680452641 a6989586621680452642) = Any a6989586621680453187 a6989586621680453188 Source #

data AllSym0 :: forall a6989586621680452640 t6989586621680452639. (~>) ((~>) a6989586621680452640 Bool) ((~>) (t6989586621680452639 a6989586621680452640) Bool) Source #

Instances
SFoldable t => SingI (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AllSym0 :: TyFun (a6989586621680452640 ~> Bool) (t6989586621680452639 a6989586621680452640 ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym0 :: TyFun (a6989586621680452640 ~> Bool) (t6989586621680452639 a6989586621680452640 ~> Bool) -> Type) (a6989586621680453174 :: a6989586621680452640 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym0 :: TyFun (a6989586621680452640 ~> Bool) (t6989586621680452639 a6989586621680452640 ~> Bool) -> Type) (a6989586621680453174 :: a6989586621680452640 ~> Bool) = (AllSym1 a6989586621680453174 t6989586621680452639 :: TyFun (t6989586621680452639 a6989586621680452640) Bool -> Type)

data AllSym1 (a6989586621680453174 :: (~>) a6989586621680452640 Bool) :: forall t6989586621680452639. (~>) (t6989586621680452639 a6989586621680452640) Bool Source #

Instances
(SFoldable t, SingI d) => SingI (AllSym1 d t :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (AllSym1 d t) Source #

SuppressUnusedWarnings (AllSym1 a6989586621680453174 t6989586621680452639 :: TyFun (t6989586621680452639 a6989586621680452640) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym1 a6989586621680453174 t :: TyFun (t a) Bool -> Type) (a6989586621680453175 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym1 a6989586621680453174 t :: TyFun (t a) Bool -> Type) (a6989586621680453175 :: t a) = All a6989586621680453174 a6989586621680453175

type AllSym2 (a6989586621680453174 :: (~>) a6989586621680452640 Bool) (a6989586621680453175 :: t6989586621680452639 a6989586621680452640) = All a6989586621680453174 a6989586621680453175 Source #

data MaximumBySym0 :: forall a6989586621680452638 t6989586621680452637. (~>) ((~>) a6989586621680452638 ((~>) a6989586621680452638 Ordering)) ((~>) (t6989586621680452637 a6989586621680452638) a6989586621680452638) Source #

Instances
SFoldable t => SingI (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (MaximumBySym0 :: TyFun (a6989586621680452638 ~> (a6989586621680452638 ~> Ordering)) (t6989586621680452637 a6989586621680452638 ~> a6989586621680452638) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaximumBySym0 :: TyFun (a6989586621680452638 ~> (a6989586621680452638 ~> Ordering)) (t6989586621680452637 a6989586621680452638 ~> a6989586621680452638) -> Type) (a6989586621680453149 :: a6989586621680452638 ~> (a6989586621680452638 ~> Ordering)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaximumBySym0 :: TyFun (a6989586621680452638 ~> (a6989586621680452638 ~> Ordering)) (t6989586621680452637 a6989586621680452638 ~> a6989586621680452638) -> Type) (a6989586621680453149 :: a6989586621680452638 ~> (a6989586621680452638 ~> Ordering)) = (MaximumBySym1 a6989586621680453149 t6989586621680452637 :: TyFun (t6989586621680452637 a6989586621680452638) a6989586621680452638 -> Type)

data MaximumBySym1 (a6989586621680453149 :: (~>) a6989586621680452638 ((~>) a6989586621680452638 Ordering)) :: forall t6989586621680452637. (~>) (t6989586621680452637 a6989586621680452638) a6989586621680452638 Source #

Instances
(SFoldable t, SingI d) => SingI (MaximumBySym1 d t :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (MaximumBySym1 d t) Source #

SuppressUnusedWarnings (MaximumBySym1 a6989586621680453149 t6989586621680452637 :: TyFun (t6989586621680452637 a6989586621680452638) a6989586621680452638 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaximumBySym1 a6989586621680453149 t :: TyFun (t a) a -> Type) (a6989586621680453150 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaximumBySym1 a6989586621680453149 t :: TyFun (t a) a -> Type) (a6989586621680453150 :: t a) = MaximumBy a6989586621680453149 a6989586621680453150

type MaximumBySym2 (a6989586621680453149 :: (~>) a6989586621680452638 ((~>) a6989586621680452638 Ordering)) (a6989586621680453150 :: t6989586621680452637 a6989586621680452638) = MaximumBy a6989586621680453149 a6989586621680453150 Source #

data MinimumBySym0 :: forall a6989586621680452636 t6989586621680452635. (~>) ((~>) a6989586621680452636 ((~>) a6989586621680452636 Ordering)) ((~>) (t6989586621680452635 a6989586621680452636) a6989586621680452636) Source #

Instances
SFoldable t => SingI (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (MinimumBySym0 :: TyFun (a6989586621680452636 ~> (a6989586621680452636 ~> Ordering)) (t6989586621680452635 a6989586621680452636 ~> a6989586621680452636) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinimumBySym0 :: TyFun (a6989586621680452636 ~> (a6989586621680452636 ~> Ordering)) (t6989586621680452635 a6989586621680452636 ~> a6989586621680452636) -> Type) (a6989586621680453124 :: a6989586621680452636 ~> (a6989586621680452636 ~> Ordering)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinimumBySym0 :: TyFun (a6989586621680452636 ~> (a6989586621680452636 ~> Ordering)) (t6989586621680452635 a6989586621680452636 ~> a6989586621680452636) -> Type) (a6989586621680453124 :: a6989586621680452636 ~> (a6989586621680452636 ~> Ordering)) = (MinimumBySym1 a6989586621680453124 t6989586621680452635 :: TyFun (t6989586621680452635 a6989586621680452636) a6989586621680452636 -> Type)

data MinimumBySym1 (a6989586621680453124 :: (~>) a6989586621680452636 ((~>) a6989586621680452636 Ordering)) :: forall t6989586621680452635. (~>) (t6989586621680452635 a6989586621680452636) a6989586621680452636 Source #

Instances
(SFoldable t, SingI d) => SingI (MinimumBySym1 d t :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (MinimumBySym1 d t) Source #

SuppressUnusedWarnings (MinimumBySym1 a6989586621680453124 t6989586621680452635 :: TyFun (t6989586621680452635 a6989586621680452636) a6989586621680452636 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinimumBySym1 a6989586621680453124 t :: TyFun (t a) a -> Type) (a6989586621680453125 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinimumBySym1 a6989586621680453124 t :: TyFun (t a) a -> Type) (a6989586621680453125 :: t a) = MinimumBy a6989586621680453124 a6989586621680453125

type MinimumBySym2 (a6989586621680453124 :: (~>) a6989586621680452636 ((~>) a6989586621680452636 Ordering)) (a6989586621680453125 :: t6989586621680452635 a6989586621680452636) = MinimumBy a6989586621680453124 a6989586621680453125 Source #

data NotElemSym0 :: forall a6989586621680452634 t6989586621680452633. (~>) a6989586621680452634 ((~>) (t6989586621680452633 a6989586621680452634) Bool) Source #

Instances
(SFoldable t, SEq a) => SingI (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621680452634 (t6989586621680452633 a6989586621680452634 ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym0 :: TyFun a6989586621680452634 (t6989586621680452633 a6989586621680452634 ~> Bool) -> Type) (a6989586621680453116 :: a6989586621680452634) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym0 :: TyFun a6989586621680452634 (t6989586621680452633 a6989586621680452634 ~> Bool) -> Type) (a6989586621680453116 :: a6989586621680452634) = (NotElemSym1 a6989586621680453116 t6989586621680452633 :: TyFun (t6989586621680452633 a6989586621680452634) Bool -> Type)

data NotElemSym1 (a6989586621680453116 :: a6989586621680452634) :: forall t6989586621680452633. (~>) (t6989586621680452633 a6989586621680452634) Bool Source #

Instances
(SFoldable t, SEq a, SingI d) => SingI (NotElemSym1 d t :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (NotElemSym1 d t) Source #

SuppressUnusedWarnings (NotElemSym1 a6989586621680453116 t6989586621680452633 :: TyFun (t6989586621680452633 a6989586621680452634) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym1 a6989586621680453116 t :: TyFun (t a) Bool -> Type) (a6989586621680453117 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym1 a6989586621680453116 t :: TyFun (t a) Bool -> Type) (a6989586621680453117 :: t a) = NotElem a6989586621680453116 a6989586621680453117

type NotElemSym2 (a6989586621680453116 :: a6989586621680452634) (a6989586621680453117 :: t6989586621680452633 a6989586621680452634) = NotElem a6989586621680453116 a6989586621680453117 Source #

data FindSym0 :: forall a6989586621680452632 t6989586621680452631. (~>) ((~>) a6989586621680452632 Bool) ((~>) (t6989586621680452631 a6989586621680452632) (Maybe a6989586621680452632)) Source #

Instances
SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621680452632 ~> Bool) (t6989586621680452631 a6989586621680452632 ~> Maybe a6989586621680452632) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym0 :: TyFun (a6989586621680452632 ~> Bool) (t6989586621680452631 a6989586621680452632 ~> Maybe a6989586621680452632) -> Type) (a6989586621680453089 :: a6989586621680452632 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym0 :: TyFun (a6989586621680452632 ~> Bool) (t6989586621680452631 a6989586621680452632 ~> Maybe a6989586621680452632) -> Type) (a6989586621680453089 :: a6989586621680452632 ~> Bool) = (FindSym1 a6989586621680453089 t6989586621680452631 :: TyFun (t6989586621680452631 a6989586621680452632) (Maybe a6989586621680452632) -> Type)

data FindSym1 (a6989586621680453089 :: (~>) a6989586621680452632 Bool) :: forall t6989586621680452631. (~>) (t6989586621680452631 a6989586621680452632) (Maybe a6989586621680452632) Source #

Instances
(SFoldable t, SingI d) => SingI (FindSym1 d t :: TyFun (t a) (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FindSym1 d t) Source #

SuppressUnusedWarnings (FindSym1 a6989586621680453089 t6989586621680452631 :: TyFun (t6989586621680452631 a6989586621680452632) (Maybe a6989586621680452632) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym1 a6989586621680453089 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680453090 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym1 a6989586621680453089 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680453090 :: t a) = Find a6989586621680453089 a6989586621680453090

type FindSym2 (a6989586621680453089 :: (~>) a6989586621680452632 Bool) (a6989586621680453090 :: t6989586621680452631 a6989586621680452632) = Find a6989586621680453089 a6989586621680453090 Source #