Copyright | (C) 2018 Ryan Scott |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Ryan Scott |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | GHC2021 |
Data.Monoid.Singletons
Synopsis
- class PMonoid a where
- class SSemigroup a => SMonoid a where
- type family Sing :: k -> Type
- data SDual (a1 :: Dual a) where
- data SAll (a :: All) where
- data SAny (a :: Any) where
- data SSum (a1 :: Sum a) where
- data SProduct (a1 :: Product a) where
- data SFirst (a1 :: First a) where
- data SLast (a1 :: Last a) where
- type family GetDual (a1 :: Dual a) :: a where ...
- type family GetAll (a :: All) :: Bool where ...
- type family GetAny (a :: Any) :: Bool where ...
- type family GetSum (a1 :: Sum a) :: a where ...
- type family GetProduct (a1 :: Product a) :: a where ...
- type family GetFirst (a1 :: First a) :: Maybe a where ...
- type family GetLast (a1 :: Last a) :: Maybe a where ...
- sGetDual :: forall a (t :: Dual a). Sing t -> Sing (Apply (GetDualSym0 :: TyFun (Dual a) a -> Type) t)
- sGetAll :: forall (t :: All). Sing t -> Sing (Apply GetAllSym0 t)
- sGetAny :: forall (t :: Any). Sing t -> Sing (Apply GetAnySym0 t)
- sGetSum :: forall a (t :: Sum a). Sing t -> Sing (Apply (GetSumSym0 :: TyFun (Sum a) a -> Type) t)
- sGetProduct :: forall a (t :: Product a). Sing t -> Sing (Apply (GetProductSym0 :: TyFun (Product a) a -> Type) t)
- sGetFirst :: forall a (t :: First a). Sing t -> Sing (Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) t)
- sGetLast :: forall a (t :: Last a). Sing t -> Sing (Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) t)
- type family MemptySym0 :: a where ...
- data MappendSym0 (a1 :: TyFun a (a ~> a))
- data MappendSym1 (a6989586621680292326 :: a) (b :: TyFun a a)
- type family MappendSym2 (a6989586621680292326 :: a) (a6989586621680292327 :: a) :: a where ...
- data MconcatSym0 (a1 :: TyFun [a] a)
- type family MconcatSym1 (a6989586621680292330 :: [a]) :: a where ...
- data DualSym0 (a1 :: TyFun a (Dual a))
- type family DualSym1 (a6989586621679687531 :: a) :: Dual a where ...
- data GetDualSym0 (a1 :: TyFun (Dual a) a)
- type family GetDualSym1 (a6989586621679687534 :: Dual a) :: a where ...
- data AllSym0 (a :: TyFun Bool All)
- type family AllSym1 (a6989586621679687547 :: Bool) :: All where ...
- data GetAllSym0 (a :: TyFun All Bool)
- type family GetAllSym1 (a6989586621679687550 :: All) :: Bool where ...
- data AnySym0 (a :: TyFun Bool Any)
- type family AnySym1 (a6989586621679687563 :: Bool) :: Any where ...
- data GetAnySym0 (a :: TyFun Any Bool)
- type family GetAnySym1 (a6989586621679687566 :: Any) :: Bool where ...
- data SumSym0 (a1 :: TyFun a (Sum a))
- type family SumSym1 (a6989586621679687582 :: a) :: Sum a where ...
- data GetSumSym0 (a1 :: TyFun (Sum a) a)
- type family GetSumSym1 (a6989586621679687585 :: Sum a) :: a where ...
- data ProductSym0 (a1 :: TyFun a (Product a))
- type family ProductSym1 (a6989586621679687601 :: a) :: Product a where ...
- data GetProductSym0 (a1 :: TyFun (Product a) a)
- type family GetProductSym1 (a6989586621679687604 :: Product a) :: a where ...
- data FirstSym0 (a1 :: TyFun (Maybe a) (First a))
- type family FirstSym1 (a6989586621680296690 :: Maybe a) :: First a where ...
- data GetFirstSym0 (a1 :: TyFun (First a) (Maybe a))
- type family GetFirstSym1 (a6989586621680296693 :: First a) :: Maybe a where ...
- data LastSym0 (a1 :: TyFun (Maybe a) (Last a))
- type family LastSym1 (a6989586621680296713 :: Maybe a) :: Last a where ...
- data GetLastSym0 (a1 :: TyFun (Last a) (Maybe a))
- type family GetLastSym1 (a6989586621680296716 :: Last a) :: Maybe a where ...
Documentation
Associated Types
Instances
class SSemigroup a => SMonoid a where Source #
Minimal complete definition
Methods
sMempty :: Sing (MemptySym0 :: a) Source #
sMappend :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) t1) t2) Source #
default sMappend :: forall (t1 :: a) (t2 :: a). Apply (Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) t1) t2 ~ Apply (Apply (Mappend_6989586621680292333Sym0 :: TyFun a (a ~> a) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) t1) t2) Source #
sMconcat :: forall (t :: [a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [a] a -> Type) t) Source #
Instances
SMonoid All Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: All) Source # sMappend :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun All (All ~> All) -> Type) t1) t2) Source # sMconcat :: forall (t :: [All]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [All] All -> Type) t) Source # | |
SMonoid Any Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: Any) Source # sMappend :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun Any (Any ~> Any) -> Type) t1) t2) Source # sMconcat :: forall (t :: [Any]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Any] Any -> Type) t) Source # | |
SMonoid Ordering Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: Ordering) Source # sMappend :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun Ordering (Ordering ~> Ordering) -> Type) t1) t2) Source # sMconcat :: forall (t :: [Ordering]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Ordering] Ordering -> Type) t) Source # | |
SMonoid () Source # | |
Defined in Data.Monoid.Singletons | |
SMonoid Symbol Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: Symbol) Source # sMappend :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun Symbol (Symbol ~> Symbol) -> Type) t1) t2) Source # sMconcat :: forall (t :: [Symbol]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Symbol] Symbol -> Type) t) Source # | |
SMonoid a => SMonoid (Identity a) Source # | |
Defined in Data.Functor.Identity.Singletons Methods sMempty :: Sing (MemptySym0 :: Identity a) Source # sMappend :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Identity a) (Identity a ~> Identity a) -> Type) t1) t2) Source # sMconcat :: forall (t :: [Identity a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Identity a] (Identity a) -> Type) t) Source # | |
SMonoid (First a) Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: First a) Source # sMappend :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (First a) (First a ~> First a) -> Type) t1) t2) Source # sMconcat :: forall (t :: [First a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [First a] (First a) -> Type) t) Source # | |
SMonoid (Last a) Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: Last a) Source # sMappend :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Last a) (Last a ~> Last a) -> Type) t1) t2) Source # sMconcat :: forall (t :: [Last a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Last a] (Last a) -> Type) t) Source # | |
SMonoid a => SMonoid (Down a) Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: Down a) Source # sMappend :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Down a) (Down a ~> Down a) -> Type) t1) t2) Source # sMconcat :: forall (t :: [Down a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Down a] (Down a) -> Type) t) Source # | |
(SOrd a, SBounded a) => SMonoid (Max a) Source # | |
Defined in Data.Semigroup.Singletons Methods sMempty :: Sing (MemptySym0 :: Max a) Source # sMappend :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Max a) (Max a ~> Max a) -> Type) t1) t2) Source # sMconcat :: forall (t :: [Max a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Max a] (Max a) -> Type) t) Source # | |
(SOrd a, SBounded a) => SMonoid (Min a) Source # | |
Defined in Data.Semigroup.Singletons Methods sMempty :: Sing (MemptySym0 :: Min a) Source # sMappend :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Min a) (Min a ~> Min a) -> Type) t1) t2) Source # sMconcat :: forall (t :: [Min a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Min a] (Min a) -> Type) t) Source # | |
SMonoid m => SMonoid (WrappedMonoid m) Source # | |
Defined in Data.Semigroup.Singletons Methods sMempty :: Sing (MemptySym0 :: WrappedMonoid m) Source # sMappend :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (WrappedMonoid m) (WrappedMonoid m ~> WrappedMonoid m) -> Type) t1) t2) Source # sMconcat :: forall (t :: [WrappedMonoid m]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [WrappedMonoid m] (WrappedMonoid m) -> Type) t) Source # | |
SMonoid a => SMonoid (Dual a) Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: Dual a) Source # sMappend :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Dual a) (Dual a ~> Dual a) -> Type) t1) t2) Source # sMconcat :: forall (t :: [Dual a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Dual a] (Dual a) -> Type) t) Source # | |
SNum a => SMonoid (Product a) Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: Product a) Source # sMappend :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Product a) (Product a ~> Product a) -> Type) t1) t2) Source # sMconcat :: forall (t :: [Product a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Product a] (Product a) -> Type) t) Source # | |
SNum a => SMonoid (Sum a) Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: Sum a) Source # sMappend :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Sum a) (Sum a ~> Sum a) -> Type) t1) t2) Source # sMconcat :: forall (t :: [Sum a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Sum a] (Sum a) -> Type) t) Source # | |
SSemigroup a => SMonoid (Maybe a) Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: Maybe a) Source # sMappend :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) t1) t2) Source # sMconcat :: forall (t :: [Maybe a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Maybe a] (Maybe a) -> Type) t) Source # | |
SMonoid [a] Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: [a]) Source # sMappend :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun [a] ([a] ~> [a]) -> Type) t1) t2) Source # sMconcat :: forall (t :: [[a]]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [[a]] [a] -> Type) t) Source # | |
SMonoid (Proxy s) Source # | |
Defined in Data.Proxy.Singletons Methods sMempty :: Sing (MemptySym0 :: Proxy s) Source # sMappend :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Proxy s) (Proxy s ~> Proxy s) -> Type) t1) t2) Source # sMconcat :: forall (t :: [Proxy s]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Proxy s] (Proxy s) -> Type) t) Source # | |
SMonoid b => SMonoid (a ~> b) Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: a ~> b) Source # sMappend :: forall (t1 :: a ~> b) (t2 :: a ~> b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (a ~> b) ((a ~> b) ~> (a ~> b)) -> Type) t1) t2) Source # sMconcat :: forall (t :: [a ~> b]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [a ~> b] (a ~> b) -> Type) t) Source # | |
(SMonoid a, SMonoid b) => SMonoid (a, b) Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: (a, b)) Source # sMappend :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (a, b) ((a, b) ~> (a, b)) -> Type) t1) t2) Source # sMconcat :: forall (t :: [(a, b)]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [(a, b)] (a, b) -> Type) t) Source # | |
SMonoid a => SMonoid (Const a b) Source # | |
Defined in Data.Functor.Const.Singletons Methods sMempty :: Sing (MemptySym0 :: Const a b) Source # sMappend :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Const a b) (Const a b ~> Const a b) -> Type) t1) t2) Source # sMconcat :: forall (t :: [Const a b]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Const a b] (Const a b) -> Type) t) Source # | |
(SMonoid a, SMonoid b, SMonoid c) => SMonoid (a, b, c) Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: (a, b, c)) Source # sMappend :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (a, b, c) ((a, b, c) ~> (a, b, c)) -> Type) t1) t2) Source # sMconcat :: forall (t :: [(a, b, c)]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [(a, b, c)] (a, b, c) -> Type) t) Source # | |
(SMonoid a, SMonoid b, SMonoid c, SMonoid d) => SMonoid (a, b, c, d) Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: (a, b, c, d)) Source # sMappend :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (a, b, c, d) ((a, b, c, d) ~> (a, b, c, d)) -> Type) t1) t2) Source # sMconcat :: forall (t :: [(a, b, c, d)]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [(a, b, c, d)] (a, b, c, d) -> Type) t) Source # | |
(SMonoid a, SMonoid b, SMonoid c, SMonoid d, SMonoid e) => SMonoid (a, b, c, d, e) Source # | |
Defined in Data.Monoid.Singletons Methods sMempty :: Sing (MemptySym0 :: (a, b, c, d, e)) Source # sMappend :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> (a, b, c, d, e)) -> Type) t1) t2) Source # sMconcat :: forall (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [(a, b, c, d, e)] (a, b, c, d, e) -> Type) t) Source # |
type family Sing :: k -> Type #
Instances
type Sing Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
type Sing Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances | |
type Sing Source # | |
Defined in GHC.TypeLits.Singletons.Internal | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances | |
type Sing Source # | |
Defined in Data.Singletons.Base.TypeError | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances | |
type Sing Source # | |
Defined in GHC.TypeLits.Singletons.Internal | |
type Sing Source # | |
Defined in GHC.TypeLits.Singletons.Internal | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances | |
type Sing Source # | |
Defined in Data.Monoid.Singletons | |
type Sing Source # | |
Defined in Data.Monoid.Singletons | |
type Sing Source # | |
Defined in Data.Ord.Singletons | |
type Sing Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
type Sing Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
type Sing Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
type Sing Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
type Sing Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
type Sing Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
type Sing Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
type Sing Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances | |
type Sing Source # | A choice of singleton for the kind Conceivably, one could generalize this instance to `Sing @k` for
any kind We cannot produce explicit singleton values for everything in |
Defined in Data.Singletons.Base.TypeRepTYPE | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances | |
type Sing Source # | |
Defined in Data.Proxy.Singletons | |
type Sing Source # | |
Defined in Data.Semigroup.Singletons | |
type Sing | |
Defined in Data.Singletons | |
type Sing | |
Defined in Data.Singletons | |
type Sing | |
Defined in Data.Singletons.Sigma | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances | |
type Sing Source # | |
Defined in Data.Functor.Const.Singletons | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances | |
type Sing Source # | |
Defined in Data.Functor.Product.Singletons | |
type Sing Source # | |
Defined in Data.Functor.Sum.Singletons | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances | |
type Sing Source # | |
Defined in Data.Functor.Compose.Singletons | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances |
data SDual (a1 :: Dual a) where Source #
Instances
data SProduct (a1 :: Product a) where Source #
Instances
SDecide a => TestCoercion (SProduct :: Product a -> Type) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
SDecide a => TestEquality (SProduct :: Product a -> Type) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
ShowSing a => Show (SProduct z) Source # | |
Eq (SProduct z) Source # | |
type family GetProduct (a1 :: Product a) :: a where ... Source #
Equations
GetProduct ('Product field :: Product a) = field |
sGetDual :: forall a (t :: Dual a). Sing t -> Sing (Apply (GetDualSym0 :: TyFun (Dual a) a -> Type) t) Source #
sGetSum :: forall a (t :: Sum a). Sing t -> Sing (Apply (GetSumSym0 :: TyFun (Sum a) a -> Type) t) Source #
sGetProduct :: forall a (t :: Product a). Sing t -> Sing (Apply (GetProductSym0 :: TyFun (Product a) a -> Type) t) Source #
sGetFirst :: forall a (t :: First a). Sing t -> Sing (Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) t) Source #
sGetLast :: forall a (t :: Last a). Sing t -> Sing (Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) t) Source #
Defunctionalization symbols
type family MemptySym0 :: a where ... Source #
Equations
MemptySym0 = Mempty :: a |
data MappendSym0 (a1 :: TyFun a (a ~> a)) Source #
Instances
SMonoid a => SingI (MappendSym0 :: TyFun a (a ~> a) -> Type) Source # | |
Defined in Data.Monoid.Singletons | |
SuppressUnusedWarnings (MappendSym0 :: TyFun a (a ~> a) -> Type) Source # | |
Defined in Data.Monoid.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) (a6989586621680292326 :: a) Source # | |
Defined in Data.Monoid.Singletons type Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) (a6989586621680292326 :: a) = MappendSym1 a6989586621680292326 |
data MappendSym1 (a6989586621680292326 :: a) (b :: TyFun a a) Source #
Instances
SMonoid a => SingI1 (MappendSym1 :: a -> TyFun a a -> Type) Source # | |
Defined in Data.Monoid.Singletons Methods liftSing :: forall (x :: a). Sing x -> Sing (MappendSym1 x) # | |
(SMonoid a, SingI d) => SingI (MappendSym1 d :: TyFun a a -> Type) Source # | |
Defined in Data.Monoid.Singletons Methods sing :: Sing (MappendSym1 d) # | |
SuppressUnusedWarnings (MappendSym1 a6989586621680292326 :: TyFun a a -> Type) Source # | |
Defined in Data.Monoid.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (MappendSym1 a6989586621680292326 :: TyFun a a -> Type) (a6989586621680292327 :: a) Source # | |
Defined in Data.Monoid.Singletons type Apply (MappendSym1 a6989586621680292326 :: TyFun a a -> Type) (a6989586621680292327 :: a) = Mappend a6989586621680292326 a6989586621680292327 |
type family MappendSym2 (a6989586621680292326 :: a) (a6989586621680292327 :: a) :: a where ... Source #
Equations
MappendSym2 (a6989586621680292326 :: a) (a6989586621680292327 :: a) = Mappend a6989586621680292326 a6989586621680292327 |
data MconcatSym0 (a1 :: TyFun [a] a) Source #
Instances
SMonoid a => SingI (MconcatSym0 :: TyFun [a] a -> Type) Source # | |
Defined in Data.Monoid.Singletons | |
SuppressUnusedWarnings (MconcatSym0 :: TyFun [a] a -> Type) Source # | |
Defined in Data.Monoid.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (MconcatSym0 :: TyFun [a] a -> Type) (a6989586621680292330 :: [a]) Source # | |
Defined in Data.Monoid.Singletons type Apply (MconcatSym0 :: TyFun [a] a -> Type) (a6989586621680292330 :: [a]) = Mconcat a6989586621680292330 |
type family MconcatSym1 (a6989586621680292330 :: [a]) :: a where ... Source #
Equations
MconcatSym1 (a6989586621680292330 :: [a]) = Mconcat a6989586621680292330 |
data DualSym0 (a1 :: TyFun a (Dual a)) Source #
Instances
SingI (DualSym0 :: TyFun a (Dual a) -> Type) Source # | |
SuppressUnusedWarnings (DualSym0 :: TyFun a (Dual a) -> Type) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers Methods suppressUnusedWarnings :: () # | |
type Apply (DualSym0 :: TyFun a (Dual a) -> Type) (a6989586621679687531 :: a) Source # | |
data GetDualSym0 (a1 :: TyFun (Dual a) a) Source #
Instances
SingI (GetDualSym0 :: TyFun (Dual a) a -> Type) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
SuppressUnusedWarnings (GetDualSym0 :: TyFun (Dual a) a -> Type) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers Methods suppressUnusedWarnings :: () # | |
type Apply (GetDualSym0 :: TyFun (Dual a) a -> Type) (a6989586621679687534 :: Dual a) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers |
type family GetDualSym1 (a6989586621679687534 :: Dual a) :: a where ... Source #
Equations
GetDualSym1 (a6989586621679687534 :: Dual a) = GetDual a6989586621679687534 |
data AllSym0 (a :: TyFun Bool All) Source #
Instances
SingI AllSym0 Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
SuppressUnusedWarnings AllSym0 Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers Methods suppressUnusedWarnings :: () # | |
type Apply AllSym0 (a6989586621679687547 :: Bool) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers |
data GetAllSym0 (a :: TyFun All Bool) Source #
Instances
SingI GetAllSym0 Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers Methods sing :: Sing GetAllSym0 # | |
SuppressUnusedWarnings GetAllSym0 Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers Methods suppressUnusedWarnings :: () # | |
type Apply GetAllSym0 (a6989586621679687550 :: All) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers |
type family GetAllSym1 (a6989586621679687550 :: All) :: Bool where ... Source #
Equations
GetAllSym1 a6989586621679687550 = GetAll a6989586621679687550 |
data AnySym0 (a :: TyFun Bool Any) Source #
Instances
SingI AnySym0 Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
SuppressUnusedWarnings AnySym0 Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers Methods suppressUnusedWarnings :: () # | |
type Apply AnySym0 (a6989586621679687563 :: Bool) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers |
data GetAnySym0 (a :: TyFun Any Bool) Source #
Instances
SingI GetAnySym0 Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers Methods sing :: Sing GetAnySym0 # | |
SuppressUnusedWarnings GetAnySym0 Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers Methods suppressUnusedWarnings :: () # | |
type Apply GetAnySym0 (a6989586621679687566 :: Any) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers |
type family GetAnySym1 (a6989586621679687566 :: Any) :: Bool where ... Source #
Equations
GetAnySym1 a6989586621679687566 = GetAny a6989586621679687566 |
data SumSym0 (a1 :: TyFun a (Sum a)) Source #
Instances
data GetSumSym0 (a1 :: TyFun (Sum a) a) Source #
Instances
SingI (GetSumSym0 :: TyFun (Sum a) a -> Type) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
SuppressUnusedWarnings (GetSumSym0 :: TyFun (Sum a) a -> Type) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers Methods suppressUnusedWarnings :: () # | |
type Apply (GetSumSym0 :: TyFun (Sum a) a -> Type) (a6989586621679687585 :: Sum a) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers |
type family GetSumSym1 (a6989586621679687585 :: Sum a) :: a where ... Source #
Equations
GetSumSym1 (a6989586621679687585 :: Sum a) = GetSum a6989586621679687585 |
data ProductSym0 (a1 :: TyFun a (Product a)) Source #
Instances
SingI (ProductSym0 :: TyFun a (Product a) -> Type) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
SuppressUnusedWarnings (ProductSym0 :: TyFun a (Product a) -> Type) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers Methods suppressUnusedWarnings :: () # | |
type Apply (ProductSym0 :: TyFun a (Product a) -> Type) (a6989586621679687601 :: a) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers |
type family ProductSym1 (a6989586621679687601 :: a) :: Product a where ... Source #
Equations
ProductSym1 (a6989586621679687601 :: a) = 'Product a6989586621679687601 |
data GetProductSym0 (a1 :: TyFun (Product a) a) Source #
Instances
SingI (GetProductSym0 :: TyFun (Product a) a -> Type) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers | |
SuppressUnusedWarnings (GetProductSym0 :: TyFun (Product a) a -> Type) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers Methods suppressUnusedWarnings :: () # | |
type Apply (GetProductSym0 :: TyFun (Product a) a -> Type) (a6989586621679687604 :: Product a) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers type Apply (GetProductSym0 :: TyFun (Product a) a -> Type) (a6989586621679687604 :: Product a) = GetProduct a6989586621679687604 |
type family GetProductSym1 (a6989586621679687604 :: Product a) :: a where ... Source #
Equations
GetProductSym1 (a6989586621679687604 :: Product a) = GetProduct a6989586621679687604 |
data FirstSym0 (a1 :: TyFun (Maybe a) (First a)) Source #
Instances
SingI (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) Source # | |
SuppressUnusedWarnings (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) Source # | |
Defined in Data.Monoid.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (a6989586621680296690 :: Maybe a) Source # | |
data GetFirstSym0 (a1 :: TyFun (First a) (Maybe a)) Source #
Instances
SingI (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) Source # | |
Defined in Data.Monoid.Singletons | |
SuppressUnusedWarnings (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) Source # | |
Defined in Data.Monoid.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) (a6989586621680296693 :: First a) Source # | |
Defined in Data.Monoid.Singletons |
type family GetFirstSym1 (a6989586621680296693 :: First a) :: Maybe a where ... Source #
Equations
GetFirstSym1 (a6989586621680296693 :: First a) = GetFirst a6989586621680296693 |
data LastSym0 (a1 :: TyFun (Maybe a) (Last a)) Source #
Instances
SingI (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) Source # | |
SuppressUnusedWarnings (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) Source # | |
Defined in Data.Monoid.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (a6989586621680296713 :: Maybe a) Source # | |
data GetLastSym0 (a1 :: TyFun (Last a) (Maybe a)) Source #
Instances
SingI (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) Source # | |
Defined in Data.Monoid.Singletons | |
SuppressUnusedWarnings (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) Source # | |
Defined in Data.Monoid.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621680296716 :: Last a) Source # | |
Defined in Data.Monoid.Singletons |
type family GetLastSym1 (a6989586621680296716 :: Last a) :: Maybe a where ... Source #
Equations
GetLastSym1 (a6989586621680296716 :: Last a) = GetLast a6989586621680296716 |
Orphan instances
PApplicative First Source # | |||||||||||||||||||||
Associated Types
| |||||||||||||||||||||
PApplicative Last Source # | |||||||||||||||||||||
Associated Types
| |||||||||||||||||||||
PFunctor First Source # | |||||||||||||||||||||
PFunctor Last Source # | |||||||||||||||||||||
PMonad First Source # | |||||||||||||||||||||
Associated Types
| |||||||||||||||||||||
PMonad Last Source # | |||||||||||||||||||||
Associated Types
| |||||||||||||||||||||
SApplicative First Source # | |||||||||||||||||||||
Methods sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (First a) -> Type) t) Source # (%<*>) :: forall a b (t1 :: First (a ~> b)) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (First (a ~> b)) (First a ~> First b) -> Type) t1) t2) Source # sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: First a) (t3 :: First b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (First a ~> (First b ~> First c)) -> Type) t1) t2) t3) Source # (%*>) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (First a) (First b ~> First b) -> Type) t1) t2) Source # (%<*) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (First a) (First b ~> First a) -> Type) t1) t2) Source # | |||||||||||||||||||||
SApplicative Last Source # | |||||||||||||||||||||
Methods sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (Last a) -> Type) t) Source # (%<*>) :: forall a b (t1 :: Last (a ~> b)) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Last (a ~> b)) (Last a ~> Last b) -> Type) t1) t2) Source # sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Last a) (t3 :: Last b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Last a ~> (Last b ~> Last c)) -> Type) t1) t2) t3) Source # (%*>) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Last a) (Last b ~> Last b) -> Type) t1) t2) Source # (%<*) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Last a) (Last b ~> Last a) -> Type) t1) t2) Source # | |||||||||||||||||||||
SFunctor First Source # | |||||||||||||||||||||
Methods sFmap :: forall a b (t1 :: a ~> b) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (First a ~> First b) -> Type) t1) t2) Source # (%<$) :: forall a b (t1 :: a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (First b ~> First a) -> Type) t1) t2) Source # | |||||||||||||||||||||
SFunctor Last Source # | |||||||||||||||||||||
Methods sFmap :: forall a b (t1 :: a ~> b) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Last a ~> Last b) -> Type) t1) t2) Source # (%<$) :: forall a b (t1 :: a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Last b ~> Last a) -> Type) t1) t2) Source # | |||||||||||||||||||||
SMonad First Source # | |||||||||||||||||||||
Methods (%>>=) :: forall a b (t1 :: First a) (t2 :: a ~> First b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>=@#@$) :: TyFun (First a) ((a ~> First b) ~> First b) -> Type) t1) t2) Source # (%>>) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (First a) (First b ~> First b) -> Type) t1) t2) Source # sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (First a) -> Type) t) Source # | |||||||||||||||||||||
SMonad Last Source # | |||||||||||||||||||||
Methods (%>>=) :: forall a b (t1 :: Last a) (t2 :: a ~> Last b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>=@#@$) :: TyFun (Last a) ((a ~> Last b) ~> Last b) -> Type) t1) t2) Source # (%>>) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Last a) (Last b ~> Last b) -> Type) t1) t2) Source # sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Last a) -> Type) t) Source # | |||||||||||||||||||||
SingKind a => SingKind (First a) Source # | |||||||||||||||||||||
SingKind a => SingKind (Last a) Source # | |||||||||||||||||||||
SDecide (Maybe a) => SDecide (First a) Source # | |||||||||||||||||||||
SDecide (Maybe a) => SDecide (Last a) Source # | |||||||||||||||||||||
PEq (First a) Source # | |||||||||||||||||||||
PEq (Last a) Source # | |||||||||||||||||||||
SEq (Maybe a) => SEq (First a) Source # | |||||||||||||||||||||
Methods (%==) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((==@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source # (%/=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source # | |||||||||||||||||||||
SEq (Maybe a) => SEq (Last a) Source # | |||||||||||||||||||||
Methods (%==) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((==@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source # (%/=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source # | |||||||||||||||||||||
POrd (First a) Source # | |||||||||||||||||||||
POrd (Last a) Source # | |||||||||||||||||||||
SOrd (Maybe a) => SOrd (First a) Source # | |||||||||||||||||||||
Methods sCompare :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (CompareSym0 :: TyFun (First a) (First a ~> Ordering) -> Type) t1) t2) Source # (%<) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source # (%<=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source # (%>) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source # (%>=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source # sMax :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (First a) (First a ~> First a) -> Type) t1) t2) Source # sMin :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (First a) (First a ~> First a) -> Type) t1) t2) Source # | |||||||||||||||||||||
SOrd (Maybe a) => SOrd (Last a) Source # | |||||||||||||||||||||
Methods sCompare :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (CompareSym0 :: TyFun (Last a) (Last a ~> Ordering) -> Type) t1) t2) Source # (%<) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source # (%<=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source # (%>) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source # (%>=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source # sMax :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Last a) (Last a ~> Last a) -> Type) t1) t2) Source # sMin :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Last a) (Last a ~> Last a) -> Type) t1) t2) Source # | |||||||||||||||||||||
PSemigroup (First a) Source # | |||||||||||||||||||||
PSemigroup (Last a) Source # | |||||||||||||||||||||
SSemigroup (First a) Source # | |||||||||||||||||||||
Methods (%<>) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<>@#@$) :: TyFun (First a) (First a ~> First a) -> Type) t1) t2) Source # sSconcat :: forall (t :: NonEmpty (First a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (First a)) (First a) -> Type) t) Source # | |||||||||||||||||||||
SSemigroup (Last a) Source # | |||||||||||||||||||||
Methods (%<>) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<>@#@$) :: TyFun (Last a) (Last a ~> Last a) -> Type) t1) t2) Source # sSconcat :: forall (t :: NonEmpty (Last a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Last a)) (Last a) -> Type) t) Source # | |||||||||||||||||||||
PShow (First a) Source # | |||||||||||||||||||||
PShow (Last a) Source # | |||||||||||||||||||||
SShow (Maybe a) => SShow (First a) Source # | |||||||||||||||||||||
Methods sShowsPrec :: forall (t1 :: Natural) (t2 :: First a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (First a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source # sShow_ :: forall (t :: First a). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (First a) Symbol -> Type) t) Source # sShowList :: forall (t1 :: [First a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [First a] (Symbol ~> Symbol) -> Type) t1) t2) Source # | |||||||||||||||||||||
SShow (Maybe a) => SShow (Last a) Source # | |||||||||||||||||||||
Methods sShowsPrec :: forall (t1 :: Natural) (t2 :: Last a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Last a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source # sShow_ :: forall (t :: Last a). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Last a) Symbol -> Type) t) Source # sShowList :: forall (t1 :: [Last a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Last a] (Symbol ~> Symbol) -> Type) t1) t2) Source # | |||||||||||||||||||||
SingI1 ('First :: Maybe a -> First a) Source # | |||||||||||||||||||||
SingI1 ('Last :: Maybe a -> Last a) Source # | |||||||||||||||||||||
SingI n => SingI ('First n :: First a) Source # | |||||||||||||||||||||
SingI n => SingI ('Last n :: Last a) Source # | |||||||||||||||||||||