Safe Haskell | None |
---|---|
Language | Haskell2010 |
Convert between functions taking HLists and functions taking many arguments
Synopsis
- class HLengthEq xs n => HCurry' (n :: HNat) f xs r | f xs -> r, r xs -> f, n f -> xs, xs -> n where
- hUncurry :: forall (n :: HNat) f (xs :: [Type]) r. (HCurry' n f xs r, ArityFwd f n, ArityRev f n) => f -> HList xs -> r
- hCurry :: forall (n :: HNat) f (xs :: [Type]) r. (HCurry' n f xs r, ArityFwd f n, ArityRev f n) => (HList xs -> r) -> f
- hCompose :: forall (xs1 :: [Type]) (xs2 :: [Type]) (xsys :: [Type]) (n1 :: HNat) f1 r (n2 :: HNat) b (n3 :: HNat) f2 x. (HAppendList1 xs1 xs2 xsys, HCurry' n1 f1 xsys r, HCurry' n2 b xs2 r, HCurry' n3 f2 xs1 x, ArityFwd b n2, ArityFwd f2 n3, ArityRev b n2, ArityRev f2 n3, HSplitAt1 ('[] :: [Type]) n3 xsys xs1 xs2) => (x -> b) -> f2 -> f1
- arityOf :: Arity f n => f -> Proxy n
Documentation
class HLengthEq xs n => HCurry' (n :: HNat) f xs r | f xs -> r, r xs -> f, n f -> xs, xs -> n where Source #
curry
/uncurry
for many arguments and HLists instead of tuples
XXX the last FD xs -> n
is needed to make hCompose infer the right types:
arguably it shouldn't be needed
hUncurry :: forall (n :: HNat) f (xs :: [Type]) r. (HCurry' n f xs r, ArityFwd f n, ArityRev f n) => f -> HList xs -> r Source #
hCurry :: forall (n :: HNat) f (xs :: [Type]) r. (HCurry' n f xs r, ArityFwd f n, ArityRev f n) => (HList xs -> r) -> f Source #
Note: with ghc-7.10 the Arity constraint added here does not work
properly with hCompose, so it is possible that other uses of hCurry
are better served by hCurry' Proxy
.
hCompose :: forall (xs1 :: [Type]) (xs2 :: [Type]) (xsys :: [Type]) (n1 :: HNat) f1 r (n2 :: HNat) b (n3 :: HNat) f2 x. (HAppendList1 xs1 xs2 xsys, HCurry' n1 f1 xsys r, HCurry' n2 b xs2 r, HCurry' n3 f2 xs1 x, ArityFwd b n2, ArityFwd f2 n3, ArityRev b n2, ArityRev f2 n3, HSplitAt1 ('[] :: [Type]) n3 xsys xs1 xs2) => (x -> b) -> f2 -> f1 Source #
compose two functions that take multiple arguments. The result of the second function is the first argument to the first function. An example is probably clearer:
>>>
let f = hCompose (,,) (,)
>>>
:t f
f :: ... -> ... -> ... -> ... -> ((..., ...), ..., ...)
>>>
f 1 2 3 4
((1,2),3,4)
Note: polymorphism can make it confusing as to how many parameters a function
actually takes. For example, the first two ids are id :: (a -> b) -> (a -> b)
in
>>>
(.) id id id 'y'
'y'
>>>
hCompose id id id 'y'
'y'
still typechecks, but in that case hCompose i1 i2 i3 x == i1 ((i2 i3) x)
has id with different types than @(.) i1 i2 i3 x == (i1 (i2 i3)) x
Prompted by http://stackoverflow.com/questions/28932054/can-hlistelim-be-composed-with-another-function