[Haskell-cafe] How to fold on types?

adam vogt vogt.adam at gmail.com
Tue Dec 25 19:17:48 CET 2012


> {-# LANGUAGE DeriveDataTypeable, ScopedTypeVariables #-}

Hi MagicCloud,

A worse, but perhaps simpler alternative to Oleg's solution uses Data.Dynamic:

> import Data.Dynamic

> data LongDec a = LongDec a a a a a a a a
>   deriving (Show, Typeable)
>
> values = "abcdefgh"

> mkLongDec :: forall a. Typeable a => [a] -> Maybe (LongDec a)
> mkLongDec = (fromDynamic =<<) .
>       foldl
>           (\f x -> do
>                        f' <- f
>                        dynApply f' (toDyn x))
>           (Just (toDyn (\x -> LongDec (x :: a))))

> main = do
>   print (mkLongDec values)
>   print (mkLongDec [1 .. 8 :: Integer])

*Main> main
Just (LongDec 'a' 'b' 'c' 'd' 'e' 'f' 'g' 'h')
Just (LongDec 1 2 3 4 5 6 7 8)

There is no check that all arguments of LongDec are the same
type (in this case a specific instance of Typeable): you'd only
be able to get Nothing out of mkLongDec was defined as:

data LongDec a = LongDec a Int a a a Char


Regards,
Adam Vogt



More information about the Haskell-Cafe mailing list