问题
Note: This is a repost of another question, which the author deleted. Here's the original question:
I have this polyvariadic comp
function in Javascript and was wondering if a similar implementation in Haskell were possible. I am mostly interested in comp
's type:
const comp = f => Object.assign(
g => comp([g].concat(f)),
{run: x => f.reduce((acc, h) => h(acc), x)}
);
const inc = n => n + 1;
const sqr = n => n * n;
const repeatStr = s => n => Array(n + 1).join(s);
comp(repeatStr("*")) (inc) (sqr).run(2); // "*****"
comp(repeatStr("*"))
(inc)
(inc)
(inc)
(inc)
(inc).run(0); // "*****"
comp
builds up a heterogeneous array that usually doesn't have a type in Haskell. I guess such a variadic function must be polymorphic in its return type. However, this task exceeds my Haskell knowledge by far. Any clue would be helpful.
Context
I use a Javascript runtime type checker so that I can build up the array inside comp
in a type-safe manner. It requires explicit type annotations and supports only parametric and rank-2 polymorphism.
回答1:
You're right. You can't build a heterogeneous list of composable functions in Haskell(1). However, you can create your own list data type for composable functions as follows:
{-# LANGUAGE GADTs #-}
data Comp a b where
Id :: Comp a a
Comp :: Comp b c -> (a -> b) -> Comp a c
run :: Comp a b -> a -> b
run Id = id
run (Comp g f) = run g . f
The Id
constructor is similar to []
and the Comp
constructor is similar to :
but with the arguments flipped.
Next, we use the varargs pattern to create a polyvariadic function. To do so, we define a type class:
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
class Chain a b c | c -> a where
chain :: Comp a b -> c
Note that our state is Comp b c
and our result is either Comp b c
or a function that takes another function (a -> b)
as an input and composes it with our state to produce a new Chain
called r
with state Comp a c
. Let's define instances for these now:
{-# LANGUAGE FlexibleInstances #-}
instance c ~ c' => Chain b c (Comp b c') where
chain = id
instance Chain a c r => Chain b c ((a -> b) -> r) where
chain g f = chain (Comp g f)
comp :: Chain b b c => c
comp = chain Id
The comp
function can now be defined as chain Id
(i.e. the chain with the empty list Id
as its state). We can finally use this comp
function as we'd do in JavaScript:
inc :: Int -> Int
inc = (+1)
sqr :: Int -> Int
sqr x = x * x
repeatStr :: String -> Int -> String
repeatStr s x = concat (replicate x s)
example1 :: String
example1 = comp (repeatStr "*") inc sqr `run` 2
example2 :: String
example2 = comp (repeatStr "*") inc inc inc inc inc `run` 0
Putting it all together:
{-# LANGUAGE GADTs, MultiParamTypeClasses, FunctionalDependencies,
FlexibleInstances #-}
data Comp a b where
Id :: Comp a a
Comp :: Comp b c -> (a -> b) -> Comp a c
run :: Comp a b -> a -> b
run Id = id
run (Comp g f) = run g . f
class Chain a b c | c -> a where
chain :: Comp a b -> c
instance c ~ c' => Chain b c (Comp b c') where
chain = id
instance Chain a c r => Chain b c ((a -> b) -> r) where
chain g f = chain (Comp g f)
comp :: Chain b b c => c
comp = chain Id
inc :: Int -> Int
inc = (+1)
sqr :: Int -> Int
sqr x = x * x
repeatStr :: String -> Int -> String
repeatStr s x = concat (replicate x s)
example1 :: String
example1 = comp (repeatStr "*") inc sqr `run` 2
example2 :: String
example2 = comp (repeatStr "*") inc inc inc inc inc `run` 0
As you can see, the type of comp
is Chain b b c => c
. To define the Chain
type class we require MultiParamTypeClasses
and FunctionalDependencies
. To use it we require FlexibleInstances
. Hence, you'll need a sophisticated JavaScript runtime type checker in order to correctly type check comp
.
Edit: As naomik and Daniel Wagner pointed out in the comments, you can use an actual function instead of a list of composable functions as your internal representation for the state of comp
. For example, in JavaScript:
const comp = run => Object.assign(g => comp(x => g(run(x))), {run});
Similarly, in Haskell:
{-# LANGUAGE GADTs, MultiParamTypeClasses, FunctionalDependencies,
FlexibleInstances #-}
newtype Comp a b = Comp { run :: a -> b }
class Chain a b c | c -> a where
chain :: Comp a b -> c
instance c ~ c' => Chain b c (Comp b c') where
chain = id
instance Chain a c r => Chain b c ((a -> b) -> r) where
chain g f = chain (Comp (run g . f))
comp :: Chain b b c => c
comp = chain (Comp id)
Note that even though we don't use GADTs anymore we still require the GADTs
language extension in order to use the equality constraint c ~ c'
in the first instance of Chain
. Also, as you can see run g . f
has been moved from the definition of run
into the second instance of Chain
. Similarly, id
has been moved from the definition of run
into the definition of comp
.
(1) You can use existential types to create a list of heterogeneous functions in Haskell but they won't have the additional constraint of being composable.
来源:https://stackoverflow.com/questions/48544123/how-to-write-this-polyvariadic-composition-function-in-haskell