singletons-base-3.3: A promoted and singled version of the base library
Copyright(C) 2018 Ryan Scott
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageGHC2021

Data.Functor.Singletons

Description

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

Synopsis

Documentation

class PFunctor (f :: Type -> Type) Source #

Associated Types

type Fmap (arg :: a ~> b) (arg1 :: f a) :: f b Source #

type (arg :: a) <$ (arg1 :: f b) :: f a infixl 4 Source #

type (arg :: a) <$ (arg1 :: f b) = Apply (Apply (TFHelper_6989586621679348493Sym0 :: TyFun a (f b ~> f a) -> Type) arg) arg1

Instances

Instances details
PFunctor Identity Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Identity a1)
type (a1 :: k1) <$ (a2 :: Identity b) 
Instance details

Defined in Data.Functor.Identity.Singletons

type (a1 :: k1) <$ (a2 :: Identity b)
PFunctor First Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: First a1) 
Instance details

Defined in Data.Monoid.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: First a1)
type (a1 :: k1) <$ (a2 :: First b) 
Instance details

Defined in Data.Monoid.Singletons

type (a1 :: k1) <$ (a2 :: First b)
PFunctor Last Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Last a1) 
Instance details

Defined in Data.Monoid.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Last a1)
type (a1 :: k1) <$ (a2 :: Last b) 
Instance details

Defined in Data.Monoid.Singletons

type (a1 :: k1) <$ (a2 :: Last b)
PFunctor Down Source # 
Instance details

Defined in Data.Functor.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Down a1) 
Instance details

Defined in Data.Functor.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Down a1)
type (a1 :: k1) <$ (a2 :: Down b) 
Instance details

Defined in Data.Functor.Singletons

type (a1 :: k1) <$ (a2 :: Down b)
PFunctor First Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: First a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: First a1)
type (a1 :: k1) <$ (a2 :: First b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a1 :: k1) <$ (a2 :: First b)
PFunctor Last Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Last a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Last a1)
type (a1 :: k1) <$ (a2 :: Last b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a1 :: k1) <$ (a2 :: Last b)
PFunctor Max Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Max a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Max a1)
type (a1 :: k1) <$ (a2 :: Max b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a1 :: k1) <$ (a2 :: Max b)
PFunctor Min Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Min a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Min a1)
type (a1 :: k1) <$ (a2 :: Min b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a1 :: k1) <$ (a2 :: Min b)
PFunctor Dual Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Dual a1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Fmap (a2 :: a1 ~> b) (a3 :: Dual a1)
type (a1 :: k1) <$ (a2 :: Dual b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a1 :: k1) <$ (a2 :: Dual b)
PFunctor Product Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Product a1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Fmap (a2 :: a1 ~> b) (a3 :: Product a1)
type (a1 :: k1) <$ (a2 :: Product b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a1 :: k1) <$ (a2 :: Product b)
PFunctor Sum Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Sum a1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Fmap (a2 :: a1 ~> b) (a3 :: Sum a1)
type (a1 :: k1) <$ (a2 :: Sum b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a1 :: k1) <$ (a2 :: Sum b)
PFunctor NonEmpty Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: NonEmpty a1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Fmap (a2 :: a1 ~> b) (a3 :: NonEmpty a1)
type (a1 :: k1) <$ (a2 :: NonEmpty b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a1 :: k1) <$ (a2 :: NonEmpty b)
PFunctor Maybe Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Maybe a1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Fmap (a2 :: a1 ~> b) (a3 :: Maybe a1)
type (a1 :: k1) <$ (a2 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a1 :: k1) <$ (a2 :: Maybe b)
PFunctor [] Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: [a1]) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Fmap (a2 :: a1 ~> b) (a3 :: [a1])
type (a1 :: k1) <$ (a2 :: [b]) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a1 :: k1) <$ (a2 :: [b])
PFunctor (Either a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

PFunctor (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Proxy a1) 
Instance details

Defined in Data.Proxy.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Proxy a1)
type (arg :: a) <$ (arg1 :: Proxy b) 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: a) <$ (arg1 :: Proxy b)
PFunctor (Arg a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PFunctor ((,) a) Source # 
Instance details

Defined in Data.Functor.Singletons

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

Defined in Data.Functor.Const.Singletons

PFunctor (Product f g) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

PFunctor (Sum f g) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

PFunctor (Compose f g) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

class SFunctor (f :: Type -> Type) where Source #

Minimal complete definition

sFmap

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: f a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: f b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) t1) t2) infixl 4 Source #

default (%<$) :: forall a b (t1 :: a) (t2 :: f b). Apply (Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) t1) t2 ~ Apply (Apply (TFHelper_6989586621679348493Sym0 :: TyFun a (f b ~> f a) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) t1) t2) Source #

Instances

Instances details
SFunctor Identity Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Identity a ~> Identity b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Identity b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Identity b ~> Identity a) -> Type) t1) t2) Source #

SFunctor First Source # 
Instance details

Defined in Data.Monoid.Singletons

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 # 
Instance details

Defined in Data.Monoid.Singletons

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 #

SFunctor Down Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Down a ~> Down b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Down b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Down b ~> Down a) -> Type) t1) t2) Source #

SFunctor First Source # 
Instance details

Defined in Data.Semigroup.Singletons

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 # 
Instance details

Defined in Data.Semigroup.Singletons

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 #

SFunctor Max Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Max a ~> Max b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Max b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Max b ~> Max a) -> Type) t1) t2) Source #

SFunctor Min Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Min a ~> Min b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Min b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Min b ~> Min a) -> Type) t1) t2) Source #

SFunctor Dual Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Dual a ~> Dual b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Dual b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Dual b ~> Dual a) -> Type) t1) t2) Source #

SFunctor Product Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Product a ~> Product b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Product b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Product b ~> Product a) -> Type) t1) t2) Source #

SFunctor Sum Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Sum a ~> Sum b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Sum b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Sum b ~> Sum a) -> Type) t1) t2) Source #

SFunctor NonEmpty Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (NonEmpty b ~> NonEmpty a) -> Type) t1) t2) Source #

SFunctor Maybe Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Maybe a ~> Maybe b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Maybe b ~> Maybe a) -> Type) t1) t2) Source #

SFunctor [] Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: [b]). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a ([b] ~> [a]) -> Type) t1) t2) Source #

SFunctor (Either a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sFmap :: forall a0 b (t1 :: a0 ~> b) (t2 :: Either a a0). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Either a a ~> Either a b) -> Type) t1) t2) Source #

(%<$) :: forall a0 b (t1 :: a0) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Either a b ~> Either a a) -> Type) t1) t2) Source #

SFunctor (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Proxy a ~> Proxy b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Proxy b ~> Proxy a) -> Type) t1) t2) Source #

SFunctor (Arg a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFmap :: forall a0 b (t1 :: a0 ~> b) (t2 :: Arg a a0). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Arg a a ~> Arg a b) -> Type) t1) t2) Source #

(%<$) :: forall a0 b (t1 :: a0) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Arg a b ~> Arg a a) -> Type) t1) t2) Source #

SFunctor ((,) a) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sFmap :: forall a0 b (t1 :: a0 ~> b) (t2 :: (a, a0)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) ((a, a) ~> (a, b)) -> Type) t1) t2) Source #

(%<$) :: forall a0 b (t1 :: a0) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a ((a, b) ~> (a, a)) -> Type) t1) t2) Source #

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

Defined in Data.Functor.Const.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Const m a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Const m a ~> Const m b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Const m b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Const m b ~> Const m a) -> Type) t1) t2) Source #

(SFunctor f, SFunctor g) => SFunctor (Product f g) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Product f g a ~> Product f g b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Product f g b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Product f g b ~> Product f g a) -> Type) t1) t2) Source #

(SFunctor f, SFunctor g) => SFunctor (Sum f g) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Sum f g a ~> Sum f g b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Sum f g b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Sum f g b ~> Sum f g a) -> Type) t1) t2) Source #

(SFunctor f, SFunctor g) => SFunctor (Compose f g) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Compose f g a ~> Compose f g b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Compose f g b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Compose f g b ~> Compose f g a) -> Type) t1) t2) Source #

type family (a1 :: f a) $> (a2 :: b) :: f b where ... infixl 4 Source #

Equations

(a_6989586621679532894 :: f b) $> (a_6989586621679532896 :: k1) = Apply (Apply (Apply (FlipSym0 :: TyFun (k1 ~> (f b ~> f k1)) (f b ~> (k1 ~> f k1)) -> Type) ((<$@#@$) :: TyFun k1 (f b ~> f k1) -> Type)) a_6989586621679532894) a_6989586621679532896 

(%$>) :: forall (f :: Type -> Type) a b (t1 :: f a) (t2 :: b). SFunctor f => Sing t1 -> Sing t2 -> Sing (Apply (Apply (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) t1) t2) infixl 4 Source #

type family (a1 :: a ~> b) <$> (a2 :: f a) :: f b where ... infixl 4 Source #

Equations

(a_6989586621679532912 :: a ~> b) <$> (a_6989586621679532914 :: f a) = Apply (Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) a_6989586621679532912) a_6989586621679532914 

(%<$>) :: forall a b (f :: Type -> Type) (t1 :: a ~> b) (t2 :: f a). SFunctor f => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) t1) t2) infixl 4 Source #

type family (a1 :: f a) <&> (a2 :: a ~> b) :: f b where ... infixl 1 Source #

Equations

(as :: f1 a) <&> (f2 :: a ~> b) = Apply (Apply ((<$>@#@$) :: TyFun (a ~> b) (f1 a ~> f1 b) -> Type) f2) as 

(%<&>) :: forall (f :: Type -> Type) a b (t1 :: f a) (t2 :: a ~> b). SFunctor f => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) t1) t2) infixl 1 Source #

type family Void (a1 :: f a) :: f () where ... Source #

Equations

Void (x :: f b) = Apply (Apply ((<$@#@$) :: TyFun () (f b ~> f ()) -> Type) Tuple0Sym0) x 

sVoid :: forall (f :: Type -> Type) a (t :: f a). SFunctor f => Sing t -> Sing (Apply (VoidSym0 :: TyFun (f a) (f ()) -> Type) t) Source #

Defunctionalization symbols

data FmapSym0 (a1 :: TyFun (a ~> b) (f a ~> f b)) Source #

Instances

Instances details
SFunctor f => SingI (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) #

SuppressUnusedWarnings (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679348484 :: a ~> b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679348484 :: a ~> b) = FmapSym1 a6989586621679348484 :: TyFun (f a) (f b) -> Type

data FmapSym1 (a6989586621679348484 :: a ~> b) (b1 :: TyFun (f a) (f b)) Source #

Instances

Instances details
SFunctor f => SingI1 (FmapSym1 :: (a ~> b) -> TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (FmapSym1 x :: TyFun (f a) (f b) -> Type) #

(SFunctor f, SingI d) => SingI (FmapSym1 d :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (FmapSym1 d :: TyFun (f a) (f b) -> Type) #

SuppressUnusedWarnings (FmapSym1 a6989586621679348484 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym1 a6989586621679348484 :: TyFun (f a) (f b) -> Type) (a6989586621679348485 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym1 a6989586621679348484 :: TyFun (f a) (f b) -> Type) (a6989586621679348485 :: f a) = Fmap a6989586621679348484 a6989586621679348485

type family FmapSym2 (a6989586621679348484 :: a ~> b) (a6989586621679348485 :: f a) :: f b where ... Source #

Equations

FmapSym2 (a6989586621679348484 :: a ~> b) (a6989586621679348485 :: f a) = Fmap a6989586621679348484 a6989586621679348485 

data (<$@#@$) (a1 :: TyFun a (f b ~> f a)) infixl 4 Source #

Instances

Instances details
SFunctor f => SingI ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) #

SuppressUnusedWarnings ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) (a6989586621679348489 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) (a6989586621679348489 :: a) = (<$@#@$$) a6989586621679348489 :: TyFun (f b) (f a) -> Type

data (a6989586621679348489 :: a) <$@#@$$ (b1 :: TyFun (f b) (f a)) infixl 4 Source #

Instances

Instances details
SFunctor f => SingI1 ((<$@#@$$) :: a -> TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<$@#@$$) x :: TyFun (f b) (f a) -> Type) #

(SFunctor f, SingI d) => SingI ((<$@#@$$) d :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<$@#@$$) d :: TyFun (f b) (f a) -> Type) #

SuppressUnusedWarnings ((<$@#@$$) a6989586621679348489 :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<$@#@$$) a6989586621679348489 :: TyFun (f b) (f a) -> Type) (a6989586621679348490 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<$@#@$$) a6989586621679348489 :: TyFun (f b) (f a) -> Type) (a6989586621679348490 :: f b) = a6989586621679348489 <$ a6989586621679348490

type family (a6989586621679348489 :: a) <$@#@$$$ (a6989586621679348490 :: f b) :: f a where ... infixl 4 Source #

Equations

(a6989586621679348489 :: a) <$@#@$$$ (a6989586621679348490 :: f b) = a6989586621679348489 <$ a6989586621679348490 

data ($>@#@$) (a1 :: TyFun (f a) (b ~> f b)) infixl 4 Source #

Instances

Instances details
SFunctor f => SingI (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) #

SuppressUnusedWarnings (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) (a6989586621679532901 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) (a6989586621679532901 :: f a) = ($>@#@$$) a6989586621679532901 :: TyFun b (f b) -> Type

data (a6989586621679532901 :: f a) $>@#@$$ (b1 :: TyFun b (f b)) infixl 4 Source #

Instances

Instances details
SFunctor f => SingI1 (($>@#@$$) :: f a -> TyFun b (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

liftSing :: forall (x :: f a). Sing x -> Sing (($>@#@$$) x :: TyFun b (f b) -> Type) #

(SFunctor f, SingI d) => SingI (($>@#@$$) d :: TyFun b (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing (($>@#@$$) d :: TyFun b (f b) -> Type) #

SuppressUnusedWarnings (($>@#@$$) a6989586621679532901 :: TyFun b (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply (($>@#@$$) a6989586621679532901 :: TyFun b (f b) -> Type) (a6989586621679532902 :: b) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply (($>@#@$$) a6989586621679532901 :: TyFun b (f b) -> Type) (a6989586621679532902 :: b) = a6989586621679532901 $> a6989586621679532902

type family (a6989586621679532901 :: f a) $>@#@$$$ (a6989586621679532902 :: b) :: f b where ... infixl 4 Source #

Equations

(a6989586621679532901 :: f a) $>@#@$$$ (a6989586621679532902 :: b) = a6989586621679532901 $> a6989586621679532902 

data (<$>@#@$) (a1 :: TyFun (a ~> b) (f a ~> f b)) infixl 4 Source #

Instances

Instances details
SFunctor f => SingI ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) #

SuppressUnusedWarnings ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679532919 :: a ~> b) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679532919 :: a ~> b) = (<$>@#@$$) a6989586621679532919 :: TyFun (f a) (f b) -> Type

data (a6989586621679532919 :: a ~> b) <$>@#@$$ (b1 :: TyFun (f a) (f b)) infixl 4 Source #

Instances

Instances details
SFunctor f => SingI1 ((<$>@#@$$) :: (a ~> b) -> TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing ((<$>@#@$$) x :: TyFun (f a) (f b) -> Type) #

(SFunctor f, SingI d) => SingI ((<$>@#@$$) d :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing ((<$>@#@$$) d :: TyFun (f a) (f b) -> Type) #

SuppressUnusedWarnings ((<$>@#@$$) a6989586621679532919 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<$>@#@$$) a6989586621679532919 :: TyFun (f a) (f b) -> Type) (a6989586621679532920 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<$>@#@$$) a6989586621679532919 :: TyFun (f a) (f b) -> Type) (a6989586621679532920 :: f a) = a6989586621679532919 <$> a6989586621679532920

type family (a6989586621679532919 :: a ~> b) <$>@#@$$$ (a6989586621679532920 :: f a) :: f b where ... infixl 4 Source #

Equations

(a6989586621679532919 :: a ~> b) <$>@#@$$$ (a6989586621679532920 :: f a) = a6989586621679532919 <$> a6989586621679532920 

data (<&>@#@$) (a1 :: TyFun (f a) ((a ~> b) ~> f b)) infixl 1 Source #

Instances

Instances details
SFunctor f => SingI ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) #

SuppressUnusedWarnings ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) (a6989586621679532908 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) (a6989586621679532908 :: f a) = (<&>@#@$$) a6989586621679532908 :: TyFun (a ~> b) (f b) -> Type

data (a6989586621679532908 :: f a) <&>@#@$$ (b1 :: TyFun (a ~> b) (f b)) infixl 1 Source #

Instances

Instances details
SFunctor f => SingI1 ((<&>@#@$$) :: f a -> TyFun (a ~> b) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

liftSing :: forall (x :: f a). Sing x -> Sing ((<&>@#@$$) x :: TyFun (a ~> b) (f b) -> Type) #

(SFunctor f, SingI d) => SingI ((<&>@#@$$) d :: TyFun (a ~> b) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing ((<&>@#@$$) d :: TyFun (a ~> b) (f b) -> Type) #

SuppressUnusedWarnings ((<&>@#@$$) a6989586621679532908 :: TyFun (a ~> b) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<&>@#@$$) a6989586621679532908 :: TyFun (a ~> b) (f b) -> Type) (a6989586621679532909 :: a ~> b) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<&>@#@$$) a6989586621679532908 :: TyFun (a ~> b) (f b) -> Type) (a6989586621679532909 :: a ~> b) = a6989586621679532908 <&> a6989586621679532909

type family (a6989586621679532908 :: f a) <&>@#@$$$ (a6989586621679532909 :: a ~> b) :: f b where ... infixl 1 Source #

Equations

(a6989586621679532908 :: f a) <&>@#@$$$ (a6989586621679532909 :: a ~> b) = a6989586621679532908 <&> a6989586621679532909 

data VoidSym0 (a1 :: TyFun (f a) (f ())) Source #

Instances

Instances details
SFunctor f => SingI (VoidSym0 :: TyFun (f a) (f ()) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing (VoidSym0 :: TyFun (f a) (f ()) -> Type) #

SuppressUnusedWarnings (VoidSym0 :: TyFun (f a) (f ()) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply (VoidSym0 :: TyFun (f a) (f ()) -> Type) (a6989586621679532892 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply (VoidSym0 :: TyFun (f a) (f ()) -> Type) (a6989586621679532892 :: f a) = Void a6989586621679532892

type family VoidSym1 (a6989586621679532892 :: f a) :: f () where ... Source #

Equations

VoidSym1 (a6989586621679532892 :: f a) = Void a6989586621679532892 

Orphan instances

PFunctor Down Source # 
Instance details

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Down a1) 
Instance details

Defined in Data.Functor.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Down a1)
type (a1 :: k1) <$ (a2 :: Down b) 
Instance details

Defined in Data.Functor.Singletons

type (a1 :: k1) <$ (a2 :: Down b)
SFunctor Down Source # 
Instance details

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Down a ~> Down b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Down b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Down b ~> Down a) -> Type) t1) t2) Source #

PFunctor ((,) a) Source # 
Instance details

SFunctor ((,) a) Source # 
Instance details

Methods

sFmap :: forall a0 b (t1 :: a0 ~> b) (t2 :: (a, a0)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) ((a, a) ~> (a, b)) -> Type) t1) t2) Source #

(%<$) :: forall a0 b (t1 :: a0) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a ((a, b) ~> (a, a)) -> Type) t1) t2) Source #