Re: [Haskell-cafe] Enumerating functions at runtime

2013-03-25 Thread Alp Mestanogullari
More details about interface files can be found at http://hackage.haskell.org/trac/ghc/wiki/Commentary/Compiler/IfaceFiles -- in particular the 'ghc --show-iface' part should be of great interest to you. On Sun, Mar 24, 2013 at 12:22 PM, Don Stewart wrote: > All the info is in the .hi files > >

Re: [Haskell-cafe] A Thought: Backus, FP, and Brute Force Learning

2013-03-25 Thread Richard A. O'Keefe
I should mention that both functional programming in general and Backus's FP _have_ been influenced by APL, which, while imperative, strongly encourages "algebraic" combination of small functions and had (a fixed set of) higher-order "operators". As for Brute Force Learning by reading imperative c

Re: [Haskell-cafe] Make a DSL serializable

2013-03-25 Thread Alberto G. Corona
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 f

Re: [Haskell-cafe] Make a DSL serializable

2013-03-25 Thread Alberto G. Corona
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

[Haskell-cafe] Pattern matching with singletons

2013-03-25 Thread Paul Brauner
Hello, the following programs seems to hit either some limitation of GHC or maybe I'm just missing something and it behaves the intended way. {-# LANGUAGE TemplateHaskell, TypeFamilies, DataKinds, GADTs #-} module Test where import Data.Singletons data TA = CA data TB = CB data TC = CC (Either

Re: [Haskell-cafe] [high-order-munich] Munich Haskell Meeting

2013-03-25 Thread Heinrich Hördegen
Dear all, of course, our Haskell Meeting in Munich will be tomorrow, 26th of March, and not the 25th. Sorry for the wrong date! Heinrich Am 25.03.2013 06:49, schrieb Heinrich Hördegen: Dear all, tomorrow, 25th of March, will be our monthly Haskell Meeting in Munich. If you want to join,

Re: [Haskell-cafe] Make a DSL serializable

2013-03-25 Thread Brandon Allbery
On Mon, Mar 25, 2013 at 8:53 AM, Corentin Dupont wrote: > 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 al

Re: [Haskell-cafe] Make a DSL serializable

2013-03-25 Thread 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

Re: [Haskell-cafe] Make a DSL serializable

2013-03-25 Thread 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

Re: [Haskell-cafe] Make a DSL serializable

2013-03-25 Thread Daniel Trstenjak
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. http

Re: [Haskell-cafe] Parsec community and up-to-date documentation

2013-03-25 Thread Roman Cheplyaka
* Konstantine Rybnikov [2013-03-25 11:22:21+0200] > On Mon, Mar 25, 2013 at 8:49 AM, Roman Cheplyaka wrote: > > > * Konstantine Rybnikov [2013-03-25 00:19:04+0200] > > > Hi! > > > > > > I've been busy with (trying to) learning/using parsec lately and as a > > > beginner had a lot of headache st

Re: [Haskell-cafe] Parsec community and up-to-date documentation

2013-03-25 Thread Konstantine Rybnikov
On Mon, Mar 25, 2013 at 8:49 AM, Roman Cheplyaka wrote: > * Konstantine Rybnikov [2013-03-25 00:19:04+0200] > > Hi! > > > > I've been busy with (trying to) learning/using parsec lately and as a > > beginner had a lot of headache starting from outdated documentation in > > various places, lack of

Re: [Haskell-cafe] Announcement - HGamer3D - 0.2.1 - why netwire

2013-03-25 Thread Ertugrul Söylemez
Peter Althainz wrote: > Its simply the types are more cumbersome, now. In netwire you > basically have one type, which is "Wire " with some type > parameters (underlying monad, inhibition type, in-type, out-type), > When underlying monad and inhibition type is choosen, you can define a > type

Re: [Haskell-cafe] Haskell-Cafe Digest, Vol 115, Issue 37

2013-03-25 Thread Luc TAESCH
Le dimanche 24 mars 2013, a écrit : > Send Haskell-Cafe mailing list submissions to > haskell-cafe@haskell.org > > To subscribe or unsubscribe via the World Wide Web, visit > http://www.haskell.org/mailman/listinfo/haskell-cafe > or, via email, send a message with subject or body

Re: [Haskell-cafe] Announcement - HGamer3D - 0.2.1 - why netwire

2013-03-25 Thread Peter Althainz
Hi Heinrich: Its simply the types are more cumbersome, now. In netwire you basically have one type, which is "Wire " with some type parameters (underlying monad, inhibition type, in-type, out-type), When underlying monad and inhibition type is choosen, you can define a type synonym and al