Re: [Haskell-cafe] Foreign.Erlang help

2012-12-25 Thread Alexander Alexeev
First of all, you can write usual TCP server in Haskell and use it from 
Erlang. It would be handy to use some widely used protocol, like 
Memcached or Redis.


If in some reason you want to use Foreign.Erlang, make sure that you are 
using the same cookie and the same node name type (short or full) in 
Erlang node and Haskell application.


On 12/24/2012 08:46 PM, Junior White wrote:

Hi all,
  I have a game server programming in erlang, but now i want to write 
some game logic in haskell, how to write a haskell node for erlang?


  ps:I have read the introduce of Foreign.Erlang,I use haskell send a 
message to a erlang echo server, but the server not receive anything.



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



--
Best regards,
Alexander Alexeev
http://eax.me/

___
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 javascript:_e({}, 'cvml',
 '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


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 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] multi-thread and lazy evaluation

2012-12-25 Thread timothyhobbs
This seems like a bug in GHC. But it has nothing to do with MVars.  I've 
narrowed this down and filed a bug report here:

http://hackage.haskell.org/trac/ghc/ticket/7528

Timothy


-- Původní zpráva --
Od: Yuras Shumovich shumovi...@gmail.com
Datum: 24. 12. 2012
Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation

On Mon, 2012-12-24 at 16:16 +0100, timothyho...@seznam.cz wrote:
 The real question is, does this mean that GHC is stopping the world every 
 time it puts an MVar?

No, GHC rts only locks the MVar itself.
See here:
http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358
(http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358)

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


Re: [Haskell-cafe] ghc-heap-view now with recursive pretty-printing

2012-12-25 Thread Thomas Schilling
On 21 December 2012 11:16, Joachim Breitner m...@joachim-breitner.de wrote:
 Prelude :script /home/jojo/.cabal/share/ghc-heap-view-0.4.0.0/ghci
 Prelude let x = [1..10]
 Prelude x
 [1,2,3,4,5,6,7,8,9,10]
 Prelude :printHeap x
 _bh [S# 1,S# 2,S# 3,S# 4,S# 5,S# 6,S# 7,S# 8,S# 9,S# 10]

 Note that the tools shows us that the list is a list of S# constructors,
 and also that it is still hidden behind a blackhole. After running
 System.Mem.performGC, this would disappear.

Why do you call it a blackhole?  I assume you mean a thunk that has
been evaluated and updated with its value.  The commonly used term for
this is indirection.  A blackhole is used to detect when a thunk's
value depends on itself (e.g., in let x = id x in ... the thunk for
x may get turned into a black hole).

It's a minor thing, but I think it's a good idea to stick to existing
terminology. Otherwise, it looks like a useful tool. Eventually, we
probably want an interactive graph where we can click a node to
evaluate it (or to show/hide children nodes).

--
Push the envelope. Watch it bend.

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


Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-25 Thread Corentin Dupont
Hi Brandon,
indeed in my example if you add:
*b - evaluate a*
after the definition of a it works.
However, in my original program it doesn't work, I suppose because I
interpret the user submitted code (here *let (a::String) = a *
 for the example) via Hint and Hint-server, and the interpretation must be
done in another thread...

Best,
Corentin

On Mon, Dec 24, 2012 at 3:46 PM, Brandon Allbery allber...@gmail.comwrote:

 On Mon, Dec 24, 2012 at 8:45 AM, Corentin Dupont 
 corentin.dup...@gmail.com wrote:

 *execBlocking :: MVar (Maybe MyData) - IO ()
 execBlocking mv = do
let (a::String) = a
--If you uncomment the next line, it will work
--putStrLn $ show a
putMVar mv (Just $ MyData a toto)*


 It's laziness, yes; you need to do something along the lines of

  let a = length a `seq` a

 or possibly Control.Exception.evaluate needs to be involved somewhere.

 --
 brandon s allbery kf8nh   sine nomine
 associates
 allber...@gmail.com
 ballb...@sinenomine.net
 unix, openafs, kerberos, infrastructure, xmonad
 http://sinenomine.net

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


Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-25 Thread Corentin Dupont
Great, with me compiled with ghc -threaded the bug shows up.
However, runnning main in ghci doesn't show the bug (it finishes
correctly).
I have GHC 7.4.1.

Corentin

On Tue, Dec 25, 2012 at 3:34 PM, timothyho...@seznam.cz wrote:

 This seems like a bug in GHC. But it has nothing to do with MVars.  I've
 narrowed this down and filed a bug report here:

 http://hackage.haskell.org/trac/ghc/ticket/7528

 Timothy

 -- Původní zpráva --
 Od: Yuras Shumovich shumovi...@gmail.com

 Datum: 24. 12. 2012
 Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation


 On Mon, 2012-12-24 at 16:16 +0100, timothyho...@seznam.cz wrote:
  The real question is, does this mean that GHC is stopping the world
 every
  time it puts an MVar?

 No, GHC rts only locks the MVar itself.
 See here:
 http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358

 Yuras


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


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


Re: [Haskell-cafe] ghc-heap-view now with recursive pretty-printing

2012-12-25 Thread Joachim Breitner
Hi,

Am Dienstag, den 25.12.2012, 16:58 +0100 schrieb Thomas Schilling:
 On 21 December 2012 11:16, Joachim Breitner m...@joachim-breitner.de wrote:
  Prelude :script /home/jojo/.cabal/share/ghc-heap-view-0.4.0.0/ghci
  Prelude let x = [1..10]
  Prelude x
  [1,2,3,4,5,6,7,8,9,10]
  Prelude :printHeap x
  _bh [S# 1,S# 2,S# 3,S# 4,S# 5,S# 6,S# 7,S# 8,S# 9,S# 10]
 
  Note that the tools shows us that the list is a list of S# constructors,
  and also that it is still hidden behind a blackhole. After running
  System.Mem.performGC, this would disappear.
 
 Why do you call it a blackhole?  I assume you mean a thunk that has
 been evaluated and updated with its value.  The commonly used term for
 this is indirection.  A blackhole is used to detect when a thunk's
 value depends on itself (e.g., in let x = id x in ... the thunk for
 x may get turned into a black hole).

I don’t call it a blackhole, GHC does :-). At least it is a closure of
type BLACKHOLE
http://hackage.haskell.org/trac/ghc/browser/includes/rts/storage/ClosureTypes.h#L61

I assume this is due to lazy blackholing or something, although it still
occurs with ghci -fno-eager-blackholing... strange.


 It's a minor thing, but I think it's a good idea to stick to existing
 terminology. Otherwise, it looks like a useful tool.

Thanks!

 Eventually, we
 probably want an interactive graph where we can click a node to
 evaluate it (or to show/hide children nodes).

Looks like I am not as good at advertising my (or my student’s) projects
as much as I thought I am:
http://felsin9.de/nnis/ghc-vis/

Greetings,
Joachim





-- 
Joachim nomeata Breitner
  m...@joachim-breitner.de  |  nome...@debian.org  |  GPG: 0x4743206C
  xmpp: nome...@joachim-breitner.de | http://www.joachim-breitner.de/



signature.asc
Description: This is a digitally signed message part
___
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] multi-thread and lazy evaluation

2012-12-25 Thread timothyhobbs
I'm not sure that there is anything great about this bug.  It seems to me 
to be a rather severe demonstration of a somewhat already known design flaw 
in the runtime :(

Could you please comment on the actual bug rather than replying here so that
the devs see that this behaviour has been confirmed?

Tim


-- Původní zpráva --
Od: Corentin Dupont corentin.dup...@gmail.com
Datum: 25. 12. 2012
Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation



Great, with me compiled with ghc -threaded the bug shows up.

However, runnning main in ghci doesn't show the bug (it finishes 
correctly).

I have GHC 7.4.1.

 

Corentin
 


On Tue, Dec 25, 2012 at 3:34 PM, timothyho...@seznam.cz
(mailto:timothyho...@seznam.cz) wrote:
 
This seems like a bug in GHC. But it has nothing to do with MVars.  I've 
narrowed this down and filed a bug report here:

http://hackage.haskell.org/trac/ghc/ticket/7528
(http://hackage.haskell.org/trac/ghc/ticket/7528)

Timothy


-- Původní zpráva --
Od: Yuras Shumovich shumovi...@gmail.com(mailto:shumovi...@gmail.com)


Datum: 24. 12. 2012
Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation




On Mon, 2012-12-24 at 16:16 +0100, timothyho...@seznam.cz
(mailto:timothyho...@seznam.cz) wrote:
 The real question is, does this mean that GHC is stopping the world every 
 time it puts an MVar?

No, GHC rts only locks the MVar itself.
See here:
http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358
(http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358)

Yuras




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




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


Re: [Haskell-cafe] Substituting values

2012-12-25 Thread Radical
Hey Petr,

On Sat, Dec 22, 2012 at 9:52 AM, Petr P petr@gmail.com wrote:

 I think you need something wha Scala has - the ability to create a partial
 function from a case expression. In Scala you could write

   def update[A](f: PartialFunction[A,A])(v: A): A =
 f.orElse({ case x = x } : PartialFunction[A,A]).apply(v);

 and then use it like

   update[Int]({ case Foo = Bar })



Thanks for the pointer. One distinction I remember from dabbling in Scala
some years ago is that Scala seems to formalize partiality whereas, if I'm
not mistaken, Haskell doesn't (though perhaps there are libraries that let
you do that). That is, to me a partial function in Haskell is almost
uniformly an error, whereas in Scala it's a somewhat common pattern.


 But AFAIK there is nothing like this in Haskell. Maybe separating 'of'
 from 'case' would be the way to extend Haskell with such a feature 
 http://www.haskell.org/pipermail/haskell-cafe/2012-November/104884.html


Does Haskell have a way to query at runtime whether a function is partial?
(Not in the full sense, since it would be necessary to prove totality, but
in the sense that a case expression is not exhaustive.) Otherwise, I'm not
sure how you could use a partial lambda without reaching `undefined`. (I
guess you could catch the exception.)

Thanks,

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


Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-25 Thread Yuras Shumovich
Hi,

AFAIK it is (partially?) fixed in HEAD, see
http://hackage.haskell.org/trac/ghc/ticket/367

It works for me with -fno-omit-yields

Thanks,
Yuras

On Tue, 2012-12-25 at 19:35 +0100, timothyho...@seznam.cz wrote:
 I'm not sure that there is anything great about this bug.  It seems to me 
 to be a rather severe demonstration of a somewhat already known design flaw 
 in the runtime :(
 
 Could you please comment on the actual bug rather than replying here so that
 the devs see that this behaviour has been confirmed?
 
 Tim
 
 
 -- Původní zpráva --
 Od: Corentin Dupont corentin.dup...@gmail.com
 Datum: 25. 12. 2012
 Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation
 
 
 
 Great, with me compiled with ghc -threaded the bug shows up.
 
 However, runnning main in ghci doesn't show the bug (it finishes 
 correctly).
 
 I have GHC 7.4.1.
 
  
 
 Corentin
  
 
 
 On Tue, Dec 25, 2012 at 3:34 PM, timothyho...@seznam.cz
 (mailto:timothyho...@seznam.cz) wrote:
  
 This seems like a bug in GHC. But it has nothing to do with MVars.  I've 
 narrowed this down and filed a bug report here:
 
 http://hackage.haskell.org/trac/ghc/ticket/7528
 (http://hackage.haskell.org/trac/ghc/ticket/7528)
 
 Timothy
 
 
 -- Původní zpráva --
 Od: Yuras Shumovich shumovi...@gmail.com(mailto:shumovi...@gmail.com)
 
 
 Datum: 24. 12. 2012
 Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation
 
 
 
 
 On Mon, 2012-12-24 at 16:16 +0100, timothyho...@seznam.cz
 (mailto:timothyho...@seznam.cz) wrote:
  The real question is, does this mean that GHC is stopping the world every 
  time it puts an MVar?
 
 No, GHC rts only locks the MVar itself.
 See here:
 http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358
 (http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358)
 
 Yuras
 
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org(mailto:Haskell-Cafe@haskell.org)
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 (http://www.haskell.org/mailman/listinfo/haskell-cafe)
 
 
 
 
 



___
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 http://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 Magicloud Magiclouds
You guys are great! Thanks.


On Wed, Dec 26, 2012 at 9:04 AM, Timon Gehr timon.g...@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@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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-cafehttp://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