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

[Haskell-cafe] createProcess fails to find executable in Windows

2012-10-25 Thread José Pedro Magalhães
Hi all, Consider the following program: module Test where import System.Process (readProcess) main :: IO () main = readProcess git [describe, --tags] = putStr In Windows I get the following behaviour: git --version git version 1.7.10.msysgit.1 ghc --version The Glorious Glasgow

Re: [Haskell-cafe] createProcess fails to find executable in Windows

2012-10-25 Thread Jesse Schalken
What if you ran the program from within the directory that contains git.exe? Can you check that the PATH environment variable is set correctly from within the program? On Thu, Oct 25, 2012 at 10:05 PM, José Pedro Magalhães j...@cs.uu.nl wrote: Hi all, Consider the following program: module

Re: [Haskell-cafe] createProcess fails to find executable in Windows

2012-10-25 Thread José Pedro Magalhães
On Thu, Oct 25, 2012 at 12:10 PM, Jesse Schalken m...@jesseschalken.comwrote: What if you ran the program from within the directory that contains git.exe? That seems to work. Can you check that the PATH environment variable is set correctly from within the program? If I run `system

Re: [Haskell-cafe] Online haskell course

2012-10-25 Thread Joao H A Franco
There is also the Haskell course (21 videos) given by Philip Wadler (one or the creators of Haskell) at University of Edinburgh in 2011. The first video is available at http://www.youtube.com/watch?v=AOl2y5uW0mAfeature=relmfu . Course materials (lecture notes, exercises, solutions, references,

Re: [Haskell-cafe] Teaching Haskell @ MOOCs like Coursera or Udacity

2012-10-25 Thread niket
The closest available is: http://www.youtube.com/playlist?list=PL386777DEA831CB75feature=playlist-comment http://www.inf.ed.ac.uk/teaching/courses/inf1/fp/ Thanks, Niket On Thu, Oct 25, 2012 at 2:07 AM, David McBride toa...@gmail.com wrote: I'm taking it primarily because it is taught by the

[Haskell-cafe] Type-directed functions with data kinds

2012-10-25 Thread Paul Visschers
Hello everyone, I've been playing around with the data kinds extension to implement vectors that have a known length at compile time. Some simple code to illustrate: {-# LANGUAGE DataKinds, GADTs, KindSignatures #-} import Prelude hiding (repeat) data Nat = Zero | Succ Nat data Vector (n ::

Re: [Haskell-cafe] Type-directed functions with data kinds

2012-10-25 Thread Iavor Diatchki
Hello Paul, If you don't want to use the class system, you could write `repeat` with a type like this: repeat :: Proxy n - a - Vector n a (`Proxy` is the singleton family 'data Proxy n = Proxy`). You can't really do it with a function of type `a - Vector n a` because there is no way for

Re: [Haskell-cafe] Type-directed functions with data kinds

2012-10-25 Thread Andres Löh
Hi Iavor. If you don't want to use the class system, you could write `repeat` with a type like this: repeat :: Proxy n - a - Vector n a (`Proxy` is the singleton family 'data Proxy n = Proxy`). How is the polymorphism becoming any less parametric by using this particular Proxy type?

Re: [Haskell-cafe] Type-directed functions with data kinds

2012-10-25 Thread Iavor Diatchki
Hello, Sorry, I made a mistake, the version of 'repeat :: Proxy n - a - Vector n a' won't work either, as Andres noticed, because `Proxy` still won't give you information about how many times to repeat. You'd have to use a structured singleton family, where the values are linked to the types:

Re: [Haskell-cafe] Type-directed functions with data kinds

2012-10-25 Thread José Pedro Magalhães
Hi Paul, On Thu, Oct 25, 2012 at 4:22 PM, Paul Visschers m...@paulvisschers.netwrote: Hello everyone, I've been playing around with the data kinds extension to implement vectors that have a known length at compile time. Some simple code to illustrate: {-# LANGUAGE DataKinds, GADTs,

[Haskell-cafe] pragma to request tail recursion optimization (and perhaps [co]inductive recursion)

2012-10-25 Thread Petr P
Hi, Haskell compilers optimize tail recursive functions as cycles, which improves both memory and CPU complexity. However, it's easy to make a mistake and break the conditions under which a function can be tail recursive and thus optimized. Is there a way to tell a Haskell compiler that a

[Haskell-cafe] Building all possible element combinations from N lists.

2012-10-25 Thread dokondr
Hi all, I am looking for the algorithm and code better then the one I wrote (please see below) to solve the problem given in the subject. Unfortunately I finally need to implement this algorithm in Java. That's why I am not only interested in beautiful Haskell algorithms, but also in the one that

Re: [Haskell-cafe] Teaching Haskell @ MOOCs like Coursera or Udacity

2012-10-25 Thread Gregg Lebovitz
I am trying to get a learning center started in the Haskell community. As pointed out below, MOOCs are hard to put together, however training and videos straight forward. There is a lot of teaching material available in the community. It is a matter of finding,

Re: [Haskell-cafe] Teaching Haskell @ MOOCs like Coursera or Udacity

2012-10-25 Thread Kristopher Micinski
On Thu, Oct 25, 2012 at 4:57 PM, Gregg Lebovitz gr...@fpcomplete.com wrote: I am trying to get a learning center started in the Haskell community. As pointed out below, MOOCs are hard to put together, however training and videos straight forward. There is a lot of teaching material available in

Re: [Haskell-cafe] Building all possible element combinations from N lists.

2012-10-25 Thread Alex Stangl
On Fri, Oct 26, 2012 at 12:44:31AM +0400, dokondr wrote: I am looking for the algorithm and code better then the one I wrote (please Build all possible element combinations from N lists. Valid combination consists of k = N elements. Where each element of a single combination is taken from one

Re: [Haskell-cafe] Building all possible element combinations from N lists.

2012-10-25 Thread dokondr
On Fri, Oct 26, 2012 Alex Stangl wrote: * * combos [] = [[]] combos ([]:ls) = combos ls combos ((h:t):ls) = map (h:) (combos ls) ++ combos (t:ls) Excellent, thanks! ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Building all possible element combinations from N lists.

2012-10-25 Thread Jake McArthur
I golfed a bit. :) sequence = filterM (const [False ..]) On Thu, Oct 25, 2012 at 6:11 PM, dokondr doko...@gmail.com wrote: On Fri, Oct 26, 2012 Alex Stangl wrote: combos [] = [[]] combos ([]:ls) = combos ls combos ((h:t):ls) = map (h:) (combos ls) ++ combos (t:ls) Excellent,

[Haskell-cafe] Problems translating Conor McBride's talk into Haskell + DataKind + KindPoly

2012-10-25 Thread Ahn, Ki Yung
Most part of Conor's talk at ICFP, until just before the last stage where he heavily uses true value dependency for compiler correctness all the code seemed to be able to translate into Haskell with the new hot DataKinds and PolyKinds extension. I tried it in GHC 7.4.1 and it was possible to

Re: [Haskell-cafe] Teaching Haskell @ MOOCs like Coursera or Udacity

2012-10-25 Thread Gregg Lebovitz
I would love to see an awesome online learning experience for Haskell too. We really need to make it easier for people to learn Haskell. Thank you for pointing this out to the community. On 10/18/2012 2:19 PM, niket wrote: I am a novice in Haskell

Re: [Haskell-cafe] Problems translating Conor McBride's talk into Haskell + DataKind + KindPoly

2012-10-25 Thread Ahn, Ki Yung
Promotion works for user defined lists such as data List a = Nil | Cons a (List a) And, if I use (List Bool) instead of [Bool] everything works out. It's only the Haskell list type constructor [] is being a problem. In the Giving Haskell a promotion paper, it says that Haskell lists are

Re: [Haskell-cafe] Building all possible element combinations from N lists.

2012-10-25 Thread Alex Stangl
On Thu, Oct 25, 2012 at 06:34:53PM -0400, Jake McArthur wrote: I golfed a bit. :) sequence = filterM (const [False ..]) I was thinking of golfing this myself tonight, but probably wouldn't have come up with this. Thanks for sparing me the effort. Bravo! Alex