Re: [Haskell-cafe] serialize an unknown type

2012-10-25 Thread Corentin Dupont
Hi,
I designed my event engine like this:

-- | events types
data Player = Arrive | Leave deriving (Typeable, Show, Eq)
data RuleEvent = Proposed | Activated | Rejected | Added | Modified |
Deleted deriving (Typeable, Show, Eq)
data Time   deriving Typeable
data InputChoice c  deriving Typeable
(...)

-- | events names
data Event a where
Player  :: Player - Event Player
RuleEv  :: RuleEvent -  Event RuleEvent
Time:: UTCTime -Event Time
InputChoice :: (Eq c, Show c) = PlayerNumber - String - [c] - c -
Event (InputChoice c)
(...)

-- | data associated with each events
data EventData a where
PlayerData  :: {playerData :: PlayerInfo}- EventData Player
RuleData:: {ruleData :: Rule}- EventData RuleEvent
TimeData:: {timeData :: UTCTime} - EventData Time
InputChoiceData :: (Show c, Read c, Typeable c) = {inputChoiceData ::
c}- EventData (InputChoice c)
(...)

-- associate an event with an handler
data EventHandler where
EH :: (Typeable e, Show e, Eq e) =
{eventNumber :: EventNumber,
 event   :: Event e,
 handler :: (EventNumber, EventData e) - Exp ()} -
EventHandler

--execute all the handlers of the specified event with the given data
triggerEvent :: (Typeable a, Show a, Eq a) = Event a - EventData a -
[EventHandler] - State Game ()


I use a type parameter e on Event and EventData to be sure that the right
data is shuffled to the right event handler.
It worked well until now. But now I'm hitting a wall with the GUI, because
the data sent back for InputChoice can only be a String.
So, I need to call triggerEvent with: Event(InputChoice String) and EventData
(InputChoice String)...
Which doesn't work obviously because the types are not the same than
initially (for example, the event was built with Event(InputChoice Bool)).

Cheers,
C




On Wed, Oct 24, 2012 at 7:25 PM, Stephen Tetley stephen.tet...@gmail.comwrote:

 Hi Corentin

 It looks like you are writing the event handler on the server side. If
 so, the range of events you can handle is fixed to just those you
 implement handlers for - having an openly extensible event type is
 useless if this is the case.

 Ignoring client/server for a moment, a function (State - State) would
 be the most extensible API you could allow for clients. You don't
 need to worry about an open set of Event types, a client knows the
 state exactly and doesn't need extensibility.

 Client/Server operation won't allow a state transformer API as Haskell
 can't readily serialize functions. But you can implement a command
 language enumerating state changing operations. The second Quickcheck
 paper gives a very good example of how to implement such a command
 language.


 Testing Monadic Code with QuickCheck (2002)
 Koen Claessen , John Hughes
 www.cse.chalmers.se/~rjmh/Papers/QuickCheckST.ps

 Or Citeseer if you need a PDF:
 http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.19.9275

 ___
 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] serialize an unknown type

2012-10-24 Thread Corentin Dupont
I'm trying to get around my problem (still stuck...).
I have really to call a function like this:
triggerEvent :: (Typeable e, Show e, Eq e) = Event e - EventData e -
State Game ()

This function simply execute an event given the corresponding data and
change the state of the game.
Now as explained my web framework won't accept random types (like e) to
be passed around.
So I said to myself OK, so let's store the events in a list and ask the
gui to just give me the number of the event.
So I have an heterogeneous list of events [EventWrap]:

data EventWrap where
EW :: (Typeable e, Show e, Eq e) = {eventNumber :: Int, event :: Event
e} - EventWrap

Do you think this solution can lead me somewhere?? I have actually doubts I
can find back my Event e from the list because of the implicit forall in
the GADT.

Thanks,
Corentin


On Wed, Oct 24, 2012 at 3:37 PM, Chris Smith cdsm...@gmail.com wrote:

 Corentin Dupont corentin.dup...@gmail.com wrote:
  I could ask my user to make his new type an instance of a class as
 suggested by Alberto...

 If you are working with unknown types, then your options are: (a)
 constrain to some type class, or (b) have your clients pass in functions to
 operate on the type alongside the values.  Actually the first is just a
 special case of the second with syntactic sugar...

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


Re: [Haskell-cafe] serialize an unknown type

2012-10-24 Thread Stephen Tetley
Hi Corentin

It looks like you are writing the event handler on the server side. If
so, the range of events you can handle is fixed to just those you
implement handlers for - having an openly extensible event type is
useless if this is the case.

Ignoring client/server for a moment, a function (State - State) would
be the most extensible API you could allow for clients. You don't
need to worry about an open set of Event types, a client knows the
state exactly and doesn't need extensibility.

Client/Server operation won't allow a state transformer API as Haskell
can't readily serialize functions. But you can implement a command
language enumerating state changing operations. The second Quickcheck
paper gives a very good example of how to implement such a command
language.


Testing Monadic Code with QuickCheck (2002)
Koen Claessen , John Hughes
www.cse.chalmers.se/~rjmh/Papers/QuickCheckST.ps

Or Citeseer if you need a PDF:
http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.19.9275

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


Re: [Haskell-cafe] serialize an unknown type

2012-10-21 Thread Corentin Dupont
Nobody on this one?
Here is a simplified version:

data Event a where
InputChoice ::  a - Event a

How to serialize/deserialize this?

Cheers,
Corentin

On Sat, Oct 20, 2012 at 10:49 PM, Corentin Dupont corentin.dup...@gmail.com
 wrote:

 Hi the list!
 I have a simple question, how can I serialize/deserialize a structure like
 this:

 data InputChoice c  deriving Typeable
 data Event a where
 InputChoice :: (Eq c, Show c) = [c] - c - Event (InputChoice c)
  (...)

 I'd like that the values of type c get serialized to a String... That's
 the easy part, but for deserializing, oops!

 Cheers,
 Corentin

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


Re: [Haskell-cafe] serialize an unknown type

2012-10-21 Thread Brandon Allbery
On Sun, Oct 21, 2012 at 12:39 PM, Corentin Dupont corentin.dup...@gmail.com
 wrote:

 Nobody on this one?
 Here is a simplified version:

 data Event a where
 InputChoice ::  a - Event a

 How to serialize/deserialize this?


How were you expecting to serialize/deserialize a function?

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix/linux, openafs, kerberos, infrastructure  http://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] serialize an unknown type

2012-10-21 Thread MigMit
Seems like nobody really understands what is it that you want to accomplish or 
what your problem is.

Отправлено с iPhone

21.10.2012, в 20:39, Corentin Dupont corentin.dup...@gmail.com написал(а):

 Nobody on this one?
 Here is a simplified version:
 
 data Event a where
 InputChoice ::  a - Event a
 
 How to serialize/deserialize this?
 
 Cheers,
 Corentin
 
 On Sat, Oct 20, 2012 at 10:49 PM, Corentin Dupont corentin.dup...@gmail.com 
 wrote:
 Hi the list!
 I have a simple question, how can I serialize/deserialize a structure like 
 this:
 
 data InputChoice c  deriving Typeable
 data Event a where
 InputChoice :: (Eq c, Show c) = [c] - c - Event (InputChoice c)
  (...)
 
 I'd like that the values of type c get serialized to a String... That's 
 the easy part, but for deserializing, oops!
 
 Cheers,
 Corentin
 
 ___
 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] serialize an unknown type

2012-10-21 Thread Corentin Dupont
Hi,
Sorry if it was not enough explicit.
I want to write functions like this:

serialize :: (Show a) = Event a - IO ()
deserialize :: (Read a) = IO () - Event a

The functions would write and read the data in a file, storing/retrieving
also the type a I suppose...
BR,
C



On Sun, Oct 21, 2012 at 7:03 PM, MigMit miguelim...@yandex.ru wrote:

 Seems like nobody really understands what is it that you want to
 accomplish or what your problem is.

 Отправлено с iPhone

 21.10.2012, в 20:39, Corentin Dupont corentin.dup...@gmail.com
 написал(а):

 Nobody on this one?
 Here is a simplified version:

 data Event a where
 InputChoice ::  a - Event a

 How to serialize/deserialize this?

 Cheers,
 Corentin

 On Sat, Oct 20, 2012 at 10:49 PM, Corentin Dupont 
 corentin.dup...@gmail.com wrote:

 Hi the list!
 I have a simple question, how can I serialize/deserialize a structure
 like this:

 data InputChoice c  deriving Typeable
 data Event a where
 InputChoice :: (Eq c, Show c) = [c] - c - Event (InputChoice c)
  (...)

 I'd like that the values of type c get serialized to a String... That's
 the easy part, but for deserializing, oops!

 Cheers,
 Corentin


 ___
 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] serialize an unknown type

2012-10-21 Thread Iustin Pop
On Sun, Oct 21, 2012 at 07:20:10PM +0200, Corentin Dupont wrote:
 Hi,
 Sorry if it was not enough explicit.
 I want to write functions like this:
 
 serialize :: (Show a) = Event a - IO ()
 deserialize :: (Read a) = IO () - Event a
 
 The functions would write and read the data in a file, storing/retrieving
 also the type a I suppose...

Can't you simply, when defining the type event, add a deriving (Show,
Read)? Then the standard (but slow) read/show serialisation would work
for you.

If you're asking to de-serialise an unknown type (i.e. you don't know
what type it should restore a-priori, but you want to do that based on
the contents of the file), things become a little more complex. Unless
you can further restrict the type 'a', really complex.

Maybe stating your actual problem, rather than the implementation
question, would be better?

regards,
iustin

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


Re: [Haskell-cafe] serialize an unknown type

2012-10-21 Thread Corentin Dupont
Hi Iustin,
yes I want to deserialize an unknown type based on the content of the file
(in this example).
Let's say I can reduce the spectum of types to: Strings, all the types in
Enum, Ints. Is it possible?

My real problem is that on my web interface I want to use web routes to
allow a user to pass an Event back to the engine.
The problem is that it seems that web-routes only accepts Strings (or some
known types) to be passed on the web route, whereas I need to pass random
types.


On Sun, Oct 21, 2012 at 8:00 PM, Iustin Pop iu...@k1024.org wrote:

 On Sun, Oct 21, 2012 at 07:20:10PM +0200, Corentin Dupont wrote:
  Hi,
  Sorry if it was not enough explicit.
  I want to write functions like this:
 
  serialize :: (Show a) = Event a - IO ()
  deserialize :: (Read a) = IO () - Event a
 
  The functions would write and read the data in a file, storing/retrieving
  also the type a I suppose...

 Can't you simply, when defining the type event, add a deriving (Show,
 Read)? Then the standard (but slow) read/show serialisation would work
 for you.

 If you're asking to de-serialise an unknown type (i.e. you don't know
 what type it should restore a-priori, but you want to do that based on
 the contents of the file), things become a little more complex. Unless
 you can further restrict the type 'a', really complex.

 Maybe stating your actual problem, rather than the implementation
 question, would be better?

 regards,
 iustin

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


Re: [Haskell-cafe] serialize an unknown type

2012-10-21 Thread MigMit
Oh, now I've got it.

First of all, functions of type IO () - Event a are impossible (unless you 
resort to tricks with unsafePerformIO, which is not what you want to deal with 
right now). You've probably meant something like IO (Event a) (at least, that 
is the type of function which would read Event a from file or input stream or 
something else external).

Secondly, functions (and values) with parametric types, like IO (Event a) 
require you to provide the type a in your code. They won't take it from 
somewhere magically. You can take a look at the read function in Prelude for 
example.

If you really want to store the type information and read it back, you should 
do it yourself, inventing some representation for your type, writing it to 
disk, reading back and parsing it. And you can't do that for all types in 
existence, so you'll need to do that for some specific types (and no, instances 
of Typeable aren't what you want). And you'll have to deal with type system, 
which won't allow you to just say hey, let that be whatever type it happens to 
be, I don't care; you'd have to wrap this into one existentially quantified 
type (or GADT).

Keep in mind that this is not very Haskell-y. First of all, try to analyse, 
what this a in Event a could be. What are the limits here? And don't say 
there aren't any, because if you don't know anything about the type, you can't 
do anything with it. So, maybe you would end up with a finite set of types — 
this would simplify matters a lot. Or maybe you'd find out that there are 
inifinitely many types of events — but they can be somehow generated with a 
finite number of constructors — that would be quite simple as well.

So, what is the bigger picture here?

On Oct 21, 2012, at 9:20 PM, Corentin Dupont corentin.dup...@gmail.com wrote:

 Hi,
 Sorry if it was not enough explicit.
 I want to write functions like this:
 
 serialize :: (Show a) = Event a - IO ()
 deserialize :: (Read a) = IO () - Event a
 
 The functions would write and read the data in a file, storing/retrieving 
 also the type a I suppose...
 BR,
 C
 
 
 
 On Sun, Oct 21, 2012 at 7:03 PM, MigMit miguelim...@yandex.ru wrote:
 Seems like nobody really understands what is it that you want to accomplish 
 or what your problem is.
 
 Отправлено с iPhone
 
 21.10.2012, в 20:39, Corentin Dupont corentin.dup...@gmail.com написал(а):
 
 Nobody on this one?
 Here is a simplified version:
 
 data Event a where
 InputChoice ::  a - Event a
 
 How to serialize/deserialize this?
 
 Cheers,
 Corentin
 
 On Sat, Oct 20, 2012 at 10:49 PM, Corentin Dupont 
 corentin.dup...@gmail.com wrote:
 Hi the list!
 I have a simple question, how can I serialize/deserialize a structure like 
 this:
 
 data InputChoice c  deriving Typeable
 data Event a where
 InputChoice :: (Eq c, Show c) = [c] - c - Event (InputChoice c)
  (...)
 
 I'd like that the values of type c get serialized to a String... That's 
 the easy part, but for deserializing, oops!
 
 Cheers,
 Corentin
 
 ___
 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] serialize an unknown type

2012-10-21 Thread Alberto G. Corona
You can include the type in the serialized string. When recovering you can
read the type and use to look for the appropriate deserializer in a lookup
table where you have registered the deserializer.

I use this trick in the IDynamic package,. that serializes-deserializes
dynamic types:

http://hackage.haskell.org/package/IDynamic-0.1


2012/10/20 Corentin Dupont corentin.dup...@gmail.com

 Hi the list!
 I have a simple question, how can I serialize/deserialize a structure like
 this:

 data InputChoice c  deriving Typeable
 data Event a where
 InputChoice :: (Eq c, Show c) = [c] - c - Event (InputChoice c)
  (...)

 I'd like that the values of type c get serialized to a String... That's
 the easy part, but for deserializing, oops!

 Cheers,
 Corentin

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




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


Re: [Haskell-cafe] serialize an unknown type

2012-10-21 Thread Iustin Pop
On Sun, Oct 21, 2012 at 08:11:50PM +0200, Corentin Dupont wrote:
 Hi Iustin,
 yes I want to deserialize an unknown type based on the content of the file
 (in this example).
 Let's say I can reduce the spectum of types to: Strings, all the types in
 Enum, Ints. Is it possible?

Maybe :) I don't know how to do all the types in enum. For Strings,
Ints and Float, you could have something like: serialise a pair instead
of just the type, and decode:

data Event = EventString String | EventInt Int | EventFloat Float
…
  (kind, val) - read in_data
  return $ case kind of
string - EventString val
int - EventInt (read val)
float - EventFloat (read val)

But this is only for a very few specific types.

 My real problem is that on my web interface I want to use web routes to
 allow a user to pass an Event back to the engine.
 The problem is that it seems that web-routes only accepts Strings (or some
 known types) to be passed on the web route, whereas I need to pass random
 types.

Are you sure you need to pass random types? Can't you define a (large)
set of known types, for example?

regards,
iustin

 On Sun, Oct 21, 2012 at 8:00 PM, Iustin Pop iu...@k1024.org wrote:
 
  On Sun, Oct 21, 2012 at 07:20:10PM +0200, Corentin Dupont wrote:
   Hi,
   Sorry if it was not enough explicit.
   I want to write functions like this:
  
   serialize :: (Show a) = Event a - IO ()
   deserialize :: (Read a) = IO () - Event a
  
   The functions would write and read the data in a file, storing/retrieving
   also the type a I suppose...
 
  Can't you simply, when defining the type event, add a deriving (Show,
  Read)? Then the standard (but slow) read/show serialisation would work
  for you.
 
  If you're asking to de-serialise an unknown type (i.e. you don't know
  what type it should restore a-priori, but you want to do that based on
  the contents of the file), things become a little more complex. Unless
  you can further restrict the type 'a', really complex.
 
  Maybe stating your actual problem, rather than the implementation
  question, would be better?
 
  regards,
  iustin
 

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


Re: [Haskell-cafe] serialize an unknown type

2012-10-21 Thread Corentin Dupont
On Sun, Oct 21, 2012 at 8:42 PM, MigMit miguelim...@yandex.ru wrote:

 Oh, now I've got it.

 First of all, functions of type IO () - Event a are impossible (unless
 you resort to tricks with unsafePerformIO, which is not what you want to
 deal with right now). You've probably meant something like IO (Event a)
 (at least, that is the type of function which would read Event a from
 file or input stream or something else external).


Yes, sorry, that's what I meant.



 Secondly, functions (and values) with parametric types, like IO (Event
 a) require you to provide the type a in your code. They won't take it
 from somewhere magically. You can take a look at the read function in
 Prelude for example.

 If you really want to store the type information and read it back, you
 should do it yourself, inventing some representation for your type, writing
 it to disk, reading back and parsing it. And you can't do that for all
 types in existence, so you'll need to do that for some specific types (and
 no, instances of Typeable aren't what you want). And you'll have to deal
 with type system, which won't allow you to just say hey, let that be
 whatever type it happens to be, I don't care; you'd have to wrap this into
 one existentially quantified type (or GADT).

 Keep in mind that this is not very Haskell-y. First of all, try to
 analyse, what this a in Event a could be. What are the limits here? And
 don't say there aren't any, because if you don't know anything about the
 type, you can't do anything with it. So, maybe you would end up with a
 finite set of types -- this would simplify matters a lot. Or maybe you'd
 find out that there are inifinitely many types of events -- but they can be
 somehow generated with a finite number of constructors -- that would be
 quite simple as well.

 So, what is the bigger picture here?



In my application, the user can define the a. That's what makes it
difficult. For example, the user can define a new enumerate and submit it
to the program (it will be interpreted by hint):
data Choice = You | Me  | Them | Everybody deriving (Enum, Typeable, Show,
Eq, Bounded)
So, the list of types is not known in advance.
I could ask my user to make his new type an instance of a class as
suggested by Alberto...




 On Oct 21, 2012, at 9:20 PM, Corentin Dupont corentin.dup...@gmail.com
 wrote:

  Hi,
  Sorry if it was not enough explicit.
  I want to write functions like this:
 
  serialize :: (Show a) = Event a - IO ()
  deserialize :: (Read a) = IO () - Event a
 
  The functions would write and read the data in a file,
 storing/retrieving also the type a I suppose...
  BR,
  C
 
 
 
  On Sun, Oct 21, 2012 at 7:03 PM, MigMit miguelim...@yandex.ru wrote:
  Seems like nobody really understands what is it that you want to
 accomplish or what your problem is.
 
  Отправлено с iPhone
 
  21.10.2012, в 20:39, Corentin Dupont corentin.dup...@gmail.com
 написал(а):
 
  Nobody on this one?
  Here is a simplified version:
 
  data Event a where
  InputChoice ::  a - Event a
 
  How to serialize/deserialize this?
 
  Cheers,
  Corentin
 
  On Sat, Oct 20, 2012 at 10:49 PM, Corentin Dupont 
 corentin.dup...@gmail.com wrote:
  Hi the list!
  I have a simple question, how can I serialize/deserialize a structure
 like this:
 
  data InputChoice c  deriving Typeable
  data Event a where
  InputChoice :: (Eq c, Show c) = [c] - c - Event (InputChoice c)
   (...)
 
  I'd like that the values of type c get serialized to a String...
 That's the easy part, but for deserializing, oops!
 
  Cheers,
  Corentin
 
  ___
  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


[Haskell-cafe] serialize an unknown type

2012-10-20 Thread Corentin Dupont
Hi the list!
I have a simple question, how can I serialize/deserialize a structure like
this:

data InputChoice c  deriving Typeable
data Event a where
InputChoice :: (Eq c, Show c) = [c] - c - Event (InputChoice c)
 (...)

I'd like that the values of type c get serialized to a String... That's
the easy part, but for deserializing, oops!

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