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

Control.Monad.Zip.Singletons

Description

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

Synopsis

Documentation

class PMonadZip (m :: Type -> Type) Source #

Associated Types

type Mzip (arg :: m a) (arg1 :: m b) :: m (a, b) Source #

type Mzip (arg :: m a) (arg1 :: m b) = Apply (Apply (Mzip_6989586621681083545Sym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) arg) arg1

type MzipWith (arg :: a ~> (b ~> c)) (arg1 :: m a) (arg2 :: m b) :: m c Source #

type MzipWith (arg :: a ~> (b ~> c)) (arg1 :: m a) (arg2 :: m b) = Apply (Apply (Apply (MzipWith_6989586621681083561Sym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) arg) arg1) arg2

type Munzip (arg :: m (a, b)) :: (m a, m b) Source #

type Munzip (arg :: m (a, b)) = Apply (Munzip_6989586621681083574Sym0 :: TyFun (m (a, b)) (m a, m b) -> Type) arg

Instances

Instances details
PMonadZip Identity Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Associated Types

type Mzip (arg1 :: Identity a) (arg2 :: Identity b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Mzip (arg1 :: Identity a) (arg2 :: Identity b)
type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Identity a1) (a4 :: Identity b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Identity a1) (a4 :: Identity b)
type Munzip (a2 :: Identity (a1, b)) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Munzip (a2 :: Identity (a1, b))
PMonadZip First Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Associated Types

type Mzip (arg1 :: First a) (arg2 :: First b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Mzip (arg1 :: First a) (arg2 :: First b)
type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: First a1) (a4 :: First b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: First a1) (a4 :: First b)
type Munzip (arg :: First (a, b)) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Munzip (arg :: First (a, b))
PMonadZip Last Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Associated Types

type Mzip (arg1 :: Last a) (arg2 :: Last b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Mzip (arg1 :: Last a) (arg2 :: Last b)
type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Last a1) (a4 :: Last b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Last a1) (a4 :: Last b)
type Munzip (arg :: Last (a, b)) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Munzip (arg :: Last (a, b))
PMonadZip Dual Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Associated Types

type Mzip (arg1 :: Dual a) (arg2 :: Dual b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Mzip (arg1 :: Dual a) (arg2 :: Dual b)
type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Dual a1) (a4 :: Dual b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Dual a1) (a4 :: Dual b)
type Munzip (arg :: Dual (a, b)) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Munzip (arg :: Dual (a, b))
PMonadZip Product Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Associated Types

type Mzip (arg1 :: Product a) (arg2 :: Product b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Mzip (arg1 :: Product a) (arg2 :: Product b)
type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Product a1) (a4 :: Product b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Product a1) (a4 :: Product b)
type Munzip (arg :: Product (a, b)) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Munzip (arg :: Product (a, b))
PMonadZip Sum Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Associated Types

type Mzip (arg1 :: Sum a) (arg2 :: Sum b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Mzip (arg1 :: Sum a) (arg2 :: Sum b)
type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Sum a1) (a4 :: Sum b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Sum a1) (a4 :: Sum b)
type Munzip (arg :: Sum (a, b)) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Munzip (arg :: Sum (a, b))
PMonadZip NonEmpty Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Associated Types

type Mzip (a2 :: NonEmpty a1) (a3 :: NonEmpty b) 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Mzip (a2 :: NonEmpty a1) (a3 :: NonEmpty b)
type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: NonEmpty a1) (a4 :: NonEmpty b) 
Instance details

Defined in Data.List.NonEmpty.Singletons

type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: NonEmpty a1) (a4 :: NonEmpty b)
type Munzip (a2 :: NonEmpty (a1, b)) 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Munzip (a2 :: NonEmpty (a1, b))
PMonadZip Maybe Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Associated Types

type Mzip (arg1 :: Maybe a) (arg2 :: Maybe b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Mzip (arg1 :: Maybe a) (arg2 :: Maybe b)
type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Maybe a1) (a4 :: Maybe b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Maybe a1) (a4 :: Maybe b)
type Munzip (arg :: Maybe (a, b)) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Munzip (arg :: Maybe (a, b))
PMonadZip [] Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Associated Types

type Mzip (a2 :: [a1]) (a3 :: [b]) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Mzip (a2 :: [a1]) (a3 :: [b])
type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: [a1]) (a4 :: [b]) 
Instance details

Defined in Control.Monad.Zip.Singletons

type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: [a1]) (a4 :: [b])
type Munzip (a2 :: [(a1, b)]) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Munzip (a2 :: [(a1, b)])
PMonadZip (Proxy :: Type -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Associated Types

type Mzip (arg1 :: Proxy a) (arg2 :: Proxy b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Mzip (arg1 :: Proxy a) (arg2 :: Proxy b)
type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Proxy a1) (a4 :: Proxy b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Proxy a1) (a4 :: Proxy b)
type Munzip (arg :: Proxy (a, b)) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Munzip (arg :: Proxy (a, b))
PMonadZip (Product f g) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

class SMonad m => SMonadZip (m :: Type -> Type) where Source #

Minimal complete definition

Nothing

Methods

sMzip :: forall a b (t1 :: m a) (t2 :: m b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) t1) t2) Source #

default sMzip :: forall a b (t1 :: m a) (t2 :: m b). Apply (Apply (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) t1) t2 ~ Apply (Apply (Mzip_6989586621681083545Sym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) t1) t2) Source #

sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: m a) (t3 :: m b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) t1) t2) t3) Source #

default sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: m a) (t3 :: m b). Apply (Apply (Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) t1) t2) t3 ~ Apply (Apply (Apply (MzipWith_6989586621681083561Sym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) t1) t2) t3 => Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) t1) t2) t3) Source #

sMunzip :: forall a b (t :: m (a, b)). Sing t -> Sing (Apply (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) t) Source #

default sMunzip :: forall a b (t :: m (a, b)). Apply (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) t ~ Apply (Munzip_6989586621681083574Sym0 :: TyFun (m (a, b)) (m a, m b) -> Type) t => Sing t -> Sing (Apply (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) t) Source #

Instances

Instances details
SMonadZip Identity Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sMzip :: forall a b (t1 :: Identity a) (t2 :: Identity b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MzipSym0 :: TyFun (Identity a) (Identity b ~> Identity (a, b)) -> Type) t1) t2) Source #

sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Identity a) (t3 :: Identity b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (Identity a ~> (Identity b ~> Identity c)) -> Type) t1) t2) t3) Source #

sMunzip :: forall a b (t :: Identity (a, b)). Sing t -> Sing (Apply (MunzipSym0 :: TyFun (Identity (a, b)) (Identity a, Identity b) -> Type) t) Source #

SMonadZip First Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sMzip :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MzipSym0 :: TyFun (First a) (First b ~> First (a, b)) -> Type) t1) t2) Source #

sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: First a) (t3 :: First b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (First a ~> (First b ~> First c)) -> Type) t1) t2) t3) Source #

sMunzip :: forall a b (t :: First (a, b)). Sing t -> Sing (Apply (MunzipSym0 :: TyFun (First (a, b)) (First a, First b) -> Type) t) Source #

SMonadZip Last Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sMzip :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MzipSym0 :: TyFun (Last a) (Last b ~> Last (a, b)) -> Type) t1) t2) Source #

sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Last a) (t3 :: Last b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (Last a ~> (Last b ~> Last c)) -> Type) t1) t2) t3) Source #

sMunzip :: forall a b (t :: Last (a, b)). Sing t -> Sing (Apply (MunzipSym0 :: TyFun (Last (a, b)) (Last a, Last b) -> Type) t) Source #

SMonadZip Dual Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sMzip :: forall a b (t1 :: Dual a) (t2 :: Dual b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MzipSym0 :: TyFun (Dual a) (Dual b ~> Dual (a, b)) -> Type) t1) t2) Source #

sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Dual a) (t3 :: Dual b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (Dual a ~> (Dual b ~> Dual c)) -> Type) t1) t2) t3) Source #

sMunzip :: forall a b (t :: Dual (a, b)). Sing t -> Sing (Apply (MunzipSym0 :: TyFun (Dual (a, b)) (Dual a, Dual b) -> Type) t) Source #

SMonadZip Product Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sMzip :: forall a b (t1 :: Product a) (t2 :: Product b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MzipSym0 :: TyFun (Product a) (Product b ~> Product (a, b)) -> Type) t1) t2) Source #

sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Product a) (t3 :: Product b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (Product a ~> (Product b ~> Product c)) -> Type) t1) t2) t3) Source #

sMunzip :: forall a b (t :: Product (a, b)). Sing t -> Sing (Apply (MunzipSym0 :: TyFun (Product (a, b)) (Product a, Product b) -> Type) t) Source #

SMonadZip Sum Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sMzip :: forall a b (t1 :: Sum a) (t2 :: Sum b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MzipSym0 :: TyFun (Sum a) (Sum b ~> Sum (a, b)) -> Type) t1) t2) Source #

sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Sum a) (t3 :: Sum b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (Sum a ~> (Sum b ~> Sum c)) -> Type) t1) t2) t3) Source #

sMunzip :: forall a b (t :: Sum (a, b)). Sing t -> Sing (Apply (MunzipSym0 :: TyFun (Sum (a, b)) (Sum a, Sum b) -> Type) t) Source #

SMonadZip NonEmpty Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sMzip :: forall a b (t1 :: NonEmpty a) (t2 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MzipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) t1) t2) Source #

sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: NonEmpty a) (t3 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) t1) t2) t3) Source #

sMunzip :: forall a b (t :: NonEmpty (a, b)). Sing t -> Sing (Apply (MunzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) t) Source #

SMonadZip Maybe Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sMzip :: forall a b (t1 :: Maybe a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MzipSym0 :: TyFun (Maybe a) (Maybe b ~> Maybe (a, b)) -> Type) t1) t2) Source #

sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Maybe a) (t3 :: Maybe b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (Maybe a ~> (Maybe b ~> Maybe c)) -> Type) t1) t2) t3) Source #

sMunzip :: forall a b (t :: Maybe (a, b)). Sing t -> Sing (Apply (MunzipSym0 :: TyFun (Maybe (a, b)) (Maybe a, Maybe b) -> Type) t) Source #

SMonadZip [] Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

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

sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: [a]) (t3 :: [b]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) t1) t2) t3) Source #

sMunzip :: forall a b (t :: [(a, b)]). Sing t -> Sing (Apply (MunzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) t) Source #

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

Defined in Control.Monad.Zip.Singletons

Methods

sMzip :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MzipSym0 :: TyFun (Proxy a) (Proxy b ~> Proxy (a, b)) -> Type) t1) t2) Source #

sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Proxy a) (t3 :: Proxy b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (Proxy a ~> (Proxy b ~> Proxy c)) -> Type) t1) t2) t3) Source #

sMunzip :: forall a b (t :: Proxy (a, b)). Sing t -> Sing (Apply (MunzipSym0 :: TyFun (Proxy (a, b)) (Proxy a, Proxy b) -> Type) t) Source #

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

Defined in Data.Functor.Product.Singletons

Methods

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

sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Product f g a) (t3 :: Product f g b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (Product f g a ~> (Product f g b ~> Product f g c)) -> Type) t1) t2) t3) Source #

sMunzip :: forall a b (t :: Product f g (a, b)). Sing t -> Sing (Apply (MunzipSym0 :: TyFun (Product f g (a, b)) (Product f g a, Product f g b) -> Type) t) Source #

Defunctionalization symbols

data MzipSym0 (a1 :: TyFun (m a) (m b ~> m (a, b))) Source #

Instances

Instances details
SMonadZip m => SingI (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) #

SuppressUnusedWarnings (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) (a6989586621681083531 :: m a) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) (a6989586621681083531 :: m a) = MzipSym1 a6989586621681083531 :: TyFun (m b) (m (a, b)) -> Type

data MzipSym1 (a6989586621681083531 :: m a) (b1 :: TyFun (m b) (m (a, b))) Source #

Instances

Instances details
SMonadZip m => SingI1 (MzipSym1 :: m a -> TyFun (m b) (m (a, b)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

liftSing :: forall (x :: m a). Sing x -> Sing (MzipSym1 x :: TyFun (m b) (m (a, b)) -> Type) #

(SMonadZip m, SingI d) => SingI (MzipSym1 d :: TyFun (m b) (m (a, b)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MzipSym1 d :: TyFun (m b) (m (a, b)) -> Type) #

SuppressUnusedWarnings (MzipSym1 a6989586621681083531 :: TyFun (m b) (m (a, b)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipSym1 a6989586621681083531 :: TyFun (m b) (m (a, b)) -> Type) (a6989586621681083532 :: m b) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipSym1 a6989586621681083531 :: TyFun (m b) (m (a, b)) -> Type) (a6989586621681083532 :: m b) = Mzip a6989586621681083531 a6989586621681083532

type family MzipSym2 (a6989586621681083531 :: m a) (a6989586621681083532 :: m b) :: m (a, b) where ... Source #

Equations

MzipSym2 (a6989586621681083531 :: m a) (a6989586621681083532 :: m b) = Mzip a6989586621681083531 a6989586621681083532 

data MzipWithSym0 (a1 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c))) Source #

Instances

Instances details
SMonadZip m => SingI (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) #

SuppressUnusedWarnings (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) (a6989586621681083537 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) (a6989586621681083537 :: a ~> (b ~> c)) = MzipWithSym1 a6989586621681083537 :: TyFun (m a) (m b ~> m c) -> Type

data MzipWithSym1 (a6989586621681083537 :: a ~> (b ~> c)) (b1 :: TyFun (m a) (m b ~> m c)) Source #

Instances

Instances details
SMonadZip m => SingI1 (MzipWithSym1 :: (a ~> (b ~> c)) -> TyFun (m a) (m b ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (MzipWithSym1 x :: TyFun (m a) (m b ~> m c) -> Type) #

(SMonadZip m, SingI d) => SingI (MzipWithSym1 d :: TyFun (m a) (m b ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MzipWithSym1 d :: TyFun (m a) (m b ~> m c) -> Type) #

SuppressUnusedWarnings (MzipWithSym1 a6989586621681083537 :: TyFun (m a) (m b ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipWithSym1 a6989586621681083537 :: TyFun (m a) (m b ~> m c) -> Type) (a6989586621681083538 :: m a) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipWithSym1 a6989586621681083537 :: TyFun (m a) (m b ~> m c) -> Type) (a6989586621681083538 :: m a) = MzipWithSym2 a6989586621681083537 a6989586621681083538

data MzipWithSym2 (a6989586621681083537 :: a ~> (b ~> c)) (a6989586621681083538 :: m a) (c1 :: TyFun (m b) (m c)) Source #

Instances

Instances details
(SMonadZip m, SingI d) => SingI1 (MzipWithSym2 d :: m a -> TyFun (m b) (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

liftSing :: forall (x :: m a). Sing x -> Sing (MzipWithSym2 d x) #

SMonadZip m => SingI2 (MzipWithSym2 :: (a ~> (b ~> c)) -> m a -> TyFun (m b) (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> c)) (y :: m a). Sing x -> Sing y -> Sing (MzipWithSym2 x y) #

(SMonadZip m, SingI d1, SingI d2) => SingI (MzipWithSym2 d1 d2 :: TyFun (m b) (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MzipWithSym2 d1 d2) #

SuppressUnusedWarnings (MzipWithSym2 a6989586621681083537 a6989586621681083538 :: TyFun (m b) (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipWithSym2 a6989586621681083537 a6989586621681083538 :: TyFun (m b) (m c) -> Type) (a6989586621681083539 :: m b) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipWithSym2 a6989586621681083537 a6989586621681083538 :: TyFun (m b) (m c) -> Type) (a6989586621681083539 :: m b) = MzipWith a6989586621681083537 a6989586621681083538 a6989586621681083539

type family MzipWithSym3 (a6989586621681083537 :: a ~> (b ~> c)) (a6989586621681083538 :: m a) (a6989586621681083539 :: m b) :: m c where ... Source #

Equations

MzipWithSym3 (a6989586621681083537 :: a ~> (b ~> c)) (a6989586621681083538 :: m a) (a6989586621681083539 :: m b) = MzipWith a6989586621681083537 a6989586621681083538 a6989586621681083539 

data MunzipSym0 (a1 :: TyFun (m (a, b)) (m a, m b)) Source #

Instances

Instances details
SMonadZip m => SingI (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) #

SuppressUnusedWarnings (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) (a6989586621681083542 :: m (a, b)) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) (a6989586621681083542 :: m (a, b)) = Munzip a6989586621681083542

type family MunzipSym1 (a6989586621681083542 :: m (a, b)) :: (m a, m b) where ... Source #

Equations

MunzipSym1 (a6989586621681083542 :: m (a, b)) = Munzip a6989586621681083542