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 (GetDual t)
- sGetAll :: forall (t :: All). Sing t -> Sing (GetAll t)
- sGetAny :: forall (t :: Any). Sing t -> Sing (GetAny t)
- sGetSum :: forall a (t :: Sum a). Sing t -> Sing (GetSum t)
- sGetProduct :: forall a (t :: Product a). Sing t -> Sing (GetProduct t)
- sGetFirst :: forall a (t :: First a). Sing t -> Sing (GetFirst t)
- sGetLast :: forall a (t :: Last a). Sing t -> Sing (GetLast t)
- type family MemptySym0 :: a where ...
- data MappendSym0 (a1 :: TyFun a (a ~> a))
- data MappendSym1 (a6989586621679860746 :: a) (b :: TyFun a a)
- type family MappendSym2 (a6989586621679860746 :: a) (a6989586621679860747 :: a) :: a where ...
- data MconcatSym0 (a1 :: TyFun [a] a)
- type family MconcatSym1 (a6989586621679860750 :: [a]) :: a where ...
- data DualSym0 (a1 :: TyFun a (Dual a))
- type family DualSym1 (a6989586621679458575 :: a) :: Dual a where ...
- data GetDualSym0 (a1 :: TyFun (Dual a) a)
- type family GetDualSym1 (a6989586621679458578 :: Dual a) :: a where ...
- data AllSym0 (a :: TyFun Bool All)
- type family AllSym1 (a6989586621679458591 :: Bool) :: All where ...
- data GetAllSym0 (a :: TyFun All Bool)
- type family GetAllSym1 (a6989586621679458594 :: All) :: Bool where ...
- data AnySym0 (a :: TyFun Bool Any)
- type family AnySym1 (a6989586621679458607 :: Bool) :: Any where ...
- data GetAnySym0 (a :: TyFun Any Bool)
- type family GetAnySym1 (a6989586621679458610 :: Any) :: Bool where ...
- data SumSym0 (a1 :: TyFun a (Sum a))
- type family SumSym1 (a6989586621679458626 :: a) :: Sum a where ...
- data GetSumSym0 (a1 :: TyFun (Sum a) a)
- type family GetSumSym1 (a6989586621679458629 :: Sum a) :: a where ...
- data ProductSym0 (a1 :: TyFun a (Product a))
- type family ProductSym1 (a6989586621679458645 :: a) :: Product a where ...
- data GetProductSym0 (a1 :: TyFun (Product a) a)
- type family GetProductSym1 (a6989586621679458648 :: Product a) :: a where ...
- data FirstSym0 (a1 :: TyFun (Maybe a) (First a))
- type family FirstSym1 (a6989586621679864297 :: Maybe a) :: First a where ...
- data GetFirstSym0 (a1 :: TyFun (First a) (Maybe a))
- type family GetFirstSym1 (a6989586621679864300 :: First a) :: Maybe a where ...
- data LastSym0 (a1 :: TyFun (Maybe a) (Last a))
- type family LastSym1 (a6989586621679864320 :: Maybe a) :: Last a where ...
- data GetLastSym0 (a1 :: TyFun (Last a) (Maybe a))
- type family GetLastSym1 (a6989586621679864323 :: Last a) :: Maybe a where ...
Documentation
Associated Types
type Mappend (arg :: a) (arg1 :: a) :: a Source #
type Mappend (arg :: a) (arg1 :: a) = Mappend_6989586621679860753 arg arg1
type Mconcat (arg :: [a]) :: a Source #
type Mconcat (arg :: [a]) = Mconcat_6989586621679860767 arg
Instances
class SSemigroup a => SMonoid a where Source #
Minimal complete definition
Methods
sMempty :: Sing (Mempty :: a) Source #
sMappend :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #
default sMappend :: forall (t1 :: a) (t2 :: a). Mappend t1 t2 ~ Mappend_6989586621679860753 t1 t2 => Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #
sMconcat :: forall (t :: [a]). Sing t -> Sing (Mconcat t) Source #
Instances
SMonoid All Source # | |
SMonoid Any Source # | |
SMonoid Ordering Source # | |
SMonoid () Source # | |
SMonoid Symbol Source # | |
(SOrd a, SBounded a) => SMonoid (Max a) Source # | |
(SOrd a, SBounded a) => SMonoid (Min a) Source # | |
SMonoid m => SMonoid (WrappedMonoid m) Source # | |
Defined in Data.Semigroup.Singletons | |
SMonoid a => SMonoid (Identity a) Source # | |
SMonoid (First a) Source # | |
SMonoid (Last a) Source # | |
SMonoid a => SMonoid (Down a) Source # | |
SMonoid a => SMonoid (Dual a) Source # | |
SNum a => SMonoid (Product a) Source # | |
SNum a => SMonoid (Sum a) Source # | |
SSemigroup a => SMonoid (Maybe a) Source # | |
SMonoid [a] Source # | |
SMonoid (Proxy s) Source # | |
SMonoid b => SMonoid (a ~> b) Source # | |
(SMonoid a, SMonoid b) => SMonoid (a, b) Source # | |
SMonoid a => SMonoid (Const a b) Source # | |
(SMonoid a, SMonoid b, SMonoid c) => SMonoid (a, b, c) Source # | |
(SMonoid a, SMonoid b, SMonoid c, SMonoid d) => SMonoid (a, b, c, d) Source # | |
(SMonoid a, SMonoid b, SMonoid c, SMonoid d, SMonoid e) => SMonoid (a, b, c, d, e) Source # | |
type family Sing :: k -> Type #
Instances
type Sing Source # | |
Defined in Data.Singletons.Base.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 Data.Singletons.Base.TypeError | |
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.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.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 # | |
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.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.Semigroup.Singletons | |
type Sing Source # | |
Defined in Data.Singletons.Base.Instances | |
type Sing Source # | |
Defined in Data.Proxy.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 |
sGetProduct :: forall a (t :: Product a). Sing t -> Sing (GetProduct 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) (a6989586621679860746 :: a) Source # | |
Defined in Data.Monoid.Singletons type Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679860746 :: a) = MappendSym1 a6989586621679860746 |
data MappendSym1 (a6989586621679860746 :: 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 a6989586621679860746 :: TyFun a a -> Type) Source # | |
Defined in Data.Monoid.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (MappendSym1 a6989586621679860746 :: TyFun a a -> Type) (a6989586621679860747 :: a) Source # | |
Defined in Data.Monoid.Singletons type Apply (MappendSym1 a6989586621679860746 :: TyFun a a -> Type) (a6989586621679860747 :: a) = Mappend a6989586621679860746 a6989586621679860747 |
type family MappendSym2 (a6989586621679860746 :: a) (a6989586621679860747 :: a) :: a where ... Source #
Equations
MappendSym2 (a6989586621679860746 :: a) (a6989586621679860747 :: a) = Mappend a6989586621679860746 a6989586621679860747 |
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) (a6989586621679860750 :: [a]) Source # | |
Defined in Data.Monoid.Singletons type Apply (MconcatSym0 :: TyFun [a] a -> Type) (a6989586621679860750 :: [a]) = Mconcat a6989586621679860750 |
type family MconcatSym1 (a6989586621679860750 :: [a]) :: a where ... Source #
Equations
MconcatSym1 (a6989586621679860750 :: [a]) = Mconcat a6989586621679860750 |
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) (a6989586621679458575 :: 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) (a6989586621679458578 :: Dual a) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers |
type family GetDualSym1 (a6989586621679458578 :: Dual a) :: a where ... Source #
Equations
GetDualSym1 (a6989586621679458578 :: Dual a) = GetDual a6989586621679458578 |
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 (a6989586621679458591 :: 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 (a6989586621679458594 :: All) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers |
type family GetAllSym1 (a6989586621679458594 :: All) :: Bool where ... Source #
Equations
GetAllSym1 a6989586621679458594 = GetAll a6989586621679458594 |
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 (a6989586621679458607 :: 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 (a6989586621679458610 :: Any) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers |
type family GetAnySym1 (a6989586621679458610 :: Any) :: Bool where ... Source #
Equations
GetAnySym1 a6989586621679458610 = GetAny a6989586621679458610 |
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) (a6989586621679458629 :: Sum a) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers |
type family GetSumSym1 (a6989586621679458629 :: Sum a) :: a where ... Source #
Equations
GetSumSym1 (a6989586621679458629 :: Sum a) = GetSum a6989586621679458629 |
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) (a6989586621679458645 :: a) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers |
type family ProductSym1 (a6989586621679458645 :: a) :: Product a where ... Source #
Equations
ProductSym1 (a6989586621679458645 :: a) = 'Product a6989586621679458645 |
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) (a6989586621679458648 :: Product a) Source # | |
Defined in Data.Semigroup.Singletons.Internal.Wrappers type Apply (GetProductSym0 :: TyFun (Product a) a -> Type) (a6989586621679458648 :: Product a) = GetProduct a6989586621679458648 |
type family GetProductSym1 (a6989586621679458648 :: Product a) :: a where ... Source #
Equations
GetProductSym1 (a6989586621679458648 :: Product a) = GetProduct a6989586621679458648 |
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) (a6989586621679864297 :: 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) (a6989586621679864300 :: First a) Source # | |
Defined in Data.Monoid.Singletons |
type family GetFirstSym1 (a6989586621679864300 :: First a) :: Maybe a where ... Source #
Equations
GetFirstSym1 (a6989586621679864300 :: First a) = GetFirst a6989586621679864300 |
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) (a6989586621679864320 :: 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) (a6989586621679864323 :: Last a) Source # | |
Defined in Data.Monoid.Singletons |
type family GetLastSym1 (a6989586621679864323 :: Last a) :: Maybe a where ... Source #
Equations
GetLastSym1 (a6989586621679864323 :: Last a) = GetLast a6989586621679864323 |
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 (Pure t :: First a) Source # (%<*>) :: forall a b (t1 :: First (a ~> b)) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (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 (LiftA2 t1 t2 t3) Source # (%*>) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source # (%<*) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source # | |||||||||||||||||||||
SApplicative Last Source # | |||||||||||||||||||||
Methods sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Last a) Source # (%<*>) :: forall a b (t1 :: Last (a ~> b)) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (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 (LiftA2 t1 t2 t3) Source # (%*>) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source # (%<*) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source # | |||||||||||||||||||||
SFunctor First Source # | |||||||||||||||||||||
SFunctor Last Source # | |||||||||||||||||||||
SMonad First Source # | |||||||||||||||||||||
SMonad Last 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 # | |||||||||||||||||||||
SEq (Maybe a) => SEq (Last a) 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 (Compare t1 t2) Source # (%<) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source # (%<=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source # (%>) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source # (%>=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source # sMax :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source # sMin :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source # | |||||||||||||||||||||
SOrd (Maybe a) => SOrd (Last a) Source # | |||||||||||||||||||||
Methods sCompare :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source # (%<) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source # (%<=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source # (%>) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source # (%>=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source # sMax :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source # sMin :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source # | |||||||||||||||||||||
PSemigroup (First a) Source # | |||||||||||||||||||||
PSemigroup (Last a) Source # | |||||||||||||||||||||
SSemigroup (First a) Source # | |||||||||||||||||||||
SSemigroup (Last a) 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 (ShowsPrec t1 t2 t3) Source # sShow_ :: forall (t :: First a). Sing t -> Sing (Show_ t) Source # sShowList :: forall (t1 :: [First a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList 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 (ShowsPrec t1 t2 t3) Source # sShow_ :: forall (t :: Last a). Sing t -> Sing (Show_ t) Source # sShowList :: forall (t1 :: [Last a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList 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 # | |||||||||||||||||||||