[EMAIL PROTECTED] writes:
>
> Let us consider the following simple code
>
> > {-# OPTIONS -fglasgow-exts #-}
> >
> > module Foo where
> >
> > data Term a where
> >B:: Bool -> Term Bool
> >C:: Term Bool -> Term t -> Term t
> >I:: Int -> Term Int
> >
> > shw (I t) = ("I "+
Let us consider the following simple code
> {-# OPTIONS -fglasgow-exts #-}
>
> module Foo where
>
> data Term a where
>B:: Bool -> Term Bool
>C:: Term Bool -> Term t -> Term t
>I:: Int -> Term Int
>
> shw (I t) = ("I "++) . shows t
> shw (B t) = ("B "++) . shows t
> shw (
Louis-Julien Guillemette wrote:
> Say we are using a GADT to represent a simple language of boolean
> constants and conditionals,
>
> data Term a where
>B:: Bool -> Term Bool
>Cnd :: Term Bool -> Term t -> Term t -> Term t
>
> and we would like to perform a type-safe CPS conversion ov
Louis-Julien Guillemette <[EMAIL PROTECTED]> wrote:
> Say we are using a GADT to represent a simple language of boolean
> constants and conditionals,
>
> data Term a where
>B:: Bool -> Term Bool
>Cnd :: Term Bool -> Term t -> Term t -> Term t
>
> and we would like to perfo
I've just run across a problem with my cabal build system -- I'm not yet sure
if this is a cabal problem or a system configuration problem.
I've been developing a package on OSX using the ghc 6.4.1 and cabal from
darwinports. All is fine and dandy. However, today I've sucked my darcs
repo dow
Say we are using a GADT to represent a simple language of boolean
constants and conditionals,
data Term a where
B:: Bool -> Term Bool
Cnd :: Term Bool -> Term t -> Term t -> Term t
and we would like to perform a type-safe CPS conversion over this language. We
encode the relationship
Hooray!! Thanks John
jgoerzen:
> Hello everyone,
>
> Finally! Simon Marlow's plan[1] for moving from CVS to darcs for
> fptools, GHC, etc. is happening. Thanks to some feedback from him and
> the author of Tailor, as well as some free time finally, I've been
> able to convert things from CVS to
Hello everyone,
Finally! Simon Marlow's plan[1] for moving from CVS to darcs for
fptools, GHC, etc. is happening. Thanks to some feedback from him and
the author of Tailor, as well as some free time finally, I've been
able to convert things from CVS to darcs according to the plan.
So, the first
On 2005-11-24, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote:
> petersen:
>> Donald Bruce Stewart wrote:
>> > hmp3 is a lightweight ncurses-based mp3 player written in Haskell. It
>> > uses mpg321 or mpg123 as its decoding backend. It is designed to be
>> > simple, fast and robust.
>>
>> Cool, th