[Haskell-cafe] How to fold on types?

Timon Gehr timon.gehr at gmx.ch
Wed Dec 26 02:04:52 CET 2012


On 12/25/2012 09:59 AM, Magicloud Magiclouds wrote:
> Say I have things like:
>
> data LongDec = LongDef a b c ... x y z
> values = [ 'a', 'b', 'c', ... 'x', 'y', 'z' ]
>
> Now I want them to be "LongDef 'a' 'b' 'c' ... 'x' 'y' 'z'".
> In form, this is something like folding. But since the type changes, so
> code like following won't work:
>
> foldl (\def value -> def value) LongDef values
>
> Is it possible to do this in some way?
> --
> 竹密岂妨流水过
> 山高哪阻野云飞
>
> And for G+, please use magiclouds#gmail.com <http://gmail.com/>.
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

This hack works, in case that helps:

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}

data LongDec = LongDef Char Char Char Char Char Char
   deriving Show

values = [ 'a', 'b', 'c', 'x', 'y', 'z' ]

class Apply a b c where
   apply :: b -> [a] -> c
instance Apply a b b where
   apply = const
instance (Apply a b c) => Apply a (a -> b) c where
   apply f (x:xs) = apply (f x) xs

main = print (apply LongDef values :: LongDec)

It requires an explicit type annotation to fix type parameter 'c'. It 
cannot be a function type. (I am not sure why though.)




More information about the Haskell-Cafe mailing list