singletons-2.5.1: 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 m6989586621680438527 t6989586621680438526. (~>) (t6989586621680438526 m6989586621680438527) m6989586621680438527
  • type FoldSym1 (arg6989586621680439149 :: t6989586621680438526 m6989586621680438527) = Fold arg6989586621680439149
  • data FoldMapSym0 :: forall a6989586621680438529 m6989586621680438528 t6989586621680438526. (~>) ((~>) a6989586621680438529 m6989586621680438528) ((~>) (t6989586621680438526 a6989586621680438529) m6989586621680438528)
  • data FoldMapSym1 (arg6989586621680439151 :: (~>) a6989586621680438529 m6989586621680438528) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438529) m6989586621680438528
  • type FoldMapSym2 (arg6989586621680439151 :: (~>) a6989586621680438529 m6989586621680438528) (arg6989586621680439152 :: t6989586621680438526 a6989586621680438529) = FoldMap arg6989586621680439151 arg6989586621680439152
  • data FoldrSym0 :: forall a6989586621680438530 b6989586621680438531 t6989586621680438526. (~>) ((~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) ((~>) b6989586621680438531 ((~>) (t6989586621680438526 a6989586621680438530) b6989586621680438531))
  • data FoldrSym1 (arg6989586621680439155 :: (~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) :: forall t6989586621680438526. (~>) b6989586621680438531 ((~>) (t6989586621680438526 a6989586621680438530) b6989586621680438531)
  • data FoldrSym2 (arg6989586621680439155 :: (~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) (arg6989586621680439156 :: b6989586621680438531) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438530) b6989586621680438531
  • type FoldrSym3 (arg6989586621680439155 :: (~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) (arg6989586621680439156 :: b6989586621680438531) (arg6989586621680439157 :: t6989586621680438526 a6989586621680438530) = Foldr arg6989586621680439155 arg6989586621680439156 arg6989586621680439157
  • data Foldr'Sym0 :: forall a6989586621680438532 b6989586621680438533 t6989586621680438526. (~>) ((~>) a6989586621680438532 ((~>) b6989586621680438533 b6989586621680438533)) ((~>) b6989586621680438533 ((~>) (t6989586621680438526 a6989586621680438532) b6989586621680438533))
  • data Foldr'Sym1 (arg6989586621680439161 :: (~>) a6989586621680438532 ((~>) b6989586621680438533 b6989586621680438533)) :: forall t6989586621680438526. (~>) b6989586621680438533 ((~>) (t6989586621680438526 a6989586621680438532) b6989586621680438533)
  • data Foldr'Sym2 (arg6989586621680439161 :: (~>) a6989586621680438532 ((~>) b6989586621680438533 b6989586621680438533)) (arg6989586621680439162 :: b6989586621680438533) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438532) b6989586621680438533
  • type Foldr'Sym3 (arg6989586621680439161 :: (~>) a6989586621680438532 ((~>) b6989586621680438533 b6989586621680438533)) (arg6989586621680439162 :: b6989586621680438533) (arg6989586621680439163 :: t6989586621680438526 a6989586621680438532) = Foldr' arg6989586621680439161 arg6989586621680439162 arg6989586621680439163
  • data FoldlSym0 :: forall a6989586621680438535 b6989586621680438534 t6989586621680438526. (~>) ((~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) ((~>) b6989586621680438534 ((~>) (t6989586621680438526 a6989586621680438535) b6989586621680438534))
  • data FoldlSym1 (arg6989586621680439167 :: (~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) :: forall t6989586621680438526. (~>) b6989586621680438534 ((~>) (t6989586621680438526 a6989586621680438535) b6989586621680438534)
  • data FoldlSym2 (arg6989586621680439167 :: (~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) (arg6989586621680439168 :: b6989586621680438534) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438535) b6989586621680438534
  • type FoldlSym3 (arg6989586621680439167 :: (~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) (arg6989586621680439168 :: b6989586621680438534) (arg6989586621680439169 :: t6989586621680438526 a6989586621680438535) = Foldl arg6989586621680439167 arg6989586621680439168 arg6989586621680439169
  • data Foldl'Sym0 :: forall a6989586621680438537 b6989586621680438536 t6989586621680438526. (~>) ((~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) ((~>) b6989586621680438536 ((~>) (t6989586621680438526 a6989586621680438537) b6989586621680438536))
  • data Foldl'Sym1 (arg6989586621680439173 :: (~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) :: forall t6989586621680438526. (~>) b6989586621680438536 ((~>) (t6989586621680438526 a6989586621680438537) b6989586621680438536)
  • data Foldl'Sym2 (arg6989586621680439173 :: (~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) (arg6989586621680439174 :: b6989586621680438536) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438537) b6989586621680438536
  • type Foldl'Sym3 (arg6989586621680439173 :: (~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) (arg6989586621680439174 :: b6989586621680438536) (arg6989586621680439175 :: t6989586621680438526 a6989586621680438537) = Foldl' arg6989586621680439173 arg6989586621680439174 arg6989586621680439175
  • data Foldr1Sym0 :: forall a6989586621680438538 t6989586621680438526. (~>) ((~>) a6989586621680438538 ((~>) a6989586621680438538 a6989586621680438538)) ((~>) (t6989586621680438526 a6989586621680438538) a6989586621680438538)
  • data Foldr1Sym1 (arg6989586621680439179 :: (~>) a6989586621680438538 ((~>) a6989586621680438538 a6989586621680438538)) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438538) a6989586621680438538
  • type Foldr1Sym2 (arg6989586621680439179 :: (~>) a6989586621680438538 ((~>) a6989586621680438538 a6989586621680438538)) (arg6989586621680439180 :: t6989586621680438526 a6989586621680438538) = Foldr1 arg6989586621680439179 arg6989586621680439180
  • data Foldl1Sym0 :: forall a6989586621680438539 t6989586621680438526. (~>) ((~>) a6989586621680438539 ((~>) a6989586621680438539 a6989586621680438539)) ((~>) (t6989586621680438526 a6989586621680438539) a6989586621680438539)
  • data Foldl1Sym1 (arg6989586621680439183 :: (~>) a6989586621680438539 ((~>) a6989586621680438539 a6989586621680438539)) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438539) a6989586621680438539
  • type Foldl1Sym2 (arg6989586621680439183 :: (~>) a6989586621680438539 ((~>) a6989586621680438539 a6989586621680438539)) (arg6989586621680439184 :: t6989586621680438526 a6989586621680438539) = Foldl1 arg6989586621680439183 arg6989586621680439184
  • data ToListSym0 :: forall a6989586621680438540 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438540) [a6989586621680438540]
  • type ToListSym1 (arg6989586621680439187 :: t6989586621680438526 a6989586621680438540) = ToList arg6989586621680439187
  • data NullSym0 :: forall a6989586621680438541 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438541) Bool
  • type NullSym1 (arg6989586621680439189 :: t6989586621680438526 a6989586621680438541) = Null arg6989586621680439189
  • data LengthSym0 :: forall a6989586621680438542 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438542) Nat
  • type LengthSym1 (arg6989586621680439191 :: t6989586621680438526 a6989586621680438542) = Length arg6989586621680439191
  • data ElemSym0 :: forall a6989586621680438543 t6989586621680438526. (~>) a6989586621680438543 ((~>) (t6989586621680438526 a6989586621680438543) Bool)
  • data ElemSym1 (arg6989586621680439193 :: a6989586621680438543) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438543) Bool
  • type ElemSym2 (arg6989586621680439193 :: a6989586621680438543) (arg6989586621680439194 :: t6989586621680438526 a6989586621680438543) = Elem arg6989586621680439193 arg6989586621680439194
  • data MaximumSym0 :: forall a6989586621680438544 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438544) a6989586621680438544
  • type MaximumSym1 (arg6989586621680439197 :: t6989586621680438526 a6989586621680438544) = Maximum arg6989586621680439197
  • data MinimumSym0 :: forall a6989586621680438545 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438545) a6989586621680438545
  • type MinimumSym1 (arg6989586621680439199 :: t6989586621680438526 a6989586621680438545) = Minimum arg6989586621680439199
  • data SumSym0 :: forall a6989586621680438546 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438546) a6989586621680438546
  • type SumSym1 (arg6989586621680439201 :: t6989586621680438526 a6989586621680438546) = Sum arg6989586621680439201
  • data ProductSym0 :: forall a6989586621680438547 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438547) a6989586621680438547
  • type ProductSym1 (arg6989586621680439203 :: t6989586621680438526 a6989586621680438547) = Product arg6989586621680439203
  • data FoldrMSym0 :: forall a6989586621680438487 b6989586621680438488 m6989586621680438486 t6989586621680438485. (~>) ((~>) a6989586621680438487 ((~>) b6989586621680438488 (m6989586621680438486 b6989586621680438488))) ((~>) b6989586621680438488 ((~>) (t6989586621680438485 a6989586621680438487) (m6989586621680438486 b6989586621680438488)))
  • data FoldrMSym1 (a6989586621680439127 :: (~>) a6989586621680438487 ((~>) b6989586621680438488 (m6989586621680438486 b6989586621680438488))) :: forall t6989586621680438485. (~>) b6989586621680438488 ((~>) (t6989586621680438485 a6989586621680438487) (m6989586621680438486 b6989586621680438488))
  • data FoldrMSym2 (a6989586621680439127 :: (~>) a6989586621680438487 ((~>) b6989586621680438488 (m6989586621680438486 b6989586621680438488))) (a6989586621680439128 :: b6989586621680438488) :: forall t6989586621680438485. (~>) (t6989586621680438485 a6989586621680438487) (m6989586621680438486 b6989586621680438488)
  • type FoldrMSym3 (a6989586621680439127 :: (~>) a6989586621680438487 ((~>) b6989586621680438488 (m6989586621680438486 b6989586621680438488))) (a6989586621680439128 :: b6989586621680438488) (a6989586621680439129 :: t6989586621680438485 a6989586621680438487) = FoldrM a6989586621680439127 a6989586621680439128 a6989586621680439129
  • data FoldlMSym0 :: forall a6989586621680438484 b6989586621680438483 m6989586621680438482 t6989586621680438481. (~>) ((~>) b6989586621680438483 ((~>) a6989586621680438484 (m6989586621680438482 b6989586621680438483))) ((~>) b6989586621680438483 ((~>) (t6989586621680438481 a6989586621680438484) (m6989586621680438482 b6989586621680438483)))
  • data FoldlMSym1 (a6989586621680439105 :: (~>) b6989586621680438483 ((~>) a6989586621680438484 (m6989586621680438482 b6989586621680438483))) :: forall t6989586621680438481. (~>) b6989586621680438483 ((~>) (t6989586621680438481 a6989586621680438484) (m6989586621680438482 b6989586621680438483))
  • data FoldlMSym2 (a6989586621680439105 :: (~>) b6989586621680438483 ((~>) a6989586621680438484 (m6989586621680438482 b6989586621680438483))) (a6989586621680439106 :: b6989586621680438483) :: forall t6989586621680438481. (~>) (t6989586621680438481 a6989586621680438484) (m6989586621680438482 b6989586621680438483)
  • type FoldlMSym3 (a6989586621680439105 :: (~>) b6989586621680438483 ((~>) a6989586621680438484 (m6989586621680438482 b6989586621680438483))) (a6989586621680439106 :: b6989586621680438483) (a6989586621680439107 :: t6989586621680438481 a6989586621680438484) = FoldlM a6989586621680439105 a6989586621680439106 a6989586621680439107
  • data Traverse_Sym0 :: forall a6989586621680438479 b6989586621680438480 f6989586621680438478 t6989586621680438477. (~>) ((~>) a6989586621680438479 (f6989586621680438478 b6989586621680438480)) ((~>) (t6989586621680438477 a6989586621680438479) (f6989586621680438478 ()))
  • data Traverse_Sym1 (a6989586621680439087 :: (~>) a6989586621680438479 (f6989586621680438478 b6989586621680438480)) :: forall t6989586621680438477. (~>) (t6989586621680438477 a6989586621680438479) (f6989586621680438478 ())
  • type Traverse_Sym2 (a6989586621680439087 :: (~>) a6989586621680438479 (f6989586621680438478 b6989586621680438480)) (a6989586621680439088 :: t6989586621680438477 a6989586621680438479) = Traverse_ a6989586621680439087 a6989586621680439088
  • data For_Sym0 :: forall a6989586621680438475 b6989586621680438476 f6989586621680438474 t6989586621680438473. (~>) (t6989586621680438473 a6989586621680438475) ((~>) ((~>) a6989586621680438475 (f6989586621680438474 b6989586621680438476)) (f6989586621680438474 ()))
  • data For_Sym1 (a6989586621680439099 :: t6989586621680438473 a6989586621680438475) :: forall b6989586621680438476 f6989586621680438474. (~>) ((~>) a6989586621680438475 (f6989586621680438474 b6989586621680438476)) (f6989586621680438474 ())
  • type For_Sym2 (a6989586621680439099 :: t6989586621680438473 a6989586621680438475) (a6989586621680439100 :: (~>) a6989586621680438475 (f6989586621680438474 b6989586621680438476)) = For_ a6989586621680439099 a6989586621680439100
  • data SequenceA_Sym0 :: forall a6989586621680438464 f6989586621680438463 t6989586621680438462. (~>) (t6989586621680438462 (f6989586621680438463 a6989586621680438464)) (f6989586621680438463 ())
  • type SequenceA_Sym1 (a6989586621680439066 :: t6989586621680438462 (f6989586621680438463 a6989586621680438464)) = SequenceA_ a6989586621680439066
  • data AsumSym0 :: forall a6989586621680438458 f6989586621680438457 t6989586621680438456. (~>) (t6989586621680438456 (f6989586621680438457 a6989586621680438458)) (f6989586621680438457 a6989586621680438458)
  • type AsumSym1 (a6989586621680439051 :: t6989586621680438456 (f6989586621680438457 a6989586621680438458)) = Asum a6989586621680439051
  • data MapM_Sym0 :: forall a6989586621680438471 b6989586621680438472 m6989586621680438470 t6989586621680438469. (~>) ((~>) a6989586621680438471 (m6989586621680438470 b6989586621680438472)) ((~>) (t6989586621680438469 a6989586621680438471) (m6989586621680438470 ()))
  • data MapM_Sym1 (a6989586621680439069 :: (~>) a6989586621680438471 (m6989586621680438470 b6989586621680438472)) :: forall t6989586621680438469. (~>) (t6989586621680438469 a6989586621680438471) (m6989586621680438470 ())
  • type MapM_Sym2 (a6989586621680439069 :: (~>) a6989586621680438471 (m6989586621680438470 b6989586621680438472)) (a6989586621680439070 :: t6989586621680438469 a6989586621680438471) = MapM_ a6989586621680439069 a6989586621680439070
  • data ForM_Sym0 :: forall a6989586621680438467 b6989586621680438468 m6989586621680438466 t6989586621680438465. (~>) (t6989586621680438465 a6989586621680438467) ((~>) ((~>) a6989586621680438467 (m6989586621680438466 b6989586621680438468)) (m6989586621680438466 ()))
  • data ForM_Sym1 (a6989586621680439081 :: t6989586621680438465 a6989586621680438467) :: forall b6989586621680438468 m6989586621680438466. (~>) ((~>) a6989586621680438467 (m6989586621680438466 b6989586621680438468)) (m6989586621680438466 ())
  • type ForM_Sym2 (a6989586621680439081 :: t6989586621680438465 a6989586621680438467) (a6989586621680439082 :: (~>) a6989586621680438467 (m6989586621680438466 b6989586621680438468)) = ForM_ a6989586621680439081 a6989586621680439082
  • data Sequence_Sym0 :: forall a6989586621680438461 m6989586621680438460 t6989586621680438459. (~>) (t6989586621680438459 (m6989586621680438460 a6989586621680438461)) (m6989586621680438460 ())
  • type Sequence_Sym1 (a6989586621680439061 :: t6989586621680438459 (m6989586621680438460 a6989586621680438461)) = Sequence_ a6989586621680439061
  • data MsumSym0 :: forall a6989586621680438455 m6989586621680438454 t6989586621680438453. (~>) (t6989586621680438453 (m6989586621680438454 a6989586621680438455)) (m6989586621680438454 a6989586621680438455)
  • type MsumSym1 (a6989586621680439056 :: t6989586621680438453 (m6989586621680438454 a6989586621680438455)) = Msum a6989586621680439056
  • data ConcatSym0 :: forall a6989586621680438452 t6989586621680438451. (~>) (t6989586621680438451 [a6989586621680438452]) [a6989586621680438452]
  • type ConcatSym1 (a6989586621680439037 :: t6989586621680438451 [a6989586621680438452]) = Concat a6989586621680439037
  • data ConcatMapSym0 :: forall a6989586621680438449 b6989586621680438450 t6989586621680438448. (~>) ((~>) a6989586621680438449 [b6989586621680438450]) ((~>) (t6989586621680438448 a6989586621680438449) [b6989586621680438450])
  • data ConcatMapSym1 (a6989586621680439021 :: (~>) a6989586621680438449 [b6989586621680438450]) :: forall t6989586621680438448. (~>) (t6989586621680438448 a6989586621680438449) [b6989586621680438450]
  • type ConcatMapSym2 (a6989586621680439021 :: (~>) a6989586621680438449 [b6989586621680438450]) (a6989586621680439022 :: t6989586621680438448 a6989586621680438449) = ConcatMap a6989586621680439021 a6989586621680439022
  • data AndSym0 :: forall t6989586621680438447. (~>) (t6989586621680438447 Bool) Bool
  • type AndSym1 (a6989586621680439012 :: t6989586621680438447 Bool) = And a6989586621680439012
  • data OrSym0 :: forall t6989586621680438446. (~>) (t6989586621680438446 Bool) Bool
  • type OrSym1 (a6989586621680439003 :: t6989586621680438446 Bool) = Or a6989586621680439003
  • data AnySym0 :: forall a6989586621680438445 t6989586621680438444. (~>) ((~>) a6989586621680438445 Bool) ((~>) (t6989586621680438444 a6989586621680438445) Bool)
  • data AnySym1 (a6989586621680438990 :: (~>) a6989586621680438445 Bool) :: forall t6989586621680438444. (~>) (t6989586621680438444 a6989586621680438445) Bool
  • type AnySym2 (a6989586621680438990 :: (~>) a6989586621680438445 Bool) (a6989586621680438991 :: t6989586621680438444 a6989586621680438445) = Any a6989586621680438990 a6989586621680438991
  • data AllSym0 :: forall a6989586621680438443 t6989586621680438442. (~>) ((~>) a6989586621680438443 Bool) ((~>) (t6989586621680438442 a6989586621680438443) Bool)
  • data AllSym1 (a6989586621680438977 :: (~>) a6989586621680438443 Bool) :: forall t6989586621680438442. (~>) (t6989586621680438442 a6989586621680438443) Bool
  • type AllSym2 (a6989586621680438977 :: (~>) a6989586621680438443 Bool) (a6989586621680438978 :: t6989586621680438442 a6989586621680438443) = All a6989586621680438977 a6989586621680438978
  • data MaximumBySym0 :: forall a6989586621680438441 t6989586621680438440. (~>) ((~>) a6989586621680438441 ((~>) a6989586621680438441 Ordering)) ((~>) (t6989586621680438440 a6989586621680438441) a6989586621680438441)
  • data MaximumBySym1 (a6989586621680438952 :: (~>) a6989586621680438441 ((~>) a6989586621680438441 Ordering)) :: forall t6989586621680438440. (~>) (t6989586621680438440 a6989586621680438441) a6989586621680438441
  • type MaximumBySym2 (a6989586621680438952 :: (~>) a6989586621680438441 ((~>) a6989586621680438441 Ordering)) (a6989586621680438953 :: t6989586621680438440 a6989586621680438441) = MaximumBy a6989586621680438952 a6989586621680438953
  • data MinimumBySym0 :: forall a6989586621680438439 t6989586621680438438. (~>) ((~>) a6989586621680438439 ((~>) a6989586621680438439 Ordering)) ((~>) (t6989586621680438438 a6989586621680438439) a6989586621680438439)
  • data MinimumBySym1 (a6989586621680438927 :: (~>) a6989586621680438439 ((~>) a6989586621680438439 Ordering)) :: forall t6989586621680438438. (~>) (t6989586621680438438 a6989586621680438439) a6989586621680438439
  • type MinimumBySym2 (a6989586621680438927 :: (~>) a6989586621680438439 ((~>) a6989586621680438439 Ordering)) (a6989586621680438928 :: t6989586621680438438 a6989586621680438439) = MinimumBy a6989586621680438927 a6989586621680438928
  • data NotElemSym0 :: forall a6989586621680438437 t6989586621680438436. (~>) a6989586621680438437 ((~>) (t6989586621680438436 a6989586621680438437) Bool)
  • data NotElemSym1 (a6989586621680438919 :: a6989586621680438437) :: forall t6989586621680438436. (~>) (t6989586621680438436 a6989586621680438437) Bool
  • type NotElemSym2 (a6989586621680438919 :: a6989586621680438437) (a6989586621680438920 :: t6989586621680438436 a6989586621680438437) = NotElem a6989586621680438919 a6989586621680438920
  • data FindSym0 :: forall a6989586621680438435 t6989586621680438434. (~>) ((~>) a6989586621680438435 Bool) ((~>) (t6989586621680438434 a6989586621680438435) (Maybe a6989586621680438435))
  • data FindSym1 (a6989586621680438892 :: (~>) a6989586621680438435 Bool) :: forall t6989586621680438434. (~>) (t6989586621680438434 a6989586621680438435) (Maybe a6989586621680438435)
  • type FindSym2 (a6989586621680438892 :: (~>) a6989586621680438435 Bool) (a6989586621680438893 :: t6989586621680438434 a6989586621680438435) = Find a6989586621680438892 a6989586621680438893

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_6989586621680439211Sym0 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_6989586621680439224Sym0 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_6989586621680439248Sym0 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'_6989586621680439278Sym0 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_6989586621680439303Sym0 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'_6989586621680439333Sym0 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_6989586621680439359Sym0 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_6989586621680439384Sym0 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_6989586621680439394Sym0 t => Sing t -> Sing (Apply ToListSym0 t :: [a]) Source #

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

sLength :: forall a (t :: t a). (Apply LengthSym0 t :: Nat) ~ Apply Length_6989586621680439437Sym0 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_6989586621680439452Sym0 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_6989586621680439466Sym0 t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a) Source #

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

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

sProduct :: forall a (t :: t a). ((Apply ProductSym0 t :: a) ~ Apply Product_6989586621680439505Sym0 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 (Let6989586621680439136F'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 (Let6989586621680439114F'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_6989586621680439091 = Apply (Apply (Apply FoldrSym0 (Apply (Apply (.@#@$) (*>@#@$)) f)) (Apply PureSym0 Tuple0Sym0)) a_6989586621680439091 

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_6989586621680439095 a_6989586621680439097 = Apply (Apply (Apply FlipSym0 Traverse_Sym0) a_6989586621680439095) a_6989586621680439097 

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_6989586621680439064 = Apply (Apply (Apply FoldrSym0 (*>@#@$)) (Apply PureSym0 Tuple0Sym0)) a_6989586621680439064 

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_6989586621680439049 = Apply (Apply (Apply FoldrSym0 (<|>@#@$)) EmptySym0) a_6989586621680439049 

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_6989586621680439073 = Apply (Apply (Apply FoldrSym0 (Apply (Apply (.@#@$) (>>@#@$)) f)) (Apply ReturnSym0 Tuple0Sym0)) a_6989586621680439073 

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_6989586621680439077 a_6989586621680439079 = Apply (Apply (Apply FlipSym0 MapM_Sym0) a_6989586621680439077) a_6989586621680439079 

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_6989586621680439059 = Apply (Apply (Apply FoldrSym0 (>>@#@$)) (Apply ReturnSym0 Tuple0Sym0)) a_6989586621680439059 

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_6989586621680439054 = Apply AsumSym0 a_6989586621680439054 

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_6989586621680439040Sym0 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_6989586621680439027Sym0 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_6989586621680439017 x (Let6989586621680439015Scrutinee_6989586621680438773Sym1 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_6989586621680439008 x (Let6989586621680439006Scrutinee_6989586621680438775Sym1 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_6989586621680438999 p x (Let6989586621680438996Scrutinee_6989586621680438777Sym2 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_6989586621680438986 p x (Let6989586621680438983Scrutinee_6989586621680438779Sym2 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_6989586621680438956 = Apply (Apply Foldl1Sym0 (Let6989586621680438960Max'Sym2 cmp a_6989586621680438956)) a_6989586621680438956 

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_6989586621680438931 = Apply (Apply Foldl1Sym0 (Let6989586621680438935Min'Sym2 cmp a_6989586621680438931)) a_6989586621680438931 

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_6989586621680438923 = Apply (Apply (Apply (.@#@$) NotSym0) (Apply ElemSym0 x)) a_6989586621680438923 

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_6989586621680438915 p y (Let6989586621680438898Scrutinee_6989586621680438785Sym2 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 m6989586621680438527 t6989586621680438526. (~>) (t6989586621680438526 m6989586621680438527) m6989586621680438527 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 (t6989586621680438526 m6989586621680438527) m6989586621680438527 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type FoldSym1 (arg6989586621680439149 :: t6989586621680438526 m6989586621680438527) = Fold arg6989586621680439149 Source #

data FoldMapSym0 :: forall a6989586621680438529 m6989586621680438528 t6989586621680438526. (~>) ((~>) a6989586621680438529 m6989586621680438528) ((~>) (t6989586621680438526 a6989586621680438529) m6989586621680438528) 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 (a6989586621680438529 ~> m6989586621680438528) (t6989586621680438526 a6989586621680438529 ~> m6989586621680438528) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldMapSym0 :: TyFun (a6989586621680438529 ~> m6989586621680438528) (t6989586621680438526 a6989586621680438529 ~> m6989586621680438528) -> Type) (arg6989586621680439151 :: a6989586621680438529 ~> m6989586621680438528) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldMapSym0 :: TyFun (a6989586621680438529 ~> m6989586621680438528) (t6989586621680438526 a6989586621680438529 ~> m6989586621680438528) -> Type) (arg6989586621680439151 :: a6989586621680438529 ~> m6989586621680438528) = (FoldMapSym1 arg6989586621680439151 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438529) m6989586621680438528 -> Type)

data FoldMapSym1 (arg6989586621680439151 :: (~>) a6989586621680438529 m6989586621680438528) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438529) m6989586621680438528 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 arg6989586621680439151 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438529) m6989586621680438528 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldMapSym1 arg6989586621680439151 t :: TyFun (t a) m -> Type) (arg6989586621680439152 :: t a) = FoldMap arg6989586621680439151 arg6989586621680439152

type FoldMapSym2 (arg6989586621680439151 :: (~>) a6989586621680438529 m6989586621680438528) (arg6989586621680439152 :: t6989586621680438526 a6989586621680438529) = FoldMap arg6989586621680439151 arg6989586621680439152 Source #

data FoldrSym0 :: forall a6989586621680438530 b6989586621680438531 t6989586621680438526. (~>) ((~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) ((~>) b6989586621680438531 ((~>) (t6989586621680438526 a6989586621680438530) b6989586621680438531)) 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 (a6989586621680438530 ~> (b6989586621680438531 ~> b6989586621680438531)) (b6989586621680438531 ~> (t6989586621680438526 a6989586621680438530 ~> b6989586621680438531)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym0 :: TyFun (a6989586621680438530 ~> (b6989586621680438531 ~> b6989586621680438531)) (b6989586621680438531 ~> (t6989586621680438526 a6989586621680438530 ~> b6989586621680438531)) -> Type) (arg6989586621680439155 :: a6989586621680438530 ~> (b6989586621680438531 ~> b6989586621680438531)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym0 :: TyFun (a6989586621680438530 ~> (b6989586621680438531 ~> b6989586621680438531)) (b6989586621680438531 ~> (t6989586621680438526 a6989586621680438530 ~> b6989586621680438531)) -> Type) (arg6989586621680439155 :: a6989586621680438530 ~> (b6989586621680438531 ~> b6989586621680438531)) = (FoldrSym1 arg6989586621680439155 t6989586621680438526 :: TyFun b6989586621680438531 (t6989586621680438526 a6989586621680438530 ~> b6989586621680438531) -> Type)

data FoldrSym1 (arg6989586621680439155 :: (~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) :: forall t6989586621680438526. (~>) b6989586621680438531 ((~>) (t6989586621680438526 a6989586621680438530) b6989586621680438531) 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 arg6989586621680439155 t6989586621680438526 :: TyFun b6989586621680438531 (t6989586621680438526 a6989586621680438530 ~> b6989586621680438531) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym1 arg6989586621680439155 t6989586621680438526 :: TyFun b6989586621680438531 (t6989586621680438526 a6989586621680438530 ~> b6989586621680438531) -> Type) (arg6989586621680439156 :: b6989586621680438531) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym1 arg6989586621680439155 t6989586621680438526 :: TyFun b6989586621680438531 (t6989586621680438526 a6989586621680438530 ~> b6989586621680438531) -> Type) (arg6989586621680439156 :: b6989586621680438531) = (FoldrSym2 arg6989586621680439155 arg6989586621680439156 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438530) b6989586621680438531 -> Type)

data FoldrSym2 (arg6989586621680439155 :: (~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) (arg6989586621680439156 :: b6989586621680438531) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438530) b6989586621680438531 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 arg6989586621680439156 arg6989586621680439155 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438530) b6989586621680438531 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym2 arg6989586621680439156 arg6989586621680439155 t :: TyFun (t a) b -> Type) (arg6989586621680439157 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym2 arg6989586621680439156 arg6989586621680439155 t :: TyFun (t a) b -> Type) (arg6989586621680439157 :: t a) = Foldr arg6989586621680439156 arg6989586621680439155 arg6989586621680439157

type FoldrSym3 (arg6989586621680439155 :: (~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) (arg6989586621680439156 :: b6989586621680438531) (arg6989586621680439157 :: t6989586621680438526 a6989586621680438530) = Foldr arg6989586621680439155 arg6989586621680439156 arg6989586621680439157 Source #

data Foldr'Sym0 :: forall a6989586621680438532 b6989586621680438533 t6989586621680438526. (~>) ((~>) a6989586621680438532 ((~>) b6989586621680438533 b6989586621680438533)) ((~>) b6989586621680438533 ((~>) (t6989586621680438526 a6989586621680438532) b6989586621680438533)) 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 (a6989586621680438532 ~> (b6989586621680438533 ~> b6989586621680438533)) (b6989586621680438533 ~> (t6989586621680438526 a6989586621680438532 ~> b6989586621680438533)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr'Sym0 :: TyFun (a6989586621680438532 ~> (b6989586621680438533 ~> b6989586621680438533)) (b6989586621680438533 ~> (t6989586621680438526 a6989586621680438532 ~> b6989586621680438533)) -> Type) (arg6989586621680439161 :: a6989586621680438532 ~> (b6989586621680438533 ~> b6989586621680438533)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr'Sym0 :: TyFun (a6989586621680438532 ~> (b6989586621680438533 ~> b6989586621680438533)) (b6989586621680438533 ~> (t6989586621680438526 a6989586621680438532 ~> b6989586621680438533)) -> Type) (arg6989586621680439161 :: a6989586621680438532 ~> (b6989586621680438533 ~> b6989586621680438533)) = (Foldr'Sym1 arg6989586621680439161 t6989586621680438526 :: TyFun b6989586621680438533 (t6989586621680438526 a6989586621680438532 ~> b6989586621680438533) -> Type)

data Foldr'Sym1 (arg6989586621680439161 :: (~>) a6989586621680438532 ((~>) b6989586621680438533 b6989586621680438533)) :: forall t6989586621680438526. (~>) b6989586621680438533 ((~>) (t6989586621680438526 a6989586621680438532) b6989586621680438533) 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 arg6989586621680439161 t6989586621680438526 :: TyFun b6989586621680438533 (t6989586621680438526 a6989586621680438532 ~> b6989586621680438533) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr'Sym1 arg6989586621680439161 t6989586621680438526 :: TyFun b6989586621680438533 (t6989586621680438526 a6989586621680438532 ~> b6989586621680438533) -> Type) (arg6989586621680439162 :: b6989586621680438533) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr'Sym1 arg6989586621680439161 t6989586621680438526 :: TyFun b6989586621680438533 (t6989586621680438526 a6989586621680438532 ~> b6989586621680438533) -> Type) (arg6989586621680439162 :: b6989586621680438533) = (Foldr'Sym2 arg6989586621680439161 arg6989586621680439162 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438532) b6989586621680438533 -> Type)

data Foldr'Sym2 (arg6989586621680439161 :: (~>) a6989586621680438532 ((~>) b6989586621680438533 b6989586621680438533)) (arg6989586621680439162 :: b6989586621680438533) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438532) b6989586621680438533 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 arg6989586621680439162 arg6989586621680439161 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438532) b6989586621680438533 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr'Sym2 arg6989586621680439162 arg6989586621680439161 t :: TyFun (t a) b -> Type) (arg6989586621680439163 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr'Sym2 arg6989586621680439162 arg6989586621680439161 t :: TyFun (t a) b -> Type) (arg6989586621680439163 :: t a) = Foldr' arg6989586621680439162 arg6989586621680439161 arg6989586621680439163

type Foldr'Sym3 (arg6989586621680439161 :: (~>) a6989586621680438532 ((~>) b6989586621680438533 b6989586621680438533)) (arg6989586621680439162 :: b6989586621680438533) (arg6989586621680439163 :: t6989586621680438526 a6989586621680438532) = Foldr' arg6989586621680439161 arg6989586621680439162 arg6989586621680439163 Source #

data FoldlSym0 :: forall a6989586621680438535 b6989586621680438534 t6989586621680438526. (~>) ((~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) ((~>) b6989586621680438534 ((~>) (t6989586621680438526 a6989586621680438535) b6989586621680438534)) 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 (b6989586621680438534 ~> (a6989586621680438535 ~> b6989586621680438534)) (b6989586621680438534 ~> (t6989586621680438526 a6989586621680438535 ~> b6989586621680438534)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym0 :: TyFun (b6989586621680438534 ~> (a6989586621680438535 ~> b6989586621680438534)) (b6989586621680438534 ~> (t6989586621680438526 a6989586621680438535 ~> b6989586621680438534)) -> Type) (arg6989586621680439167 :: b6989586621680438534 ~> (a6989586621680438535 ~> b6989586621680438534)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym0 :: TyFun (b6989586621680438534 ~> (a6989586621680438535 ~> b6989586621680438534)) (b6989586621680438534 ~> (t6989586621680438526 a6989586621680438535 ~> b6989586621680438534)) -> Type) (arg6989586621680439167 :: b6989586621680438534 ~> (a6989586621680438535 ~> b6989586621680438534)) = (FoldlSym1 arg6989586621680439167 t6989586621680438526 :: TyFun b6989586621680438534 (t6989586621680438526 a6989586621680438535 ~> b6989586621680438534) -> Type)

data FoldlSym1 (arg6989586621680439167 :: (~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) :: forall t6989586621680438526. (~>) b6989586621680438534 ((~>) (t6989586621680438526 a6989586621680438535) b6989586621680438534) 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 arg6989586621680439167 t6989586621680438526 :: TyFun b6989586621680438534 (t6989586621680438526 a6989586621680438535 ~> b6989586621680438534) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym1 arg6989586621680439167 t6989586621680438526 :: TyFun b6989586621680438534 (t6989586621680438526 a6989586621680438535 ~> b6989586621680438534) -> Type) (arg6989586621680439168 :: b6989586621680438534) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym1 arg6989586621680439167 t6989586621680438526 :: TyFun b6989586621680438534 (t6989586621680438526 a6989586621680438535 ~> b6989586621680438534) -> Type) (arg6989586621680439168 :: b6989586621680438534) = (FoldlSym2 arg6989586621680439167 arg6989586621680439168 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438535) b6989586621680438534 -> Type)

data FoldlSym2 (arg6989586621680439167 :: (~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) (arg6989586621680439168 :: b6989586621680438534) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438535) b6989586621680438534 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 arg6989586621680439168 arg6989586621680439167 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438535) b6989586621680438534 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym2 arg6989586621680439168 arg6989586621680439167 t :: TyFun (t a) b -> Type) (arg6989586621680439169 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym2 arg6989586621680439168 arg6989586621680439167 t :: TyFun (t a) b -> Type) (arg6989586621680439169 :: t a) = Foldl arg6989586621680439168 arg6989586621680439167 arg6989586621680439169

type FoldlSym3 (arg6989586621680439167 :: (~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) (arg6989586621680439168 :: b6989586621680438534) (arg6989586621680439169 :: t6989586621680438526 a6989586621680438535) = Foldl arg6989586621680439167 arg6989586621680439168 arg6989586621680439169 Source #

data Foldl'Sym0 :: forall a6989586621680438537 b6989586621680438536 t6989586621680438526. (~>) ((~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) ((~>) b6989586621680438536 ((~>) (t6989586621680438526 a6989586621680438537) b6989586621680438536)) 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 (b6989586621680438536 ~> (a6989586621680438537 ~> b6989586621680438536)) (b6989586621680438536 ~> (t6989586621680438526 a6989586621680438537 ~> b6989586621680438536)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym0 :: TyFun (b6989586621680438536 ~> (a6989586621680438537 ~> b6989586621680438536)) (b6989586621680438536 ~> (t6989586621680438526 a6989586621680438537 ~> b6989586621680438536)) -> Type) (arg6989586621680439173 :: b6989586621680438536 ~> (a6989586621680438537 ~> b6989586621680438536)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym0 :: TyFun (b6989586621680438536 ~> (a6989586621680438537 ~> b6989586621680438536)) (b6989586621680438536 ~> (t6989586621680438526 a6989586621680438537 ~> b6989586621680438536)) -> Type) (arg6989586621680439173 :: b6989586621680438536 ~> (a6989586621680438537 ~> b6989586621680438536)) = (Foldl'Sym1 arg6989586621680439173 t6989586621680438526 :: TyFun b6989586621680438536 (t6989586621680438526 a6989586621680438537 ~> b6989586621680438536) -> Type)

data Foldl'Sym1 (arg6989586621680439173 :: (~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) :: forall t6989586621680438526. (~>) b6989586621680438536 ((~>) (t6989586621680438526 a6989586621680438537) b6989586621680438536) 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 arg6989586621680439173 t6989586621680438526 :: TyFun b6989586621680438536 (t6989586621680438526 a6989586621680438537 ~> b6989586621680438536) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym1 arg6989586621680439173 t6989586621680438526 :: TyFun b6989586621680438536 (t6989586621680438526 a6989586621680438537 ~> b6989586621680438536) -> Type) (arg6989586621680439174 :: b6989586621680438536) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym1 arg6989586621680439173 t6989586621680438526 :: TyFun b6989586621680438536 (t6989586621680438526 a6989586621680438537 ~> b6989586621680438536) -> Type) (arg6989586621680439174 :: b6989586621680438536) = (Foldl'Sym2 arg6989586621680439173 arg6989586621680439174 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438537) b6989586621680438536 -> Type)

data Foldl'Sym2 (arg6989586621680439173 :: (~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) (arg6989586621680439174 :: b6989586621680438536) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438537) b6989586621680438536 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 arg6989586621680439174 arg6989586621680439173 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438537) b6989586621680438536 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym2 arg6989586621680439174 arg6989586621680439173 t :: TyFun (t a) b -> Type) (arg6989586621680439175 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym2 arg6989586621680439174 arg6989586621680439173 t :: TyFun (t a) b -> Type) (arg6989586621680439175 :: t a) = Foldl' arg6989586621680439174 arg6989586621680439173 arg6989586621680439175

type Foldl'Sym3 (arg6989586621680439173 :: (~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) (arg6989586621680439174 :: b6989586621680438536) (arg6989586621680439175 :: t6989586621680438526 a6989586621680438537) = Foldl' arg6989586621680439173 arg6989586621680439174 arg6989586621680439175 Source #

data Foldr1Sym0 :: forall a6989586621680438538 t6989586621680438526. (~>) ((~>) a6989586621680438538 ((~>) a6989586621680438538 a6989586621680438538)) ((~>) (t6989586621680438526 a6989586621680438538) a6989586621680438538) 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 (a6989586621680438538 ~> (a6989586621680438538 ~> a6989586621680438538)) (t6989586621680438526 a6989586621680438538 ~> a6989586621680438538) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr1Sym0 :: TyFun (a6989586621680438538 ~> (a6989586621680438538 ~> a6989586621680438538)) (t6989586621680438526 a6989586621680438538 ~> a6989586621680438538) -> Type) (arg6989586621680439179 :: a6989586621680438538 ~> (a6989586621680438538 ~> a6989586621680438538)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr1Sym0 :: TyFun (a6989586621680438538 ~> (a6989586621680438538 ~> a6989586621680438538)) (t6989586621680438526 a6989586621680438538 ~> a6989586621680438538) -> Type) (arg6989586621680439179 :: a6989586621680438538 ~> (a6989586621680438538 ~> a6989586621680438538)) = (Foldr1Sym1 arg6989586621680439179 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438538) a6989586621680438538 -> Type)

data Foldr1Sym1 (arg6989586621680439179 :: (~>) a6989586621680438538 ((~>) a6989586621680438538 a6989586621680438538)) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438538) a6989586621680438538 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 arg6989586621680439179 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438538) a6989586621680438538 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr1Sym1 arg6989586621680439179 t :: TyFun (t a) a -> Type) (arg6989586621680439180 :: t a) = Foldr1 arg6989586621680439179 arg6989586621680439180

type Foldr1Sym2 (arg6989586621680439179 :: (~>) a6989586621680438538 ((~>) a6989586621680438538 a6989586621680438538)) (arg6989586621680439180 :: t6989586621680438526 a6989586621680438538) = Foldr1 arg6989586621680439179 arg6989586621680439180 Source #

data Foldl1Sym0 :: forall a6989586621680438539 t6989586621680438526. (~>) ((~>) a6989586621680438539 ((~>) a6989586621680438539 a6989586621680438539)) ((~>) (t6989586621680438526 a6989586621680438539) a6989586621680438539) 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 (a6989586621680438539 ~> (a6989586621680438539 ~> a6989586621680438539)) (t6989586621680438526 a6989586621680438539 ~> a6989586621680438539) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl1Sym0 :: TyFun (a6989586621680438539 ~> (a6989586621680438539 ~> a6989586621680438539)) (t6989586621680438526 a6989586621680438539 ~> a6989586621680438539) -> Type) (arg6989586621680439183 :: a6989586621680438539 ~> (a6989586621680438539 ~> a6989586621680438539)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl1Sym0 :: TyFun (a6989586621680438539 ~> (a6989586621680438539 ~> a6989586621680438539)) (t6989586621680438526 a6989586621680438539 ~> a6989586621680438539) -> Type) (arg6989586621680439183 :: a6989586621680438539 ~> (a6989586621680438539 ~> a6989586621680438539)) = (Foldl1Sym1 arg6989586621680439183 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438539) a6989586621680438539 -> Type)

data Foldl1Sym1 (arg6989586621680439183 :: (~>) a6989586621680438539 ((~>) a6989586621680438539 a6989586621680438539)) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438539) a6989586621680438539 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 arg6989586621680439183 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438539) a6989586621680438539 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl1Sym1 arg6989586621680439183 t :: TyFun (t a) a -> Type) (arg6989586621680439184 :: t a) = Foldl1 arg6989586621680439183 arg6989586621680439184

type Foldl1Sym2 (arg6989586621680439183 :: (~>) a6989586621680438539 ((~>) a6989586621680438539 a6989586621680438539)) (arg6989586621680439184 :: t6989586621680438526 a6989586621680438539) = Foldl1 arg6989586621680439183 arg6989586621680439184 Source #

data ToListSym0 :: forall a6989586621680438540 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438540) [a6989586621680438540] Source #

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ToListSym0 :: TyFun (t6989586621680438526 a6989586621680438540) [a6989586621680438540] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type ToListSym1 (arg6989586621680439187 :: t6989586621680438526 a6989586621680438540) = ToList arg6989586621680439187 Source #

data NullSym0 :: forall a6989586621680438541 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438541) Bool Source #

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (NullSym0 :: TyFun (t6989586621680438526 a6989586621680438541) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type NullSym1 (arg6989586621680439189 :: t6989586621680438526 a6989586621680438541) = Null arg6989586621680439189 Source #

data LengthSym0 :: forall a6989586621680438542 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438542) Nat Source #

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (LengthSym0 :: TyFun (t6989586621680438526 a6989586621680438542) Nat -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type LengthSym1 (arg6989586621680439191 :: t6989586621680438526 a6989586621680438542) = Length arg6989586621680439191 Source #

data ElemSym0 :: forall a6989586621680438543 t6989586621680438526. (~>) a6989586621680438543 ((~>) (t6989586621680438526 a6989586621680438543) 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 a6989586621680438543 (t6989586621680438526 a6989586621680438543 ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym0 :: TyFun a6989586621680438543 (t6989586621680438526 a6989586621680438543 ~> Bool) -> Type) (arg6989586621680439193 :: a6989586621680438543) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym0 :: TyFun a6989586621680438543 (t6989586621680438526 a6989586621680438543 ~> Bool) -> Type) (arg6989586621680439193 :: a6989586621680438543) = (ElemSym1 arg6989586621680439193 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438543) Bool -> Type)

data ElemSym1 (arg6989586621680439193 :: a6989586621680438543) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438543) 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 arg6989586621680439193 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438543) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym1 arg6989586621680439193 t :: TyFun (t a) Bool -> Type) (arg6989586621680439194 :: t a) = Elem arg6989586621680439193 arg6989586621680439194

type ElemSym2 (arg6989586621680439193 :: a6989586621680438543) (arg6989586621680439194 :: t6989586621680438526 a6989586621680438543) = Elem arg6989586621680439193 arg6989586621680439194 Source #

data MaximumSym0 :: forall a6989586621680438544 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438544) a6989586621680438544 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 (t6989586621680438526 a6989586621680438544) a6989586621680438544 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type MaximumSym1 (arg6989586621680439197 :: t6989586621680438526 a6989586621680438544) = Maximum arg6989586621680439197 Source #

data MinimumSym0 :: forall a6989586621680438545 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438545) a6989586621680438545 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 (t6989586621680438526 a6989586621680438545) a6989586621680438545 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type MinimumSym1 (arg6989586621680439199 :: t6989586621680438526 a6989586621680438545) = Minimum arg6989586621680439199 Source #

data SumSym0 :: forall a6989586621680438546 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438546) a6989586621680438546 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 (t6989586621680438526 a6989586621680438546) a6989586621680438546 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type SumSym1 (arg6989586621680439201 :: t6989586621680438526 a6989586621680438546) = Sum arg6989586621680439201 Source #

data ProductSym0 :: forall a6989586621680438547 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438547) a6989586621680438547 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 (t6989586621680438526 a6989586621680438547) a6989586621680438547 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type ProductSym1 (arg6989586621680439203 :: t6989586621680438526 a6989586621680438547) = Product arg6989586621680439203 Source #

data FoldrMSym0 :: forall a6989586621680438487 b6989586621680438488 m6989586621680438486 t6989586621680438485. (~>) ((~>) a6989586621680438487 ((~>) b6989586621680438488 (m6989586621680438486 b6989586621680438488))) ((~>) b6989586621680438488 ((~>) (t6989586621680438485 a6989586621680438487) (m6989586621680438486 b6989586621680438488))) 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 (a6989586621680438487 ~> (b6989586621680438488 ~> m6989586621680438486 b6989586621680438488)) (b6989586621680438488 ~> (t6989586621680438485 a6989586621680438487 ~> m6989586621680438486 b6989586621680438488)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrMSym0 :: TyFun (a6989586621680438487 ~> (b6989586621680438488 ~> m6989586621680438486 b6989586621680438488)) (b6989586621680438488 ~> (t6989586621680438485 a6989586621680438487 ~> m6989586621680438486 b6989586621680438488)) -> Type) (a6989586621680439127 :: a6989586621680438487 ~> (b6989586621680438488 ~> m6989586621680438486 b6989586621680438488)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrMSym0 :: TyFun (a6989586621680438487 ~> (b6989586621680438488 ~> m6989586621680438486 b6989586621680438488)) (b6989586621680438488 ~> (t6989586621680438485 a6989586621680438487 ~> m6989586621680438486 b6989586621680438488)) -> Type) (a6989586621680439127 :: a6989586621680438487 ~> (b6989586621680438488 ~> m6989586621680438486 b6989586621680438488)) = (FoldrMSym1 a6989586621680439127 t6989586621680438485 :: TyFun b6989586621680438488 (t6989586621680438485 a6989586621680438487 ~> m6989586621680438486 b6989586621680438488) -> Type)

data FoldrMSym1 (a6989586621680439127 :: (~>) a6989586621680438487 ((~>) b6989586621680438488 (m6989586621680438486 b6989586621680438488))) :: forall t6989586621680438485. (~>) b6989586621680438488 ((~>) (t6989586621680438485 a6989586621680438487) (m6989586621680438486 b6989586621680438488)) 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 a6989586621680439127 t6989586621680438485 :: TyFun b6989586621680438488 (t6989586621680438485 a6989586621680438487 ~> m6989586621680438486 b6989586621680438488) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrMSym1 a6989586621680439127 t6989586621680438485 :: TyFun b6989586621680438488 (t6989586621680438485 a6989586621680438487 ~> m6989586621680438486 b6989586621680438488) -> Type) (a6989586621680439128 :: b6989586621680438488) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrMSym1 a6989586621680439127 t6989586621680438485 :: TyFun b6989586621680438488 (t6989586621680438485 a6989586621680438487 ~> m6989586621680438486 b6989586621680438488) -> Type) (a6989586621680439128 :: b6989586621680438488) = (FoldrMSym2 a6989586621680439127 a6989586621680439128 t6989586621680438485 :: TyFun (t6989586621680438485 a6989586621680438487) (m6989586621680438486 b6989586621680438488) -> Type)

data FoldrMSym2 (a6989586621680439127 :: (~>) a6989586621680438487 ((~>) b6989586621680438488 (m6989586621680438486 b6989586621680438488))) (a6989586621680439128 :: b6989586621680438488) :: forall t6989586621680438485. (~>) (t6989586621680438485 a6989586621680438487) (m6989586621680438486 b6989586621680438488) 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 a6989586621680439128 a6989586621680439127 t6989586621680438485 :: TyFun (t6989586621680438485 a6989586621680438487) (m6989586621680438486 b6989586621680438488) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrMSym2 a6989586621680439128 a6989586621680439127 t :: TyFun (t a) (m b) -> Type) (a6989586621680439129 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrMSym2 a6989586621680439128 a6989586621680439127 t :: TyFun (t a) (m b) -> Type) (a6989586621680439129 :: t a) = FoldrM a6989586621680439128 a6989586621680439127 a6989586621680439129

type FoldrMSym3 (a6989586621680439127 :: (~>) a6989586621680438487 ((~>) b6989586621680438488 (m6989586621680438486 b6989586621680438488))) (a6989586621680439128 :: b6989586621680438488) (a6989586621680439129 :: t6989586621680438485 a6989586621680438487) = FoldrM a6989586621680439127 a6989586621680439128 a6989586621680439129 Source #

data FoldlMSym0 :: forall a6989586621680438484 b6989586621680438483 m6989586621680438482 t6989586621680438481. (~>) ((~>) b6989586621680438483 ((~>) a6989586621680438484 (m6989586621680438482 b6989586621680438483))) ((~>) b6989586621680438483 ((~>) (t6989586621680438481 a6989586621680438484) (m6989586621680438482 b6989586621680438483))) 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 (b6989586621680438483 ~> (a6989586621680438484 ~> m6989586621680438482 b6989586621680438483)) (b6989586621680438483 ~> (t6989586621680438481 a6989586621680438484 ~> m6989586621680438482 b6989586621680438483)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlMSym0 :: TyFun (b6989586621680438483 ~> (a6989586621680438484 ~> m6989586621680438482 b6989586621680438483)) (b6989586621680438483 ~> (t6989586621680438481 a6989586621680438484 ~> m6989586621680438482 b6989586621680438483)) -> Type) (a6989586621680439105 :: b6989586621680438483 ~> (a6989586621680438484 ~> m6989586621680438482 b6989586621680438483)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlMSym0 :: TyFun (b6989586621680438483 ~> (a6989586621680438484 ~> m6989586621680438482 b6989586621680438483)) (b6989586621680438483 ~> (t6989586621680438481 a6989586621680438484 ~> m6989586621680438482 b6989586621680438483)) -> Type) (a6989586621680439105 :: b6989586621680438483 ~> (a6989586621680438484 ~> m6989586621680438482 b6989586621680438483)) = (FoldlMSym1 a6989586621680439105 t6989586621680438481 :: TyFun b6989586621680438483 (t6989586621680438481 a6989586621680438484 ~> m6989586621680438482 b6989586621680438483) -> Type)

data FoldlMSym1 (a6989586621680439105 :: (~>) b6989586621680438483 ((~>) a6989586621680438484 (m6989586621680438482 b6989586621680438483))) :: forall t6989586621680438481. (~>) b6989586621680438483 ((~>) (t6989586621680438481 a6989586621680438484) (m6989586621680438482 b6989586621680438483)) 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 a6989586621680439105 t6989586621680438481 :: TyFun b6989586621680438483 (t6989586621680438481 a6989586621680438484 ~> m6989586621680438482 b6989586621680438483) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlMSym1 a6989586621680439105 t6989586621680438481 :: TyFun b6989586621680438483 (t6989586621680438481 a6989586621680438484 ~> m6989586621680438482 b6989586621680438483) -> Type) (a6989586621680439106 :: b6989586621680438483) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlMSym1 a6989586621680439105 t6989586621680438481 :: TyFun b6989586621680438483 (t6989586621680438481 a6989586621680438484 ~> m6989586621680438482 b6989586621680438483) -> Type) (a6989586621680439106 :: b6989586621680438483) = (FoldlMSym2 a6989586621680439105 a6989586621680439106 t6989586621680438481 :: TyFun (t6989586621680438481 a6989586621680438484) (m6989586621680438482 b6989586621680438483) -> Type)

data FoldlMSym2 (a6989586621680439105 :: (~>) b6989586621680438483 ((~>) a6989586621680438484 (m6989586621680438482 b6989586621680438483))) (a6989586621680439106 :: b6989586621680438483) :: forall t6989586621680438481. (~>) (t6989586621680438481 a6989586621680438484) (m6989586621680438482 b6989586621680438483) 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 a6989586621680439106 a6989586621680439105 t6989586621680438481 :: TyFun (t6989586621680438481 a6989586621680438484) (m6989586621680438482 b6989586621680438483) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlMSym2 a6989586621680439106 a6989586621680439105 t :: TyFun (t a) (m b) -> Type) (a6989586621680439107 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlMSym2 a6989586621680439106 a6989586621680439105 t :: TyFun (t a) (m b) -> Type) (a6989586621680439107 :: t a) = FoldlM a6989586621680439106 a6989586621680439105 a6989586621680439107

type FoldlMSym3 (a6989586621680439105 :: (~>) b6989586621680438483 ((~>) a6989586621680438484 (m6989586621680438482 b6989586621680438483))) (a6989586621680439106 :: b6989586621680438483) (a6989586621680439107 :: t6989586621680438481 a6989586621680438484) = FoldlM a6989586621680439105 a6989586621680439106 a6989586621680439107 Source #

data Traverse_Sym0 :: forall a6989586621680438479 b6989586621680438480 f6989586621680438478 t6989586621680438477. (~>) ((~>) a6989586621680438479 (f6989586621680438478 b6989586621680438480)) ((~>) (t6989586621680438477 a6989586621680438479) (f6989586621680438478 ())) 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 (a6989586621680438479 ~> f6989586621680438478 b6989586621680438480) (t6989586621680438477 a6989586621680438479 ~> f6989586621680438478 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Traverse_Sym0 :: TyFun (a6989586621680438479 ~> f6989586621680438478 b6989586621680438480) (t6989586621680438477 a6989586621680438479 ~> f6989586621680438478 ()) -> Type) (a6989586621680439087 :: a6989586621680438479 ~> f6989586621680438478 b6989586621680438480) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Traverse_Sym0 :: TyFun (a6989586621680438479 ~> f6989586621680438478 b6989586621680438480) (t6989586621680438477 a6989586621680438479 ~> f6989586621680438478 ()) -> Type) (a6989586621680439087 :: a6989586621680438479 ~> f6989586621680438478 b6989586621680438480) = (Traverse_Sym1 a6989586621680439087 t6989586621680438477 :: TyFun (t6989586621680438477 a6989586621680438479) (f6989586621680438478 ()) -> Type)

data Traverse_Sym1 (a6989586621680439087 :: (~>) a6989586621680438479 (f6989586621680438478 b6989586621680438480)) :: forall t6989586621680438477. (~>) (t6989586621680438477 a6989586621680438479) (f6989586621680438478 ()) 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 a6989586621680439087 t6989586621680438477 :: TyFun (t6989586621680438477 a6989586621680438479) (f6989586621680438478 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Apply (Traverse_Sym1 a6989586621680439087 t :: TyFun (t a) (f ()) -> Type) (a6989586621680439088 :: t a) = Traverse_ a6989586621680439087 a6989586621680439088

type Traverse_Sym2 (a6989586621680439087 :: (~>) a6989586621680438479 (f6989586621680438478 b6989586621680438480)) (a6989586621680439088 :: t6989586621680438477 a6989586621680438479) = Traverse_ a6989586621680439087 a6989586621680439088 Source #

data For_Sym0 :: forall a6989586621680438475 b6989586621680438476 f6989586621680438474 t6989586621680438473. (~>) (t6989586621680438473 a6989586621680438475) ((~>) ((~>) a6989586621680438475 (f6989586621680438474 b6989586621680438476)) (f6989586621680438474 ())) 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 (t6989586621680438473 a6989586621680438475) ((a6989586621680438475 ~> f6989586621680438474 b6989586621680438476) ~> f6989586621680438474 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (For_Sym0 :: TyFun (t6989586621680438473 a6989586621680438475) ((a6989586621680438475 ~> f6989586621680438474 b6989586621680438476) ~> f6989586621680438474 ()) -> Type) (a6989586621680439099 :: t6989586621680438473 a6989586621680438475) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (For_Sym0 :: TyFun (t6989586621680438473 a6989586621680438475) ((a6989586621680438475 ~> f6989586621680438474 b6989586621680438476) ~> f6989586621680438474 ()) -> Type) (a6989586621680439099 :: t6989586621680438473 a6989586621680438475) = (For_Sym1 a6989586621680439099 b6989586621680438476 f6989586621680438474 :: TyFun (a6989586621680438475 ~> f6989586621680438474 b6989586621680438476) (f6989586621680438474 ()) -> Type)

data For_Sym1 (a6989586621680439099 :: t6989586621680438473 a6989586621680438475) :: forall b6989586621680438476 f6989586621680438474. (~>) ((~>) a6989586621680438475 (f6989586621680438474 b6989586621680438476)) (f6989586621680438474 ()) 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 a6989586621680439099 b6989586621680438476 f6989586621680438474 :: TyFun (a6989586621680438475 ~> f6989586621680438474 b6989586621680438476) (f6989586621680438474 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type For_Sym2 (a6989586621680439099 :: t6989586621680438473 a6989586621680438475) (a6989586621680439100 :: (~>) a6989586621680438475 (f6989586621680438474 b6989586621680438476)) = For_ a6989586621680439099 a6989586621680439100 Source #

data SequenceA_Sym0 :: forall a6989586621680438464 f6989586621680438463 t6989586621680438462. (~>) (t6989586621680438462 (f6989586621680438463 a6989586621680438464)) (f6989586621680438463 ()) 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 (t6989586621680438462 (f6989586621680438463 a6989586621680438464)) (f6989586621680438463 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type SequenceA_Sym1 (a6989586621680439066 :: t6989586621680438462 (f6989586621680438463 a6989586621680438464)) = SequenceA_ a6989586621680439066 Source #

data AsumSym0 :: forall a6989586621680438458 f6989586621680438457 t6989586621680438456. (~>) (t6989586621680438456 (f6989586621680438457 a6989586621680438458)) (f6989586621680438457 a6989586621680438458) 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 (t6989586621680438456 (f6989586621680438457 a6989586621680438458)) (f6989586621680438457 a6989586621680438458) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type AsumSym1 (a6989586621680439051 :: t6989586621680438456 (f6989586621680438457 a6989586621680438458)) = Asum a6989586621680439051 Source #

data MapM_Sym0 :: forall a6989586621680438471 b6989586621680438472 m6989586621680438470 t6989586621680438469. (~>) ((~>) a6989586621680438471 (m6989586621680438470 b6989586621680438472)) ((~>) (t6989586621680438469 a6989586621680438471) (m6989586621680438470 ())) 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 (a6989586621680438471 ~> m6989586621680438470 b6989586621680438472) (t6989586621680438469 a6989586621680438471 ~> m6989586621680438470 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MapM_Sym0 :: TyFun (a6989586621680438471 ~> m6989586621680438470 b6989586621680438472) (t6989586621680438469 a6989586621680438471 ~> m6989586621680438470 ()) -> Type) (a6989586621680439069 :: a6989586621680438471 ~> m6989586621680438470 b6989586621680438472) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MapM_Sym0 :: TyFun (a6989586621680438471 ~> m6989586621680438470 b6989586621680438472) (t6989586621680438469 a6989586621680438471 ~> m6989586621680438470 ()) -> Type) (a6989586621680439069 :: a6989586621680438471 ~> m6989586621680438470 b6989586621680438472) = (MapM_Sym1 a6989586621680439069 t6989586621680438469 :: TyFun (t6989586621680438469 a6989586621680438471) (m6989586621680438470 ()) -> Type)

data MapM_Sym1 (a6989586621680439069 :: (~>) a6989586621680438471 (m6989586621680438470 b6989586621680438472)) :: forall t6989586621680438469. (~>) (t6989586621680438469 a6989586621680438471) (m6989586621680438470 ()) 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 a6989586621680439069 t6989586621680438469 :: TyFun (t6989586621680438469 a6989586621680438471) (m6989586621680438470 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Apply (MapM_Sym1 a6989586621680439069 t :: TyFun (t a) (m ()) -> Type) (a6989586621680439070 :: t a) = MapM_ a6989586621680439069 a6989586621680439070

type MapM_Sym2 (a6989586621680439069 :: (~>) a6989586621680438471 (m6989586621680438470 b6989586621680438472)) (a6989586621680439070 :: t6989586621680438469 a6989586621680438471) = MapM_ a6989586621680439069 a6989586621680439070 Source #

data ForM_Sym0 :: forall a6989586621680438467 b6989586621680438468 m6989586621680438466 t6989586621680438465. (~>) (t6989586621680438465 a6989586621680438467) ((~>) ((~>) a6989586621680438467 (m6989586621680438466 b6989586621680438468)) (m6989586621680438466 ())) 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 (t6989586621680438465 a6989586621680438467) ((a6989586621680438467 ~> m6989586621680438466 b6989586621680438468) ~> m6989586621680438466 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ForM_Sym0 :: TyFun (t6989586621680438465 a6989586621680438467) ((a6989586621680438467 ~> m6989586621680438466 b6989586621680438468) ~> m6989586621680438466 ()) -> Type) (a6989586621680439081 :: t6989586621680438465 a6989586621680438467) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ForM_Sym0 :: TyFun (t6989586621680438465 a6989586621680438467) ((a6989586621680438467 ~> m6989586621680438466 b6989586621680438468) ~> m6989586621680438466 ()) -> Type) (a6989586621680439081 :: t6989586621680438465 a6989586621680438467) = (ForM_Sym1 a6989586621680439081 b6989586621680438468 m6989586621680438466 :: TyFun (a6989586621680438467 ~> m6989586621680438466 b6989586621680438468) (m6989586621680438466 ()) -> Type)

data ForM_Sym1 (a6989586621680439081 :: t6989586621680438465 a6989586621680438467) :: forall b6989586621680438468 m6989586621680438466. (~>) ((~>) a6989586621680438467 (m6989586621680438466 b6989586621680438468)) (m6989586621680438466 ()) 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 a6989586621680439081 b6989586621680438468 m6989586621680438466 :: TyFun (a6989586621680438467 ~> m6989586621680438466 b6989586621680438468) (m6989586621680438466 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type ForM_Sym2 (a6989586621680439081 :: t6989586621680438465 a6989586621680438467) (a6989586621680439082 :: (~>) a6989586621680438467 (m6989586621680438466 b6989586621680438468)) = ForM_ a6989586621680439081 a6989586621680439082 Source #

data Sequence_Sym0 :: forall a6989586621680438461 m6989586621680438460 t6989586621680438459. (~>) (t6989586621680438459 (m6989586621680438460 a6989586621680438461)) (m6989586621680438460 ()) 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 (t6989586621680438459 (m6989586621680438460 a6989586621680438461)) (m6989586621680438460 ()) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type Sequence_Sym1 (a6989586621680439061 :: t6989586621680438459 (m6989586621680438460 a6989586621680438461)) = Sequence_ a6989586621680439061 Source #

data MsumSym0 :: forall a6989586621680438455 m6989586621680438454 t6989586621680438453. (~>) (t6989586621680438453 (m6989586621680438454 a6989586621680438455)) (m6989586621680438454 a6989586621680438455) 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 (t6989586621680438453 (m6989586621680438454 a6989586621680438455)) (m6989586621680438454 a6989586621680438455) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type MsumSym1 (a6989586621680439056 :: t6989586621680438453 (m6989586621680438454 a6989586621680438455)) = Msum a6989586621680439056 Source #

data ConcatSym0 :: forall a6989586621680438452 t6989586621680438451. (~>) (t6989586621680438451 [a6989586621680438452]) [a6989586621680438452] Source #

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ConcatSym0 :: TyFun (t6989586621680438451 [a6989586621680438452]) [a6989586621680438452] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type ConcatSym1 (a6989586621680439037 :: t6989586621680438451 [a6989586621680438452]) = Concat a6989586621680439037 Source #

data ConcatMapSym0 :: forall a6989586621680438449 b6989586621680438450 t6989586621680438448. (~>) ((~>) a6989586621680438449 [b6989586621680438450]) ((~>) (t6989586621680438448 a6989586621680438449) [b6989586621680438450]) 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 (a6989586621680438449 ~> [b6989586621680438450]) (t6989586621680438448 a6989586621680438449 ~> [b6989586621680438450]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ConcatMapSym0 :: TyFun (a6989586621680438449 ~> [b6989586621680438450]) (t6989586621680438448 a6989586621680438449 ~> [b6989586621680438450]) -> Type) (a6989586621680439021 :: a6989586621680438449 ~> [b6989586621680438450]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ConcatMapSym0 :: TyFun (a6989586621680438449 ~> [b6989586621680438450]) (t6989586621680438448 a6989586621680438449 ~> [b6989586621680438450]) -> Type) (a6989586621680439021 :: a6989586621680438449 ~> [b6989586621680438450]) = (ConcatMapSym1 a6989586621680439021 t6989586621680438448 :: TyFun (t6989586621680438448 a6989586621680438449) [b6989586621680438450] -> Type)

data ConcatMapSym1 (a6989586621680439021 :: (~>) a6989586621680438449 [b6989586621680438450]) :: forall t6989586621680438448. (~>) (t6989586621680438448 a6989586621680438449) [b6989586621680438450] 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 a6989586621680439021 t6989586621680438448 :: TyFun (t6989586621680438448 a6989586621680438449) [b6989586621680438450] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type ConcatMapSym2 (a6989586621680439021 :: (~>) a6989586621680438449 [b6989586621680438450]) (a6989586621680439022 :: t6989586621680438448 a6989586621680438449) = ConcatMap a6989586621680439021 a6989586621680439022 Source #

data AndSym0 :: forall t6989586621680438447. (~>) (t6989586621680438447 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 (t6989586621680438447 Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type AndSym1 (a6989586621680439012 :: t6989586621680438447 Bool) = And a6989586621680439012 Source #

data OrSym0 :: forall t6989586621680438446. (~>) (t6989586621680438446 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 (t6989586621680438446 Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type OrSym1 (a6989586621680439003 :: t6989586621680438446 Bool) = Or a6989586621680439003 Source #

data AnySym0 :: forall a6989586621680438445 t6989586621680438444. (~>) ((~>) a6989586621680438445 Bool) ((~>) (t6989586621680438444 a6989586621680438445) 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 (a6989586621680438445 ~> Bool) (t6989586621680438444 a6989586621680438445 ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym0 :: TyFun (a6989586621680438445 ~> Bool) (t6989586621680438444 a6989586621680438445 ~> Bool) -> Type) (a6989586621680438990 :: a6989586621680438445 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym0 :: TyFun (a6989586621680438445 ~> Bool) (t6989586621680438444 a6989586621680438445 ~> Bool) -> Type) (a6989586621680438990 :: a6989586621680438445 ~> Bool) = (AnySym1 a6989586621680438990 t6989586621680438444 :: TyFun (t6989586621680438444 a6989586621680438445) Bool -> Type)

data AnySym1 (a6989586621680438990 :: (~>) a6989586621680438445 Bool) :: forall t6989586621680438444. (~>) (t6989586621680438444 a6989586621680438445) 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 a6989586621680438990 t6989586621680438444 :: TyFun (t6989586621680438444 a6989586621680438445) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym1 a6989586621680438990 t :: TyFun (t a) Bool -> Type) (a6989586621680438991 :: t a) = Any a6989586621680438990 a6989586621680438991

type AnySym2 (a6989586621680438990 :: (~>) a6989586621680438445 Bool) (a6989586621680438991 :: t6989586621680438444 a6989586621680438445) = Any a6989586621680438990 a6989586621680438991 Source #

data AllSym0 :: forall a6989586621680438443 t6989586621680438442. (~>) ((~>) a6989586621680438443 Bool) ((~>) (t6989586621680438442 a6989586621680438443) 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 (a6989586621680438443 ~> Bool) (t6989586621680438442 a6989586621680438443 ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym0 :: TyFun (a6989586621680438443 ~> Bool) (t6989586621680438442 a6989586621680438443 ~> Bool) -> Type) (a6989586621680438977 :: a6989586621680438443 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym0 :: TyFun (a6989586621680438443 ~> Bool) (t6989586621680438442 a6989586621680438443 ~> Bool) -> Type) (a6989586621680438977 :: a6989586621680438443 ~> Bool) = (AllSym1 a6989586621680438977 t6989586621680438442 :: TyFun (t6989586621680438442 a6989586621680438443) Bool -> Type)

data AllSym1 (a6989586621680438977 :: (~>) a6989586621680438443 Bool) :: forall t6989586621680438442. (~>) (t6989586621680438442 a6989586621680438443) 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 a6989586621680438977 t6989586621680438442 :: TyFun (t6989586621680438442 a6989586621680438443) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym1 a6989586621680438977 t :: TyFun (t a) Bool -> Type) (a6989586621680438978 :: t a) = All a6989586621680438977 a6989586621680438978

type AllSym2 (a6989586621680438977 :: (~>) a6989586621680438443 Bool) (a6989586621680438978 :: t6989586621680438442 a6989586621680438443) = All a6989586621680438977 a6989586621680438978 Source #

data MaximumBySym0 :: forall a6989586621680438441 t6989586621680438440. (~>) ((~>) a6989586621680438441 ((~>) a6989586621680438441 Ordering)) ((~>) (t6989586621680438440 a6989586621680438441) a6989586621680438441) 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 (a6989586621680438441 ~> (a6989586621680438441 ~> Ordering)) (t6989586621680438440 a6989586621680438441 ~> a6989586621680438441) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaximumBySym0 :: TyFun (a6989586621680438441 ~> (a6989586621680438441 ~> Ordering)) (t6989586621680438440 a6989586621680438441 ~> a6989586621680438441) -> Type) (a6989586621680438952 :: a6989586621680438441 ~> (a6989586621680438441 ~> Ordering)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaximumBySym0 :: TyFun (a6989586621680438441 ~> (a6989586621680438441 ~> Ordering)) (t6989586621680438440 a6989586621680438441 ~> a6989586621680438441) -> Type) (a6989586621680438952 :: a6989586621680438441 ~> (a6989586621680438441 ~> Ordering)) = (MaximumBySym1 a6989586621680438952 t6989586621680438440 :: TyFun (t6989586621680438440 a6989586621680438441) a6989586621680438441 -> Type)

data MaximumBySym1 (a6989586621680438952 :: (~>) a6989586621680438441 ((~>) a6989586621680438441 Ordering)) :: forall t6989586621680438440. (~>) (t6989586621680438440 a6989586621680438441) a6989586621680438441 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 a6989586621680438952 t6989586621680438440 :: TyFun (t6989586621680438440 a6989586621680438441) a6989586621680438441 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaximumBySym1 a6989586621680438952 t :: TyFun (t a) a -> Type) (a6989586621680438953 :: t a) = MaximumBy a6989586621680438952 a6989586621680438953

type MaximumBySym2 (a6989586621680438952 :: (~>) a6989586621680438441 ((~>) a6989586621680438441 Ordering)) (a6989586621680438953 :: t6989586621680438440 a6989586621680438441) = MaximumBy a6989586621680438952 a6989586621680438953 Source #

data MinimumBySym0 :: forall a6989586621680438439 t6989586621680438438. (~>) ((~>) a6989586621680438439 ((~>) a6989586621680438439 Ordering)) ((~>) (t6989586621680438438 a6989586621680438439) a6989586621680438439) 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 (a6989586621680438439 ~> (a6989586621680438439 ~> Ordering)) (t6989586621680438438 a6989586621680438439 ~> a6989586621680438439) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinimumBySym0 :: TyFun (a6989586621680438439 ~> (a6989586621680438439 ~> Ordering)) (t6989586621680438438 a6989586621680438439 ~> a6989586621680438439) -> Type) (a6989586621680438927 :: a6989586621680438439 ~> (a6989586621680438439 ~> Ordering)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinimumBySym0 :: TyFun (a6989586621680438439 ~> (a6989586621680438439 ~> Ordering)) (t6989586621680438438 a6989586621680438439 ~> a6989586621680438439) -> Type) (a6989586621680438927 :: a6989586621680438439 ~> (a6989586621680438439 ~> Ordering)) = (MinimumBySym1 a6989586621680438927 t6989586621680438438 :: TyFun (t6989586621680438438 a6989586621680438439) a6989586621680438439 -> Type)

data MinimumBySym1 (a6989586621680438927 :: (~>) a6989586621680438439 ((~>) a6989586621680438439 Ordering)) :: forall t6989586621680438438. (~>) (t6989586621680438438 a6989586621680438439) a6989586621680438439 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 a6989586621680438927 t6989586621680438438 :: TyFun (t6989586621680438438 a6989586621680438439) a6989586621680438439 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinimumBySym1 a6989586621680438927 t :: TyFun (t a) a -> Type) (a6989586621680438928 :: t a) = MinimumBy a6989586621680438927 a6989586621680438928

type MinimumBySym2 (a6989586621680438927 :: (~>) a6989586621680438439 ((~>) a6989586621680438439 Ordering)) (a6989586621680438928 :: t6989586621680438438 a6989586621680438439) = MinimumBy a6989586621680438927 a6989586621680438928 Source #

data NotElemSym0 :: forall a6989586621680438437 t6989586621680438436. (~>) a6989586621680438437 ((~>) (t6989586621680438436 a6989586621680438437) 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 a6989586621680438437 (t6989586621680438436 a6989586621680438437 ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym0 :: TyFun a6989586621680438437 (t6989586621680438436 a6989586621680438437 ~> Bool) -> Type) (a6989586621680438919 :: a6989586621680438437) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym0 :: TyFun a6989586621680438437 (t6989586621680438436 a6989586621680438437 ~> Bool) -> Type) (a6989586621680438919 :: a6989586621680438437) = (NotElemSym1 a6989586621680438919 t6989586621680438436 :: TyFun (t6989586621680438436 a6989586621680438437) Bool -> Type)

data NotElemSym1 (a6989586621680438919 :: a6989586621680438437) :: forall t6989586621680438436. (~>) (t6989586621680438436 a6989586621680438437) 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 a6989586621680438919 t6989586621680438436 :: TyFun (t6989586621680438436 a6989586621680438437) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym1 a6989586621680438919 t :: TyFun (t a) Bool -> Type) (a6989586621680438920 :: t a) = NotElem a6989586621680438919 a6989586621680438920

type NotElemSym2 (a6989586621680438919 :: a6989586621680438437) (a6989586621680438920 :: t6989586621680438436 a6989586621680438437) = NotElem a6989586621680438919 a6989586621680438920 Source #

data FindSym0 :: forall a6989586621680438435 t6989586621680438434. (~>) ((~>) a6989586621680438435 Bool) ((~>) (t6989586621680438434 a6989586621680438435) (Maybe a6989586621680438435)) 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 (a6989586621680438435 ~> Bool) (t6989586621680438434 a6989586621680438435 ~> Maybe a6989586621680438435) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym0 :: TyFun (a6989586621680438435 ~> Bool) (t6989586621680438434 a6989586621680438435 ~> Maybe a6989586621680438435) -> Type) (a6989586621680438892 :: a6989586621680438435 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym0 :: TyFun (a6989586621680438435 ~> Bool) (t6989586621680438434 a6989586621680438435 ~> Maybe a6989586621680438435) -> Type) (a6989586621680438892 :: a6989586621680438435 ~> Bool) = (FindSym1 a6989586621680438892 t6989586621680438434 :: TyFun (t6989586621680438434 a6989586621680438435) (Maybe a6989586621680438435) -> Type)

data FindSym1 (a6989586621680438892 :: (~>) a6989586621680438435 Bool) :: forall t6989586621680438434. (~>) (t6989586621680438434 a6989586621680438435) (Maybe a6989586621680438435) 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 a6989586621680438892 t6989586621680438434 :: TyFun (t6989586621680438434 a6989586621680438435) (Maybe a6989586621680438435) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym1 a6989586621680438892 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680438893 :: t a) = Find a6989586621680438892 a6989586621680438893

type FindSym2 (a6989586621680438892 :: (~>) a6989586621680438435 Bool) (a6989586621680438893 :: t6989586621680438434 a6989586621680438435) = Find a6989586621680438892 a6989586621680438893 Source #