typelevel-1.2.3: Useful type level operations (type families and related operators).

Safe HaskellNone
LanguageHaskell2010

Type.Inference

Synopsis

Documentation

type KnownType cls t = KnownTypeT cls t Identity Source #

The Inferable type class describes a monad with a functional dependency on the given type. It allows for writing polymorphic code and ensuring Haskell that the type will be resolved while evaluating the monadic stack.

newtype KnownTypeT (cls :: ck) (t :: tk) (m :: * -> *) (a :: *) Source #

Constructors

KnownTypeT (IdentityT m a) 
Instances
MonadTrans (KnownTypeT cls t) Source # 
Instance details

Defined in Type.Inference

Methods

lift :: Monad m => m a -> KnownTypeT cls t m a #

Monad m => Monad (KnownTypeT cls t m) Source # 
Instance details

Defined in Type.Inference

Methods

(>>=) :: KnownTypeT cls t m a -> (a -> KnownTypeT cls t m b) -> KnownTypeT cls t m b #

(>>) :: KnownTypeT cls t m a -> KnownTypeT cls t m b -> KnownTypeT cls t m b #

return :: a -> KnownTypeT cls t m a #

fail :: String -> KnownTypeT cls t m a #

Functor m => Functor (KnownTypeT cls t m) Source # 
Instance details

Defined in Type.Inference

Methods

fmap :: (a -> b) -> KnownTypeT cls t m a -> KnownTypeT cls t m b #

(<$) :: a -> KnownTypeT cls t m b -> KnownTypeT cls t m a #

MonadFix m => MonadFix (KnownTypeT cls t m) Source # 
Instance details

Defined in Type.Inference

Methods

mfix :: (a -> KnownTypeT cls t m a) -> KnownTypeT cls t m a #

Applicative m => Applicative (KnownTypeT cls t m) Source # 
Instance details

Defined in Type.Inference

Methods

pure :: a -> KnownTypeT cls t m a #

(<*>) :: KnownTypeT cls t m (a -> b) -> KnownTypeT cls t m a -> KnownTypeT cls t m b #

liftA2 :: (a -> b -> c) -> KnownTypeT cls t m a -> KnownTypeT cls t m b -> KnownTypeT cls t m c #

(*>) :: KnownTypeT cls t m a -> KnownTypeT cls t m b -> KnownTypeT cls t m b #

(<*) :: KnownTypeT cls t m a -> KnownTypeT cls t m b -> KnownTypeT cls t m a #

MonadIO m => MonadIO (KnownTypeT cls t m) Source # 
Instance details

Defined in Type.Inference

Methods

liftIO :: IO a -> KnownTypeT cls t m a #

Alternative m => Alternative (KnownTypeT cls t m) Source # 
Instance details

Defined in Type.Inference

Methods

empty :: KnownTypeT cls t m a #

(<|>) :: KnownTypeT cls t m a -> KnownTypeT cls t m a -> KnownTypeT cls t m a #

some :: KnownTypeT cls t m a -> KnownTypeT cls t m [a] #

many :: KnownTypeT cls t m a -> KnownTypeT cls t m [a] #

MonadPlus m => MonadPlus (KnownTypeT cls t m) Source # 
Instance details

Defined in Type.Inference

Methods

mzero :: KnownTypeT cls t m a #

mplus :: KnownTypeT cls t m a -> KnownTypeT cls t m a -> KnownTypeT cls t m a #

MonadThrow m => MonadThrow (KnownTypeT cls t m) Source # 
Instance details

Defined in Type.Inference

Methods

throwM :: Exception e => e -> KnownTypeT cls t m a #

MonadCatch m => MonadCatch (KnownTypeT cls t m) Source # 
Instance details

Defined in Type.Inference

Methods

catch :: Exception e => KnownTypeT cls t m a -> (e -> KnownTypeT cls t m a) -> KnownTypeT cls t m a #

MonadMask m => MonadMask (KnownTypeT cls t m) Source # 
Instance details

Defined in Type.Inference

Methods

mask :: ((forall a. KnownTypeT cls t m a -> KnownTypeT cls t m a) -> KnownTypeT cls t m b) -> KnownTypeT cls t m b #

uninterruptibleMask :: ((forall a. KnownTypeT cls t m a -> KnownTypeT cls t m a) -> KnownTypeT cls t m b) -> KnownTypeT cls t m b #

generalBracket :: KnownTypeT cls t m a -> (a -> ExitCase b -> KnownTypeT cls t m c) -> (a -> KnownTypeT cls t m b) -> KnownTypeT cls t m (b, c) #

PrimMonad m => PrimMonad (KnownTypeT cls t m) Source # 
Instance details

Defined in Type.Inference

Associated Types

type PrimState (KnownTypeT cls t m) :: Type #

Methods

primitive :: (State# (PrimState (KnownTypeT cls t m)) -> (#State# (PrimState (KnownTypeT cls t m)), a#)) -> KnownTypeT cls t m a #

(Show1 m, Show a) => Show (KnownTypeT cls t m a) Source # 
Instance details

Defined in Type.Inference

Methods

showsPrec :: Int -> KnownTypeT cls t m a -> ShowS #

show :: KnownTypeT cls t m a -> String #

showList :: [KnownTypeT cls t m a] -> ShowS #

Wrapped (KnownTypeT cls t m a) Source # 
Instance details

Defined in Type.Inference

Associated Types

type Unwrapped (KnownTypeT cls t m a) :: Type #

Methods

_Wrapped' :: Iso' (KnownTypeT cls t m a) (Unwrapped (KnownTypeT cls t m a)) #

KnownTypeT cls1 t1 m1 a1 ~ t2 => Rewrapped (KnownTypeT cls2 t3 m2 a2) t2 Source # 
Instance details

Defined in Type.Inference

type PrimState (KnownTypeT cls t m) Source # 
Instance details

Defined in Type.Inference

type PrimState (KnownTypeT cls t m) = PrimState m
type Unwrapped (KnownTypeT cls t m a) Source # 
Instance details

Defined in Type.Inference

type Unwrapped (KnownTypeT cls t m a) = IdentityT m a

type family Infer (p :: k) m where ... Source #

Equations

Infer p (KnownTypeT p t m) = t 
Infer p (t m) = Infer p m 

type family TryInfer (p :: k) m a :: Constraint where ... Source #

Equations

TryInfer p (KnownTypeT p t m) a = a ~ t 
TryInfer p (t m) a = TryInfer p m a 
TryInfer p m a = () 

inferT :: forall cls t m a. KnownTypeT cls t m a -> m a Source #