Thinking about an unlistN

I wrote this function the other day, and I was wondering if I'm missing something.. whether there is already a function or idiom around to do this. unlist3 :: (a -> a -> a -> b) -> [a] -> b unlist3 f (x:y:z:xs) = f x y z I was also wondering whether the function can be generalized to N or whether this is just one of those edges in the type system that you can't abstract over. Thanks, Michael

I'm no expert, but it looks like the generalization of that would be
some f that took a list:
f :: [a] -> b
so what you'd have is a fold, right?
foldr1 :: (a -> a -> a) -> [a] -> a
Best,
Philip Neustrom
On Sun, Aug 10, 2008 at 11:47 AM, Michael Feathers
I wrote this function the other day, and I was wondering if I'm missing something.. whether there is already a function or idiom around to do this.
unlist3 :: (a -> a -> a -> b) -> [a] -> b unlist3 f (x:y:z:xs) = f x y z
I was also wondering whether the function can be generalized to N or whether this is just one of those edges in the type system that you can't abstract over.
Thanks,
Michael
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Philip, Thanks. It's not quite that, though. It's more like an adapter for a function with a specific arity. If I have, say, a function f :: a -> a -> a -> a -> b it would be nice to be able to just: unlistN 4 f [1..4] Michael (does look like there's no way to make that fly with the type system however) Philip Neustrom wrote:
I'm no expert, but it looks like the generalization of that would be some f that took a list:
f :: [a] -> b
so what you'd have is a fold, right?
foldr1 :: (a -> a -> a) -> [a] -> a
Best, Philip Neustrom
On Sun, Aug 10, 2008 at 11:47 AM, Michael Feathers
wrote: I wrote this function the other day, and I was wondering if I'm missing something.. whether there is already a function or idiom around to do this.
unlist3 :: (a -> a -> a -> b) -> [a] -> b unlist3 f (x:y:z:xs) = f x y z
I was also wondering whether the function can be generalized to N or whether this is just one of those edges in the type system that you can't abstract over.
Thanks,
Michael
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Now Playing: Clammbon - 246 http://youtube.com/watch?v=PO77bN8W1mA

Hi,
On Sun, Aug 10, 2008 at 8:57 PM, Michael Feathers
If I have, say, a function f :: a -> a -> a -> a -> b it would be nice to be able to just:
unlistN 4 f [1..4]
It indeed doesn't work like this; there's more than one way to do something *like* this, if you really want to. The closest one is probably to use type-level numbers: {-# OPTIONS_GHC -fglasgow-exts #-} data Zero data Suc a zero :: Zero; zero = undefined; suc :: a -> Suc a; suc = undefined one = suc zero; two = suc one; three = suc two; four = suc three class Unlist n a b where type UnlistFn n a b unlist :: n -> UnlistFn n a b -> [a] -> b instance Unlist Zero a b where type UnlistFn Zero a b = b unlist _ r _ = r instance Unlist n a b => Unlist (Suc n) a b where type UnlistFn (Suc n) a b = a -> UnlistFn n a b unlist _ f (x:xs) = unlist (undefined :: n) (f x) xs main = print (unlist four (,,,) "abcd") This prints ('a','b','c','d'). Hope this is fun[*], - Benja [*] I hesistate to say "hope this helps" in this case :-)

Michael Feathers wrote:
I wrote this function the other day, and I was wondering if I'm missing something.. whether there is already a function or idiom around to do this.
unlist3 :: (a -> a -> a -> b) -> [a] -> b unlist3 f (x:y:z:xs) = f x y z
I was also wondering whether the function can be generalized to N or whether this is just one of those edges in the type system that you can't abstract over.
In Scheme and Lisp, the "apply" function does this, so the following Scheme definition would do the trick: (define unlist apply) (Although this doesn't ignore the xs as in the example; that would require some code to extract a sublist of the desired length.) In Haskell, bring on the type system shenanigans! ;) Anton

--- On Sun, 8/10/08, Michael Feathers
I wrote this function the other day, and I was wondering if I'm missing something.. whether there is already a function or idiom around to do this.
unlist3 :: (a -> a -> a -> b) -> [a] -> b unlist3 f (x:y:z:xs) = f x y z
I was also wondering whether the function can be generalized to N or whether this is just one of those edges in the type system that you can't abstract over.
Well, there's always haskell's Swiss Army Knife, TH:
module Unlist(unlistN) where
import Language.Haskell.TH
unlistN n = do f <- newName "f" xs <- sequence (replicate n (newName "x")) lamE [varP f,(foldr ((flip infixP) '(:)) (wildP) (map varP xs))] (foldl appE (varE f) (map varE xs))
{-# OPTIONS_GHC -XTemplateHaskell #-} module UseUnlist where
import Unlist
f i0 i1 i2 i3 = i0 + i1 + i2 + i3
x = $(unlistN 4) f [1,2,3,4,5,6,7]
rcg

On Sun, Aug 10, 2008 at 11:47 AM, Michael Feathers
unlist3 :: (a -> a -> a -> b) -> [a] -> b unlist3 f (x:y:z:xs) = f x y z
Oleg has written about this. Be careful, its easy to overdose on: "Functions with the variable number of (variously typed) arguments" http://okmij.org/ftp/Haskell/types.html#polyvar-fn
I was also wondering whether the function can be generalized to N or whether this is just one of those edges in the type system that you can't abstract over.
With template haskell I don't think that exists. Justin
participants (6)
-
Anton van Straaten
-
Benja Fallenstein
-
Justin Bailey
-
Michael Feathers
-
Philip Neustrom
-
Robert Greayer