
Hi Café, I have a DSL like this: data Exp where OnEvent :: EventName -> (Int -> Exp) -> Exp (...) The "OnEvent" element carries a function (the handler to be called when the event happens), and that makes my DSL non showable/serializable. How could I fix that? This is a real handicap not to be able to serialize the state of my whole application because of that :) Thanks, Corentin

Hi Corentin,
I have a DSL like this: data Exp where OnEvent :: EventName -> (Int -> Exp) -> Exp (...)
The "OnEvent" element carries a function (the handler to be called when the event happens), and that makes my DSL non showable/serializable. How could I fix that? This is a real handicap not to be able to serialize the state of my whole application because of that :)
You could have a unique id for your handlers, which might be an Int or a String and have some kind of registration for the handlers. data Exp where OnEvent :: EventName -> HandlerId -> Exp type HandlerId = String type Handler = (Int -> Exp) type Handlers = HashMap HandlerId Handler registerHandler :: Handlers -> (HandlerId, Handler) -> Handlers getHandler :: Handlers -> HandlerId -> Maybe Handler But you have to ensure, that for each application run the same HandlerId also gets the same Handler. Less flexible but more secure is an ADT for you Handler. data Handler = DoThat | DoSometingElse You can than just pattern match on your handler and don't need any kind of registration. But you can go further and define your own little Handler DSL. Greetings, Daniel

Hi Daniel, in my game the handlers are supplied by the players as part of little programs that they submit. An haskell interpreter is reading the program code submitted and inserts it in the game. So there is an infinite number of handlers... I was thinking of hiding the parameters of the handlers like this: data Exp a where OnEvent :: EventName -> Exp () -> Exp () getArg :: Exp Int setArg :: Exp () deriving (Show) Now it should be possible to write the Show instance: instance Show a -> Show (Exp a) where ... You could write a program like this: myProgram :: Exp () myProgram = do OnEvent NewPlayer (getArg >>= (\name -> output $ "Hello to player " ++ name)) But I don't find it elegant at all: there is no compile time guaranty that the caller will set the argument correctly as you can have with normal function signatures... Best, Corentin On Sun, Mar 24, 2013 at 6:25 PM, Daniel Trstenjak < daniel.trstenjak@gmail.com> wrote:
Hi Corentin,
I have a DSL like this: data Exp where OnEvent :: EventName -> (Int -> Exp) -> Exp (...)
The "OnEvent" element carries a function (the handler to be called when the event happens), and that makes my DSL non showable/serializable. How could I fix that? This is a real handicap not to be able to serialize the state of my whole application because of that :)
You could have a unique id for your handlers, which might be an Int or a String and have some kind of registration for the handlers.
data Exp where OnEvent :: EventName -> HandlerId -> Exp
type HandlerId = String type Handler = (Int -> Exp) type Handlers = HashMap HandlerId Handler
registerHandler :: Handlers -> (HandlerId, Handler) -> Handlers getHandler :: Handlers -> HandlerId -> Maybe Handler
But you have to ensure, that for each application run the same HandlerId also gets the same Handler.
Less flexible but more secure is an ADT for you Handler.
data Handler = DoThat | DoSometingElse
You can than just pattern match on your handler and don't need any kind of registration.
But you can go further and define your own little Handler DSL.
Greetings, Daniel
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, Mar 24, 2013 at 4:16 PM, Corentin Dupont
Hi Daniel, in my game the handlers are supplied by the players as part of little programs that they submit. An haskell interpreter is reading the program code submitted and inserts it in the game. So there is an infinite number of handlers...
You might store both the compiled code and the originally submitted code, and serialize the latter in a form that restart can recompile. I don't think that can be any less safe than the original submission/compilation/insertion. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Hi Brandon,
in fact, that's what I'm doing. I record the list of actions performed by
the players, including the submission of the code. I serialize this list of
actions instead of the state of the game. When deserializing, I replay all
the players actions from scratch to get back to the same state than before.
This is the only way to do it (replaying from scratch), since the pieces of
code submitted can interact with other pieces of code submitted earlier:
they are not independant.
But I always bothered me that this state is not serializable...
On Sun, Mar 24, 2013 at 10:02 PM, Brandon Allbery
On Sun, Mar 24, 2013 at 4:16 PM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
Hi Daniel, in my game the handlers are supplied by the players as part of little programs that they submit. An haskell interpreter is reading the program code submitted and inserts it in the game. So there is an infinite number of handlers...
You might store both the compiled code and the originally submitted code, and serialize the latter in a form that restart can recompile. I don't think that can be any less safe than the original submission/compilation/insertion.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Sun, Mar 24, 2013 at 5:44 PM, Corentin Dupont
But I always bothered me that this state is not serializable...
I am not quite sure how to respond to that. You seem to be asking for magic. That kind of state has never been sanely serializeable. Not in Haskell, not anywhere else. The usual hack is to dump an entire memory image to disk, either as an executable (see "gcore" and "undump"; also see how the GNU emacs build dumps a "preloaded" emacs executable) or by dumping the data segment as raw bytes and reloading it as such (which doesn't work so well in modern demand paged executables; it can work better with a virtual machine environment, and various Lisp and Smalltalk implementations dump and reload their raw VM images this way). I would not be surprised if what you seem to be asking for turns out to be yet another guise of the halting problem. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Isn't this similar to the problem Cloud Haskell had to solve to send code
to another process to run?
Mike
On Mar 24, 2013 5:06 PM, "Brandon Allbery"
On Sun, Mar 24, 2013 at 5:44 PM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
But I always bothered me that this state is not serializable...
I am not quite sure how to respond to that. You seem to be asking for magic.
That kind of state has never been sanely serializeable. Not in Haskell, not anywhere else. The usual hack is to dump an entire memory image to disk, either as an executable (see "gcore" and "undump"; also see how the GNU emacs build dumps a "preloaded" emacs executable) or by dumping the data segment as raw bytes and reloading it as such (which doesn't work so well in modern demand paged executables; it can work better with a virtual machine environment, and various Lisp and Smalltalk implementations dump and reload their raw VM images this way).
I would not be surprised if what you seem to be asking for turns out to be yet another guise of the halting problem.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@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

I also came across Scala's Swarm, making use serializable delimited
continuations. Looks good!
http://www.scala-lang.org/node/3485
On Sun, Mar 24, 2013 at 11:13 PM, Michael Better
Isn't this similar to the problem Cloud Haskell had to solve to send code to another process to run?
Mike On Mar 24, 2013 5:06 PM, "Brandon Allbery"
wrote: On Sun, Mar 24, 2013 at 5:44 PM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
But I always bothered me that this state is not serializable...
I am not quite sure how to respond to that. You seem to be asking for magic.
That kind of state has never been sanely serializeable. Not in Haskell, not anywhere else. The usual hack is to dump an entire memory image to disk, either as an executable (see "gcore" and "undump"; also see how the GNU emacs build dumps a "preloaded" emacs executable) or by dumping the data segment as raw bytes and reloading it as such (which doesn't work so well in modern demand paged executables; it can work better with a virtual machine environment, and various Lisp and Smalltalk implementations dump and reload their raw VM images this way).
I would not be surprised if what you seem to be asking for turns out to be yet another guise of the halting problem.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@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

the package Workflow serialize also the state of a computation, so it can
be re-started and continued. It uses also the above mentioned event trick
to serialize the state.
By the way you can use the workflow monad transformer to recover the state
of the game. You don´t need to serialize anything explicitly, the
transformer will do it, but your step results must be serializable.
If you have this code:
loop= do
eventhandlercode <- receive
handler <- compile eventhandlercode
execute handler
loop
then the lifted process in the workflow monad would be:
loop=do
eventhandlercode <- step receive
handler <- liftIO $ compile eventhandlercode
liftIO $ execute handler
loop
step will store the result and will recover the execution state.
Only the step result should be serializable.
2013/3/24 Corentin Dupont
I also came across Scala's Swarm, making use serializable delimited continuations. Looks good! http://www.scala-lang.org/node/3485
On Sun, Mar 24, 2013 at 11:13 PM, Michael Better
wrote: Isn't this similar to the problem Cloud Haskell had to solve to send code to another process to run?
Mike On Mar 24, 2013 5:06 PM, "Brandon Allbery"
wrote: On Sun, Mar 24, 2013 at 5:44 PM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
But I always bothered me that this state is not serializable...
I am not quite sure how to respond to that. You seem to be asking for magic.
That kind of state has never been sanely serializeable. Not in Haskell, not anywhere else. The usual hack is to dump an entire memory image to disk, either as an executable (see "gcore" and "undump"; also see how the GNU emacs build dumps a "preloaded" emacs executable) or by dumping the data segment as raw bytes and reloading it as such (which doesn't work so well in modern demand paged executables; it can work better with a virtual machine environment, and various Lisp and Smalltalk implementations dump and reload their raw VM images this way).
I would not be surprised if what you seem to be asking for turns out to be yet another guise of the halting problem.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alberto.

Workflow is impressive! I didn't know you could serialize IO
states/computations.
On Mon, Mar 25, 2013 at 2:06 AM, Alberto G. Corona
the package Workflow serialize also the state of a computation, so it can be re-started and continued. It uses also the above mentioned event trick to serialize the state.
By the way you can use the workflow monad transformer to recover the state of the game. You don´t need to serialize anything explicitly, the transformer will do it, but your step results must be serializable.
If you have this code:
loop= do eventhandlercode <- receive handler <- compile eventhandlercode execute handler loop
then the lifted process in the workflow monad would be:
loop=do eventhandlercode <- step receive handler <- liftIO $ compile eventhandlercode liftIO $ execute handler loop
step will store the result and will recover the execution state. Only the step result should be serializable.
2013/3/24 Corentin Dupont
I also came across Scala's Swarm, making use serializable delimited continuations. Looks good! http://www.scala-lang.org/node/3485
On Sun, Mar 24, 2013 at 11:13 PM, Michael Better
wrote: Isn't this similar to the problem Cloud Haskell had to solve to send code to another process to run?
Mike On Mar 24, 2013 5:06 PM, "Brandon Allbery"
wrote: On Sun, Mar 24, 2013 at 5:44 PM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
But I always bothered me that this state is not serializable...
I am not quite sure how to respond to that. You seem to be asking for magic.
That kind of state has never been sanely serializeable. Not in Haskell, not anywhere else. The usual hack is to dump an entire memory image to disk, either as an executable (see "gcore" and "undump"; also see how the GNU emacs build dumps a "preloaded" emacs executable) or by dumping the data segment as raw bytes and reloading it as such (which doesn't work so well in modern demand paged executables; it can work better with a virtual machine environment, and various Lisp and Smalltalk implementations dump and reload their raw VM images this way).
I would not be surprised if what you seem to be asking for turns out to be yet another guise of the halting problem.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alberto.

On Mon, Mar 25, 2013 at 8:53 AM, Corentin Dupont
Workflow is impressive! I didn't know you could serialize IO states/computations.
In certain constrained cases you can. General case, as I said earlier, is kinda impossible without serializing the entire machine state. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Corentin:
Thanks. It is not exactly the serialization of IO state computations,
but when re-started, the IO state is recreated from
the serialized intermediate results. It makes use of a simple idea,
although it is not easy to realize it practically.
I suppose that scala does something similar for their
serializable delimited continuations.
2013/3/25 Corentin Dupont
Workflow is impressive! I didn't know you could serialize IO states/computations.
On Mon, Mar 25, 2013 at 2:06 AM, Alberto G. Corona
wrote: the package Workflow serialize also the state of a computation, so it can be re-started and continued. It uses also the above mentioned event trick to serialize the state.
By the way you can use the workflow monad transformer to recover the state of the game. You don´t need to serialize anything explicitly, the transformer will do it, but your step results must be serializable.
If you have this code:
loop= do eventhandlercode <- receive handler <- compile eventhandlercode execute handler loop
then the lifted process in the workflow monad would be:
loop=do eventhandlercode <- step receive handler <- liftIO $ compile eventhandlercode liftIO $ execute handler loop
step will store the result and will recover the execution state. Only the step result should be serializable.
2013/3/24 Corentin Dupont
I also came across Scala's Swarm, making use serializable delimited continuations. Looks good! http://www.scala-lang.org/node/3485
On Sun, Mar 24, 2013 at 11:13 PM, Michael Better
wrote: Isn't this similar to the problem Cloud Haskell had to solve to send code to another process to run?
Mike On Mar 24, 2013 5:06 PM, "Brandon Allbery"
wrote: On Sun, Mar 24, 2013 at 5:44 PM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
But I always bothered me that this state is not serializable...
I am not quite sure how to respond to that. You seem to be asking for magic.
That kind of state has never been sanely serializeable. Not in Haskell, not anywhere else. The usual hack is to dump an entire memory image to disk, either as an executable (see "gcore" and "undump"; also see how the GNU emacs build dumps a "preloaded" emacs executable) or by dumping the data segment as raw bytes and reloading it as such (which doesn't work so well in modern demand paged executables; it can work better with a virtual machine environment, and various Lisp and Smalltalk implementations dump and reload their raw VM images this way).
I would not be surprised if what you seem to be asking for turns out to be yet another guise of the halting problem.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alberto.
-- Alberto.

Hi Michael, On Sun, Mar 24, 2013 at 05:13:35PM -0500, Michael Better wrote:
Isn't this similar to the problem Cloud Haskell had to solve to send code to another process to run?
As much as I know, the sendable code of 'Cloud Haskell' is limited, you can't just send any kind of function. https://github.com/jepst/CloudHaskell#process-management Greetings, Daniel

On Sun, Mar 24, 2013 at 11:05 PM, Brandon Allbery
On Sun, Mar 24, 2013 at 5:44 PM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
But I always bothered me that this state is not serializable...
I am not quite sure how to respond to that. You seem to be asking for magic.
haha as always :) But Haskell is a bit about magic...
That kind of state has never been sanely serializeable. Not in Haskell, not anywhere else. The usual hack is to dump an entire memory image to disk, either as an executable (see "gcore" and "undump"; also see how the GNU emacs build dumps a "preloaded" emacs executable) or by dumping the data segment as raw bytes and reloading it as such (which doesn't work so well in modern demand paged executables; it can work better with a virtual machine environment, and various Lisp and Smalltalk implementations dump and reload their raw VM images this way).
I would not be surprised if what you seem to be asking for turns out to be yet another guise of the halting problem.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

That is the advantage of recording the sequence of events instead of the
final state: that the state don´t need to be seriallizable. And this
indeed the way to serlize something that can be decomposed in events. I
think that this is elegant.. Specially if the events and the state are
elements of a Monoid instance.
2013/3/24 Corentin Dupont
Hi Brandon, in fact, that's what I'm doing. I record the list of actions performed by the players, including the submission of the code. I serialize this list of actions instead of the state of the game. When deserializing, I replay all the players actions from scratch to get back to the same state than before. This is the only way to do it (replaying from scratch), since the pieces of code submitted can interact with other pieces of code submitted earlier: they are not independant. But I always bothered me that this state is not serializable...
On Sun, Mar 24, 2013 at 10:02 PM, Brandon Allbery
wrote: On Sun, Mar 24, 2013 at 4:16 PM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
Hi Daniel, in my game the handlers are supplied by the players as part of little programs that they submit. An haskell interpreter is reading the program code submitted and inserts it in the game. So there is an infinite number of handlers...
You might store both the compiled code and the originally submitted code, and serialize the latter in a form that restart can recompile. I don't think that can be any less safe than the original submission/compilation/insertion.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@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
-- Alberto.

What do you mean by monoid? It's not clear to me how a state (essentially a
structure with many fields) can be a monoid...
I figured out that the Writer monad may be good for that purpose.
On Mon, Mar 25, 2013 at 1:50 AM, Alberto G. Corona
That is the advantage of recording the sequence of events instead of the final state: that the state don´t need to be seriallizable. And this indeed the way to serlize something that can be decomposed in events. I think that this is elegant.. Specially if the events and the state are elements of a Monoid instance.
2013/3/24 Corentin Dupont
Hi Brandon, in fact, that's what I'm doing. I record the list of actions performed by the players, including the submission of the code. I serialize this list of actions instead of the state of the game. When deserializing, I replay all the players actions from scratch to get back to the same state than before. This is the only way to do it (replaying from scratch), since the pieces of code submitted can interact with other pieces of code submitted earlier: they are not independant. But I always bothered me that this state is not serializable...
On Sun, Mar 24, 2013 at 10:02 PM, Brandon Allbery
wrote: On Sun, Mar 24, 2013 at 4:16 PM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
Hi Daniel, in my game the handlers are supplied by the players as part of little programs that they submit. An haskell interpreter is reading the program code submitted and inserts it in the game. So there is an infinite number of handlers...
You might store both the compiled code and the originally submitted code, and serialize the latter in a form that restart can recompile. I don't think that can be any less safe than the original submission/compilation/insertion.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@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
-- Alberto.

It is possible as long as there is a empty event and there is a operation
that mix two events to créate an state and an operation that mix an state
and a event to créate an state.
Then, if the events are serializable, the deserialization of the state from
a serialized list of events would be
deserialize list= mconcat . read $ list
it is a way to have a general expression for the deserialization instead of
a ad-hoc loop.
2013/3/25 Corentin Dupont
What do you mean by monoid? It's not clear to me how a state (essentially a structure with many fields) can be a monoid... I figured out that the Writer monad may be good for that purpose.
On Mon, Mar 25, 2013 at 1:50 AM, Alberto G. Corona
wrote: That is the advantage of recording the sequence of events instead of the final state: that the state don´t need to be seriallizable. And this indeed the way to serlize something that can be decomposed in events. I think that this is elegant.. Specially if the events and the state are elements of a Monoid instance.
2013/3/24 Corentin Dupont
Hi Brandon, in fact, that's what I'm doing. I record the list of actions performed by the players, including the submission of the code. I serialize this list of actions instead of the state of the game. When deserializing, I replay all the players actions from scratch to get back to the same state than before. This is the only way to do it (replaying from scratch), since the pieces of code submitted can interact with other pieces of code submitted earlier: they are not independant. But I always bothered me that this state is not serializable...
On Sun, Mar 24, 2013 at 10:02 PM, Brandon Allbery
wrote: On Sun, Mar 24, 2013 at 4:16 PM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
Hi Daniel, in my game the handlers are supplied by the players as part of little programs that they submit. An haskell interpreter is reading the program code submitted and inserts it in the game. So there is an infinite number of handlers...
You might store both the compiled code and the originally submitted code, and serialize the latter in a form that restart can recompile. I don't think that can be any less safe than the original submission/compilation/insertion.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@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
-- Alberto.
-- Alberto.

On 2013-03-25 19:00:42 +0000, Alberto G. Corona said:
It is possible as long as there is a empty event and there is a operation that mix two events to créate an state and an operation that mix an state and a event to créate an state.
I just read this at a time I am learning FRP Reactive banana and these two collides : Workflow (Event, state) ~ FRP (Event, bahavior) is that anyway connected, Alberto ? ( workflow and FRP ) ( are worflow are serializable persitent FRP Network ?)
-

Hi Luc,
I really don't know what exactly what FRP is. Every time i read about it, I
figure out different things depending on the library.
I used the term event in a wider way as something that happens in the
computation no matter if it is generated inside or outside. Workflow
does not handle -external- events althout it can be used in this context,
like the example loop that I wrote above.
I think that it can be used to recover the state of a FRP program after
restart, in the same ortogonal way than in the example above, lifting the
computation with the workflow transformer
2013/3/26 luc taesch
On 2013-03-25 19:00:42 +0000, Alberto G. Corona said:
It is possible as long as there is a empty event and there is a
operation that mix two events to créate an state and an operation that mix an state and a event to créate an state.
I just read this at a time I am learning FRP Reactive banana and these two collides : Workflow (Event, state) ~ FRP (Event, bahavior)
is that anyway connected, Alberto ? ( workflow and FRP ) ( are worflow are serializable persitent FRP Network ?)
-
______________________________**_________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alberto.
participants (6)
-
Alberto G. Corona
-
Brandon Allbery
-
Corentin Dupont
-
Daniel Trstenjak
-
luc taesch
-
Michael Better