registry-0.2.1.0: data structure for assembling components
Safe HaskellNone
LanguageHaskell2010

Data.Registry.Lift

Contents

Description

This code is taken from https://stackoverflow.com/questions/28003135/is-it-possible-to-encode-a-generic-lift-function-in-haskell

to allow a generic lift operation over an Applicative context So if you have a function: Int -> Text -> IO Int, it can be lifted to have all of its parameters in IO:

 f :: Int -> Text -> IO Int

 lifted :: IO Int -> IO Text -> IO Int
 lifted = to @IO f
Synopsis

Documentation

class Applicative f => ApplyVariadic f a b where Source #

Typeclass for lifting pure functions to effectful arguments and results

Methods

applyVariadic :: f a -> b Source #

Instances

Instances details
(Applicative f, b ~ f a) => ApplyVariadic f a b Source # 
Instance details

Defined in Data.Registry.Lift

Methods

applyVariadic :: f a -> b Source #

(Monad f, b ~ f a) => ApplyVariadic f (f a) b Source # 
Instance details

Defined in Data.Registry.Lift

Methods

applyVariadic :: f (f a) -> b Source #

(Applicative f, ApplyVariadic f a' b', b ~ (f a -> b')) => ApplyVariadic f (a -> a') b Source # 
Instance details

Defined in Data.Registry.Lift

Methods

applyVariadic :: f (a -> a') -> b Source #

allTo :: forall f a b. ApplyVariadic f a b => a -> b Source #

Lift a pure function to effectful arguments and results

class Monad f => ApplyVariadic1 f a b where Source #

Typeclass for lifting impure functions to effectful arguments and results

Methods

applyVariadic1 :: f a -> b Source #

Instances

Instances details
(Monad f, b ~ f a) => ApplyVariadic1 f (f a) b Source # 
Instance details

Defined in Data.Registry.Lift

Methods

applyVariadic1 :: f (f a) -> b Source #

(Monad f, ApplyVariadic1 f a' b', b ~ (f a -> b')) => ApplyVariadic1 f (a -> a') b Source # 
Instance details

Defined in Data.Registry.Lift

Methods

applyVariadic1 :: f (a -> a') -> b Source #

argsTo :: forall f a b. ApplyVariadic1 f a b => a -> b Source #

Lift an effectful function to effectful arguments and results

class ApplyVariadic2 f g a b where Source #

Typeclass for lifting a function with a result of type m b into a function with a result of type n b

Methods

applyVariadic2 :: (forall x. f x -> g x) -> a -> b Source #

Instances

Instances details
b ~ g a => ApplyVariadic2 f g (f a) b Source # 
Instance details

Defined in Data.Registry.Lift

Methods

applyVariadic2 :: (forall x. f x -> g x) -> f a -> b Source #

(ApplyVariadic2 f g a' b', b ~ (a -> b')) => ApplyVariadic2 f g (a -> a') b Source # 
Instance details

Defined in Data.Registry.Lift

Methods

applyVariadic2 :: (forall x. f x -> g x) -> (a -> a') -> b Source #

outTo :: forall g f a b. ApplyVariadic2 f g a b => (forall x. f x -> g x) -> a -> b Source #

Lift a function returning an effectful result to a function returning another effectful result

Tagging

newtype Tag (s :: Symbol) a Source #

The output of some constructors can be "tagged" with a string to indicate how a given value was built.

Constructors

Tag 

Fields

Instances

Instances details
Functor (Tag s) Source # 
Instance details

Defined in Data.Registry.Lift

Methods

fmap :: (a -> b) -> Tag s a -> Tag s b #

(<$) :: a -> Tag s b -> Tag s a #

Applicative (Tag s) Source # 
Instance details

Defined in Data.Registry.Lift

Methods

pure :: a -> Tag s a #

(<*>) :: Tag s (a -> b) -> Tag s a -> Tag s b #

liftA2 :: (a -> b -> c) -> Tag s a -> Tag s b -> Tag s c #

(*>) :: Tag s a -> Tag s b -> Tag s b #

(<*) :: Tag s a -> Tag s b -> Tag s a #

Eq a => Eq (Tag s a) Source # 
Instance details

Defined in Data.Registry.Lift

Methods

(==) :: Tag s a -> Tag s a -> Bool #

(/=) :: Tag s a -> Tag s a -> Bool #

Show a => Show (Tag s a) Source # 
Instance details

Defined in Data.Registry.Lift

Methods

showsPrec :: Int -> Tag s a -> ShowS #

show :: Tag s a -> String #

showList :: [Tag s a] -> ShowS #

tag :: forall (s :: Symbol) fun. CNumArgs (CountArgs fun) fun => fun -> Apply (Tag s) (CountArgs fun) fun Source #

Tag a given constructor f with a string s. The applyLast function only applies the tag to the output type of the constructor. For example data Salary = Fixed Int | Variable Int Double tag @Variable Variable :: Int -> Double -> Tag Variable Salary

data Nat Source #

ApplyLast typeclass provided by @neongreen It uses an auxiliary typeclass to count the arguments of a function

Constructors

Z 
S Nat 

data NumArgs :: Nat -> Type -> Type where Source #

Constructors

NAZ :: NumArgs Z a 
NAS :: NumArgs n b -> NumArgs (S n) (a -> b) 

type family CountArgs (f :: Type) :: Nat where ... Source #

Equations

CountArgs (a -> b) = S (CountArgs b) 
CountArgs result = Z 

class CNumArgs (numArgs :: Nat) (arrows :: Type) where Source #

Methods

getNA :: NumArgs numArgs arrows Source #

Instances

Instances details
CNumArgs 'Z a Source # 
Instance details

Defined in Data.Registry.Lift

Methods

getNA :: NumArgs 'Z a Source #

CNumArgs n b => CNumArgs ('S n) (a -> b) Source # 
Instance details

Defined in Data.Registry.Lift

Methods

getNA :: NumArgs ('S n) (a -> b) Source #

type family Apply (f :: Type -> Type) (n :: Nat) (arrows :: Type) :: Type where ... Source #

Equations

Apply f (S n) (a -> b) = a -> Apply f n b 
Apply f Z a = f a 

applyLast :: forall f fun. (Applicative f, CNumArgs (CountArgs fun) fun) => fun -> Apply f (CountArgs fun) fun Source #

applyLast' :: forall f n fun. Applicative f => NumArgs n fun -> fun -> Apply f n fun Source #