apply-unordered-mono-1.0: Apply functions to arguments in an unordered type-directed fashion
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Apply.Unordered.Mono

Description

This modules is an experiment in type family / typeclass machinery to provide type-directed function application and argument reordering. It is severely restricted, in that it only supports monomorphic arguments and parameters.

Few commonly known functions in base are monomorphic with multiple arguments, so I will use an example from Data.Text :

{-# LANGUAGE OverloadedStrings #-}
import qualified Data.Text as T

ex1 :: Int -> T.Text
ex1 = T.replicate ? ("wow! " :: Text)

Cool! The (?) operator has magically provided the 2nd argument of T.replicate (its type is Int -> Text -> Text).

This module also provides reorderArgs, which does this variety of function application in a variadic fashion.

ex2 :: T.Text -> Int -> T.Text
ex2 = reorderArgs T.replicate
Synopsis

Type-directed function application which uses first match

applyByType :: forall a f matches. (matches ~ HasAMatch a f f, ApplyByType matches a f) => f -> a -> ApplyByTypeResult matches a f Source #

Applies a function to an argument, by providing the argument to the first parameter which matches the argument type. This does not handle any polymorphism in the function type or any argument types.

reorderArgs :: forall f g. ReorderArgs (HasArg f) f g => f -> g Source #

(?) :: forall a f matches. (matches ~ HasAMatch a f f, ApplyByType matches a f) => f -> a -> ApplyByTypeResult matches a f infixl 1 Source #

Operator alias for applyByType

Type-directed function application which requires unique match

applyByUniqueType :: forall a f matches. (matches ~ HasUniqueMatch a f f, ApplyByType matches a f) => f -> a -> ApplyByTypeResult matches a f Source #

Similarly to applyByType, applies a function to an argument by matching the argument type with the parameter type. If the match is ambiguous, this is a type error.

reorderUniqueArgs :: forall f g. ReorderUniqueArgs (HasArg f) f g => f -> g Source #

(?!) :: forall a f matches. (matches ~ HasUniqueMatch a f f, ApplyByType matches a f) => f -> a -> ApplyByTypeResult matches a f infixl 1 Source #

Operator alias for applyByUniqueType

Machinery for type directed function application

data MatchArgResult Source #

A data-kind for MatchArgResult to return.

Constructors

Matches

Indicates the first argument matches.

Doesn'tMatch

Indicates the first argument doesn't match.

NoArgToMatch

Indicates the function has no first argument.

type family MatchFirstArg a f :: MatchArgResult where ... Source #

A type family which checks if the specified argument type matches the first parameter of a function.

Equations

MatchFirstArg a (a -> _) = 'Matches 
MatchFirstArg a (b -> _) = 'Doesn'tMatch 
MatchFirstArg _ _ = 'NoArgToMatch 

type family HasAMatch a f f0 :: MatchArgResult where ... Source #

A type family which returns a TypeError, specifically NoMatchErrorMsg, if the specified argument type matches none of the function parameter types. Otherwise, it behaves the same as MatchFirstArg.

Equations

HasAMatch a (a -> _) f0 = MatchFirstArg a f0 
HasAMatch a (b -> r) f0 = HasAMatch a r f0 
HasAMatch a _ f0 = TypeError (NoMatchErrorMsg a f0) 

class ApplyByType (matches :: MatchArgResult) a f Source #

Typeclass used to implement applyByType. The first type argument is used to select instances, and should always be MatchFirstArg a f.

Minimal complete definition

applyByTypeImpl

Associated Types

type ApplyByTypeResult matches a f Source #

Instances

Instances details
(TypeError (NoMatchForResultErrorMsg a r) :: Constraint) => ApplyByType 'NoArgToMatch a r Source # 
Instance details

Defined in Control.Apply.Unordered.Mono

Associated Types

type ApplyByTypeResult 'NoArgToMatch a r Source #

ApplyByType 'Matches a (a -> r) Source # 
Instance details

Defined in Control.Apply.Unordered.Mono

Associated Types

type ApplyByTypeResult 'Matches a (a -> r) Source #

Methods

applyByTypeImpl :: Proxy 'Matches -> (a -> r) -> a -> ApplyByTypeResult 'Matches a (a -> r)

ApplyByType (MatchFirstArg a r) a r => ApplyByType 'Doesn'tMatch a (b -> r) Source # 
Instance details

Defined in Control.Apply.Unordered.Mono

Associated Types

type ApplyByTypeResult 'Doesn'tMatch a (b -> r) Source #

Methods

applyByTypeImpl :: Proxy 'Doesn'tMatch -> (b -> r) -> a -> ApplyByTypeResult 'Doesn'tMatch a (b -> r)

Machinery for unique match function application

type family HasUniqueMatch a f f0 :: MatchArgResult where ... Source #

A type family similar to HasAMatch, but also checks that there's a unique match for the argument type.

Equations

HasUniqueMatch a (a -> r) f0 = CheckAmbiguousMatch a r f0 
HasUniqueMatch a (b -> r) f0 = HasUniqueMatch a r f0 
HasUniqueMatch a _ f0 = TypeError (NoMatchErrorMsg a f0) 

type family CheckAmbiguousMatch a f f0 :: MatchArgResult where ... Source #

Used to implement HasUniqueMatch, this type family is used after the match is found. Any additional matches cause an AmbiguousMatchErrorMsg.

Equations

CheckAmbiguousMatch a (a -> _) f0 = TypeError (AmbiguousMatchErrorMsg a f0) 
CheckAmbiguousMatch a (b -> r) f0 = CheckAmbiguousMatch a r f0 
CheckAmbiguousMatch a _ f0 = MatchFirstArg a f0 

Machinery for reordering parameters

data HasArgResult Source #

A data-kind for HasArg to return.

Constructors

ArgPresent

Indicates that the type is a function type.

NoArg

Indicates that the type is not a function type.

type family HasArg f :: HasArgResult where ... Source #

Checks whether the specified type is a function type ( -> ).

Equations

HasArg (_ -> _) = 'ArgPresent 
HasArg _ = 'NoArg 

class ReorderArgs (fHasArg :: HasArgResult) f g Source #

Typeclass used to implement reorderArgs. The first type argument is used to select instances, and should always be HasArg f.

Minimal complete definition

reorderArgsImpl

Instances

Instances details
r1 ~ r2 => ReorderArgs 'NoArg r1 r2 Source # 
Instance details

Defined in Control.Apply.Unordered.Mono

Methods

reorderArgsImpl :: Proxy 'NoArg -> r1 -> r2

(matches ~ HasAMatch a (b -> y) (b -> y), result ~ ApplyByTypeResult matches a (b -> y), ApplyByType matches a (b -> y), ReorderArgs (HasArg result) result x) => ReorderArgs 'ArgPresent (b -> y) (a -> x) Source # 
Instance details

Defined in Control.Apply.Unordered.Mono

Methods

reorderArgsImpl :: Proxy 'ArgPresent -> (b -> y) -> a -> x

class ReorderUniqueArgs (fHasArg :: HasArgResult) f g Source #

Typeclass used to implement reorderUniqueArgs. The first type argument is used to select instances, and should always be HasArg f.

Minimal complete definition

reorderUniqueArgsImpl

Instances

Instances details
r1 ~ r2 => ReorderUniqueArgs 'NoArg r1 r2 Source # 
Instance details

Defined in Control.Apply.Unordered.Mono

Methods

reorderUniqueArgsImpl :: Proxy 'NoArg -> r1 -> r2

(matches ~ HasUniqueMatch a (b -> y) (b -> y), result ~ ApplyByTypeResult matches a (b -> y), ApplyByType matches a (b -> y), ReorderUniqueArgs (HasArg result) result x) => ReorderUniqueArgs 'ArgPresent (b -> y) (a -> x) Source # 
Instance details

Defined in Control.Apply.Unordered.Mono

Methods

reorderUniqueArgsImpl :: Proxy 'ArgPresent -> (b -> y) -> a -> x