[Haskell-cafe] Thinking about an unlistN
Robert Greayer
robgreayer at yahoo.com
Sun Aug 10 22:34:34 EDT 2008
--- On Sun, 8/10/08, Michael Feathers <mfeathers at mindspring.com> 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.
>
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
More information about the Haskell-Cafe
mailing list