开发者

How do I define Lisp’s apply in Haskell?

Shouldn’t this definition be allowed in a lazy language like Haskell in which functions are curried?

apply f [] = f
apply f (x:xs) = apply (f x) xs

It’s basically a function that app开发者_如何学Clies the given function to the given list of arguments and is very easily done in Lisp for example. Are there any workarounds?


It is hard to give a static type to the apply function, since its type depends on the type of the (possibly heterogeneous) list argument. There are at least two ways one way to write this function in Haskell that I can think of:

Using reflection

We can defer type checking of the application until runtime:

import Data.Dynamic
import Data.Typeable

apply :: Dynamic -> [Dynamic] -> Dynamic
apply f []      = f
apply f (x:xs)  = apply (f `dynApp` x) xs

Note that now the Haskell program may fail with a type error at runtime.

Via type class recursion

Using the semi-standard Text.Printf trick (invented by augustss, IIRC), a solution can be coded up in this style (exercise). It may not be very useful though, and still requires some trick to hide the types in the list.

Edit: I couldn't come up with a way to write this, without using dynamic types or hlists/existentials. Would love to see an example


I like Sjoerd Visscher's reply, but the extensions -- especially IncoherentInstances, used in this case to make partial application possible -- might be a bit daunting. Here's a solution that doesn't require any extensions.

First, we define a datatype of functions that know what to do with any number of arguments. You should read a here as being the "argument type", and b as being the "return type".

data ListF a b = Cons b (ListF a (a -> b))

Then we can write some (Haskell) functions that munge these (variadic) functions. I use the F suffix for any functions that happen to be in the Prelude.

headF :: ListF a b -> b
headF (Cons b _) = b

mapF :: (b -> c) -> ListF a b -> ListF a c
mapF f (Cons v fs) = Cons (f v) (mapF (f.) fs)

partialApply :: ListF a b -> [a] -> ListF a b
partialApply fs          []     = fs
partialApply (Cons f fs) (x:xs) = partialApply (mapF ($x) fs) xs

apply :: ListF a b -> [a] -> b
apply f xs = headF (partialApply f xs)

For example, the sum function could be thought of as a variadic function:

sumF :: Num a => ListF a a
sumF = Cons 0 (mapF (+) sumF)

sumExample = apply sumF [3, 4, 5]

However, we also want to be able to deal with normal functions, which don't necessarily know what to do with any number of arguments. So, what to do? Well, like Lisp, we can throw an exception at runtime. Below, we'll use f as a simple example of a non-variadic function.

f True True True  = 32
f True True False = 67
f _ _ _ = 9

tooMany = error "too many arguments"
tooFew  = error "too few arguments"
lift0 v = Cons v tooMany
lift1 f = Cons tooFew (lift0 f)
lift2 f = Cons tooFew (lift1 f)
lift3 f = Cons tooFew (lift2 f)

fF1 = lift3 f

fExample1 = apply fF1 [True, True, True]
fExample2 = apply fF1 [True, False]
fExample3 = apply (partialApply fF1 [True, False]) [False]

Of course, if you don't like the boilerplate of defining lift0, lift1, lift2, lift3, etc. separately, then you need to enable some extensions. But you can get quite far without them!

Here is how you can generalize to a single lift function. First, we define some standard type-level numbers:

{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, TypeFamilies, UndecidableInstances #-}

data Z = Z
newtype S n = S n

Then introduce the typeclass for lifting. You should read the type I n a b as "n copies of a as arguments, then a return type of b".

class Lift n a b where
    type I n a b :: *
    lift :: n -> I n a b -> ListF a b

instance Lift Z a b where
    type I Z a b = b
    lift _ b = Cons b tooMany

instance (Lift n a (a -> b), I n a (a -> b) ~ (a -> I n a b)) => Lift (S n) a b where
    type I (S n) a b = a -> I n a b
    lift (S n) f = Cons tooFew (lift n f)

And here's the examples using f from before, rewritten using the generalized lift:

fF2 = lift (S (S (S Z))) f

fExample4 = apply fF2 [True, True, True]
fExample5 = apply fF2 [True, False]
fExample6 = apply (partialApply fF2 [True, False]) [False]


No, it cannot. f and f x are different types. Due to the statically typed nature of haskell, it can't take any function. It has to take a specific type of function.

Suppose f is passed in with type a -> b -> c. Then f x has type b -> c. But a -> b -> c must have the same type as a -> b. Hence a function of type a -> (b -> c) must be a function of type a -> b. So b must be the same as b -> c, which is an infinite type b -> b -> b -> ... -> c. It cannot exist. (continue to substitute b -> c for b)


Here's one way to do it in GHC. You'll need some type annotations here and there to convince GHC that it's all going to work out.

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE IncoherentInstances #-}

class Apply f a r | f -> a r where
  apply :: f -> [a] -> r
instance Apply f a r => Apply (a -> f) a r where
  apply f (a:as) = apply (f a) as
instance Apply r a r where
  apply r _ = r

test = apply ((+) :: Int -> Int -> Int) [1::Int,2]

apply' :: (a -> a -> a) -> [a] -> a
apply' = apply

test' = apply' (+) [1,2]


This code is a good illustration of the differences between static and dynamic type-checking. With static type-checking, the compiler can't be sure that apply f really is being passed arguments that f expects, so it rejects the program. In lisp, the checking is done at runtime and the program might fail then.


I am not sure how much this would be helpful as I am writing this in F# but I think this can be easily done in Haskell too:

type 'a RecFunction  = RecFunction of ('a -> 'a RecFunction)
let rec apply (f: 'a RecFunction) (lst: 'a list) = 
    match (lst,f) with
    | ([],_) -> f
    | ((x::xs), RecFunction z) -> apply (z x) xs

In this case the "f" in question is defined using a discriminated union which allows recursive data type definition. This can be used to solved the mentioned problem I guess.


With the help and input of some others I defined a way to achieve this (well, sort of, with a custom list type) which is a bit different from the previous answers. This is an old question, but it seems to still be visited so I will add the approach for completeness.

We use one extension (GADTs), with a list type a bit similar to Daniel Wagner's, but with a tagging function type rather than a Peano number. Let's go through the code in pieces. First we set the extension and define the list type. The datatype is polymorphic so in this formulation arguments don't have to have the same type.

{-# LANGUAGE GADTs #-}

-- n represents function type, o represents output type
data LApp n o where
  -- no arguments applied (function and output type are the same)
  End :: LApp o o
  -- intentional similarity to ($)
  (:$) :: a -> LApp m o -> LApp (a -> m) o

infixr 5 :$ -- same as :

Let's define a function that can take a list like this and apply it to a function. There is some type trickery here: the function has type n, a call to listApply will only compile if this type matches the n tag on our list type. By leaving our output type o unspecified, we leave some freedom in this (when creating the list we don't have to immediately entirely fix the kind of function it can be applied to).

-- the apply function
listApply :: n -> LApp n o -> o
listApply fun End = fun
listApply fun (p :$ l) = listApply (fun p) l

That's it! We can now apply functions to arguments stored in our list type. Expected more? :)

-- showing off the power of AppL
main = do print . listApply reverse $ "yrruC .B lleksaH" :$ End
          print . listApply (*) $ 1/2 :$ pi :$ End
          print . listApply ($) $ head :$ [1..] :$ End
          print $ listApply True End

Unfortunately we are kind of locked in to our list type, we can't just convert normal lists to use them with listApply. I suspect this is a fundamental issue with the type checker (types end up depending on the value of a list) but to be honest I'm not entirely sure.

-- Can't do this :(
-- listApply (**) $ foldr (:$) End [2, 32]

If you feel uncomfortable about using a heterogeneous list, all you have to do is add an extra parameter to the LApp type, e.g:

-- Alternative definition
-- data FList n o a where
--   Nil :: FList o o a
--   Cons :: a -> FList f o a -> FList (a -> f) o a

Here a represents the argument type, where the function which is applied to will also have to accept arguments of all the same type.


This isn't precisely an answer to your original question, but I think it might be an answer to your use-case.

pure f <*> [arg] <*> [arg2] ...
-- example
λ>pure (\a b c -> (a*b)+c) <*> [2,4] <*> [3] <*> [1]
[7,13]
λ>pure (+) <*> [1] <*> [2]
[3]

The applicative instance of list is a lot broader than this super narrow use-case though...

λ>pure (+1) <*> [1..10]
[2,3,4,5,6,7,8,9,10,11]
-- Or, apply (+1) to items 1 through 10 and collect the results in a list

λ>pure (+) <*> [1..5] <*> [1..5]
[2,3,4,5,6,3,4,5,6,7,4,5,6,7,8,5,6,7,8,9,6,7,8,9,10]

{- The applicative instance of list gives you every possible combination of 
elements from the lists provided, so that is every possible sum of pairs 
between one and five -}

λ>pure (\a b c -> (a*b)+c) <*> [2,4] <*> [4,3] <*> [1]
[9,7,17,13]
{- that's -  2*4+1, 2*3+1, 4*4+1, 4*3+1
Or, I am repeating argC when I call this function twice, but a and b are 
different -}
λ>pure (\a b c -> show (a*b) ++ c) <*> [1,2] <*> [3,4] <*> [" look mah, other types"]
["3 look mah, other types","4 look mah, other types","6 look mah, other types","8 look mah, other types"]

So it's not the same concept, precisely, but it a lot of those compositional use-cases, and adds a few more.

0

上一篇:

下一篇:

精彩评论

暂无评论...
验证码 换一张
取 消

最新问答

问答排行榜