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

Control.Monad.Fail.Singletons

Description

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

Synopsis

Documentation

class PMonadFail (m :: k -> Type) Source #

Associated Types

type Fail (arg :: [Char]) :: m a Source #

Instances

Instances details
PMonadFail Maybe Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Associated Types

type Fail a2 
Instance details

Defined in Control.Monad.Fail.Singletons

type Fail a2
PMonadFail [] Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Associated Types

type Fail a2 
Instance details

Defined in Control.Monad.Fail.Singletons

type Fail a2

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

Methods

sFail :: forall a (t :: [Char]). Sing t -> Sing (Apply (FailSym0 :: TyFun [Char] (m a) -> Type) t) Source #

Instances

Instances details
SMonadFail Maybe Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Methods

sFail :: forall a (t :: [Char]). Sing t -> Sing (Apply (FailSym0 :: TyFun [Char] (Maybe a) -> Type) t) Source #

SMonadFail [] Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Methods

sFail :: forall a (t :: [Char]). Sing t -> Sing (Apply (FailSym0 :: TyFun [Char] [a] -> Type) t) Source #

Defunctionalization symbols

data FailSym0 (a1 :: TyFun [Char] (m a)) Source #

Instances

Instances details
SMonadFail m => SingI (FailSym0 :: TyFun [Char] (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Methods

sing :: Sing (FailSym0 :: TyFun [Char] (m a) -> Type) #

SuppressUnusedWarnings (FailSym0 :: TyFun [Char] (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

type Apply (FailSym0 :: TyFun [Char] (m a) -> Type) (a6989586621679549513 :: [Char]) Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

type Apply (FailSym0 :: TyFun [Char] (m a) -> Type) (a6989586621679549513 :: [Char]) = Fail a6989586621679549513 :: m a

type family FailSym1 (a6989586621679549513 :: [Char]) :: m a where ... Source #

Equations

FailSym1 a6989586621679549513 = Fail a6989586621679549513 :: m a