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

Control.Monad.Fail.Singletons

Description

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

Synopsis

Documentation

class PMonadFail m 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 arg :: m a Source #

PMonadFail [] Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Associated Types

type Fail arg :: m a Source #

class SMonad m => SMonadFail m where Source #

Methods

sFail :: forall a (t :: [Char]). Sing t -> Sing (Apply FailSym0 t :: m a) 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 t) Source #

SMonadFail [] Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Methods

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

Defunctionalization symbols

data FailSym0 :: (~>) [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

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

Defined in Control.Monad.Fail.Singletons

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

Defined in Control.Monad.Fail.Singletons

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

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

Equations

FailSym1 a6989586621679540843 = Fail a6989586621679540843