[Haskell-cafe] How to fold on types?

Magicloud Magiclouds magicloud.magiclouds at gmail.com
Wed Dec 26 02:42:46 CET 2012


You guys are great! Thanks.


On Wed, Dec 26, 2012 at 9:04 AM, Timon Gehr <timon.gehr at gmx.ch> wrote:

> 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<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.)
>
>
> ______________________________**_________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/**mailman/listinfo/haskell-cafe<http://www.haskell.org/mailman/listinfo/haskell-cafe>
>



-- 
竹密岂妨流水过
山高哪阻野云飞

And for G+, please use magiclouds#gmail.com.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20121226/a72820de/attachment.htm>


More information about the Haskell-Cafe mailing list