Re: [Haskell-cafe] How to fold on types?

2012-12-25 Thread Magicloud Magiclouds
You guys are great! Thanks.


On Wed, Dec 26, 2012 at 9:04 AM, Timon Gehr  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 .
>>
>>
>> __**_
>> Haskell-Cafe mailing list
>> Haskell-Cafe@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.)
>
>
> __**_
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/**mailman/listinfo/haskell-cafe
>



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

And for G+, please use magiclouds#gmail.com.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to fold on types?

2012-12-25 Thread Timon Gehr

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 .


___
Haskell-Cafe mailing list
Haskell-Cafe@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.)



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to fold on types?

2012-12-25 Thread adam vogt
> {-# 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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to fold on types?

2012-12-25 Thread oleg

Magiclouds asked how to build values of data types with many
components from a list of components. For example, suppose we have

data D3 = D3 Int Int Int deriving Show
v3 = [1::Int,2,3]

How can we build the value D3 1 2 3 using the list v3 as the source
for D3's fields? We can't use (foldl ($) D3 values) since the type
changes throughout the iteration: D3 and D3 1 have different type.

The enclosed code shows the solution. It defines the function fcurry
such that

t1 = fcurry D3 v3
-- D3 1 2 3
gives the expected result (D3 1 2 3).

The code is the instance of the general folding over heterogeneous
lists, search for HFoldr in 
http://code.haskell.org/HList/Data/HList/HList.hs

{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts  #-}
{-# LANGUAGE TypeFamilies, DataKinds, PolyKinds, ScopedTypeVariables  #-}
{-# LANGUAGE UndecidableInstances  #-}

-- `Folding' over the data type: creating values of data types
-- with many components from a list of components
-- UndecidableInstances is a bit surprising since everything is decidable,
-- but GHC can't see it.
-- Extensions DataKinds, PolyKinds aren't strictly needed, but
-- they make the code a bit nicer. If we already have them, 
-- why suffer avoiding them. 

module P where

-- The example from MagicCloud's message

data D3 = D3 Int Int Int deriving Show
v3 = [1::Int,2,3]

type family IsArrow a :: Bool
type instance IsArrow (a->b) = True
type instance IsArrow D3 = False
-- add more instances as needed for other non-arrow types

data Proxy a = Proxy

class FarCurry a r t where
fcurry :: (a->t) -> [a] -> r

instance ((IsArrow t) ~ f, FarCurry' f a r t) => FarCurry a r t where
fcurry = fcurry' (Proxy::Proxy f)

class FarCurry' f a r t where
fcurry' :: Proxy f -> (a->t) -> [a] -> r

instance r ~ r' => FarCurry' False a r' r where
fcurry' _ cons (x:_) = cons x

instance FarCurry a r t => FarCurry' True a r (a->t) where
fcurry' _ cons (x:t) = fcurry (cons x) t

-- Example
t1 = fcurry D3 v3
-- D3 1 2 3

-- Let's add another data type
data D4 = D4 Int Int Int Int deriving Show
type instance IsArrow D4 = False

t2 = fcurry D4 [1::Int,2,3,4]
-- D4 1 2 3 4



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to fold on types?

2012-12-25 Thread Тимур Амиров
Thinking from subway (: foldl ($) LongDef values ?

вторник, 25 декабря 2012 г. пользователь Тимур Амиров писал:

> Try folding over data type constructor with $?
>
> вторник, 25 декабря 2012 г. пользователь Magicloud Magiclouds писал:
>
>> Forgot to mention, solution without TemplateHaskell.
>>
>>
>> On Tue, Dec 25, 2012 at 4:59 PM, Magicloud Magiclouds <
>> magicloud.magiclo...@gmail.com> 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.
>>>
>>
>>
>>
>> --
>> 竹密岂妨流水过
>> 山高哪阻野云飞
>>
>> And for G+, please use magiclouds#gmail.com.
>>
>
>
> --
> Best
> Timur DeTeam Amirov
> Moscow, Russia
>
>

-- 
Best
Timur DeTeam Amirov
Moscow, Russia
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to fold on types?

2012-12-25 Thread Тимур Амиров
Try folding over data type constructor with $?

вторник, 25 декабря 2012 г. пользователь Magicloud Magiclouds писал:

> Forgot to mention, solution without TemplateHaskell.
>
>
> On Tue, Dec 25, 2012 at 4:59 PM, Magicloud Magiclouds <
> magicloud.magiclo...@gmail.com  'magicloud.magiclo...@gmail.com');>> 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.
>>
>
>
>
> --
> 竹密岂妨流水过
> 山高哪阻野云飞
>
> And for G+, please use magiclouds#gmail.com.
>


-- 
Best
Timur DeTeam Amirov
Moscow, Russia
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe