[Haskell-cafe] translation between two flavors of lexically-scoped type variables

2012-07-05 Thread Kangyuan Niu
The paper Lexically scoped type variables by Simon Peyton Jones and Mark
Shields describes two ways to give type variables lexical scoping. They
state that one of the advantages of the GHC-style type-sharing approach
over the SML-style type-lambda approach is that the former allows for
existential quantification in addition to universal quantification. As an
example, they give this code:

data Ap = forall a. Ap [a] ([a] - Int)

The constructor `Ap` has the type:

Ap :: forall a. [a] - ([a] - Int) - Ap

And one can write a function:

revap :: Ap - Int
revap (Ap (xs :: [a]) f) = f ys
  where
ys :: [a]
ys = reverse xs

with the annotations on `xs` and `ys` being existential instead of
universal.

But I'm a little confused about *why* type-lambdas don't allow this. Aren't
both Haskell and SML translatable into System F, from which type-lambda is
directly taken? What does the translation for the above code even look
like? Why isn't it possible to write something like:

fun 'a revap (Ap (xs : 'a list) f) = f ys
  where
ys :: 'a list
ys = reverse xs

in SML?

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


Re: [Haskell-cafe] Using syntactic to implement the lambda calculus

2012-07-05 Thread Emil Axelsson

Hi Alex!

2012-07-03 20:18, Alex Rozenshteyn skrev:

I'm trying to implement the lambda calculus (with CBV evaluation) using
the syntactic package, in such a way that a simple extension is also
simple to implement.

I am stuck on the fact that it seems that the Value type needs to be
parametrized over the Expr type and I can't seem to figure out how to do it.


The trick is to see that your `Expr` and `Value` can be merged to a 
single type:


  data Expr group
where
  Var :: Ident - Expr NONVAL
  Lam :: Ident - Expr any - Expr VAL
  App :: Expr any1 - Expr any2 - Expr NONVAL

  data VAL
  data NONVAL

  type Value = Expr VAL

  eval :: Expr any - Value
  ...

(Here I'm using polymorphic constructors to emulate that `Value` is a 
sub-type of `Expr`. I could have made a more direct translation with two 
lambda constructors. Then all constructors would have been monomorphic.)


Once this is done, the conversion to Syntactic is easy:

  data Var :: * - * where Var :: Ident - Var (Full NONVAL)
  data Lam :: * - * where Lam :: Ident - Lam (any :- Full VAL)
  data App :: * - * where App :: App (any1 :- any2 :- Full NONVAL)

  type Expr group = ASTF (Lam :+: Var :+: App) group
  type Value  = ASTF (Lam :+: Var :+: App) VAL

  eval :: Expr any - Value
  eval var
  | Just (Var _) - prj var = error not closed
  eval e@(lam :$ _)
  | Just (Lam _) - prj lam = e
  eval (app :$ e1 :$ e2)
  | Just App - prj app = case eval e1 of
  (lam :$ e) | Just (Lam i) - prj lam   - subst e (eval e2) i
  _ - error illegal application

  subst :: Expr any - Value - Ident - Value
  subst = undefined

Of course, you need to generalize the types of `eval` and `subst` in 
order to make them extensible. For more details, see this paper:


  http://www.cse.chalmers.se/~emax/documents/axelsson2012generic.pdf

(The paper refers to syntactic-1.0 which hasn't been uploaded yet, so 
there are some small differences.)


/ Emil


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


[Haskell-cafe] Is haskell.org down?

2012-07-05 Thread C K Kashyap
Regards,
Kashyap
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is haskell.org down?

2012-07-05 Thread Ivan Lazar Miljenovic
Not anymore!

On 5 July 2012 15:13, C K Kashyap ckkash...@gmail.com wrote:
 Regards,
 Kashyap

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




-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
http://IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] existential types and cast

2012-07-05 Thread Paolino
Hi Corentin,
This is how I would model your request (without concrete constructors for
Player and Rule)
I'm sure there are better descriptions also  as I'm not an expert.

paolino

{-# LANGUAGE DataKinds, GADTs, KindSignatures #-}

data Player
data Rule

data Data = Player | Rule
data EventKind  = Action | Reaction

data Event :: EventKind - * where
  NewPlayer  :: Player - Event Action
  NewRule:: Rule - Event Action
  NewHandler :: (Event Action - IO ()) - Event Reaction

handle ::  Event Action - Event Reaction - IO ()
handle x (NewHandler f) = f x

reaction :: Event a - [Event Reaction] - IO [Event Reaction]

reaction f@(NewHandler _) es = return $ f:es
reaction p@(NewPlayer _) es = mapM_ (handle p) es  return es
reaction r@(NewRule _) es = mapM_ (handle r) es  return es

2012/7/4 Corentin Dupont corentin.dup...@gmail.com

 Hi,
 for example, in my game (Nomic) if a new player arrives, I trigger a
 NewPlayer event. All handlers registered for that event should be
 triggered, and passed a structure Player containing all the infos of the
 incoming player.
 If there is a new rule submitted, that the same: the event NewRule is
 triggered and the handlers are passed a structure Rule. Thus I want the
 handlers registered on NewPlayer to have the type Player - xxx, and on
 NewRule to have the type Rule - xxx. I want to be able to associate an
 arbitrary data type (here Player and Rule) to an event.
 The handlers are inherently of different types, but I want to store them
 in a unique list hence the existential...


 On Wed, Jul 4, 2012 at 4:33 PM, Paolino paolo.verone...@gmail.com wrote:

 Hi Corentin,
 If you could explain *why* there should be a type associated to each
 event value, it would help, maybe.
 If it's a design choice , maybe it's wrong design. One reason to use
 dynamic typing would be to plug  in new type of events. But if you already
 have the events semantics , this is not useful.
 If the language of events is complex , possibly recursive, you can use
 GADTs to enforce their validity by construction and you don't need to
 typefy the event values, but some of their characteristics.
 Remember type machinery is good to give correctness at the compilation
 time which Typeable defeats moving checks at runtime. So lifting values to
 types and eliminating this information with existentials and casting seems
 wrong.

 paolino

 2012/7/4 Corentin Dupont corentin.dup...@gmail.com

  Hi Paolino,
 the user can add as many handlers he wants for each event.
 When a event is triggered along with a data, all handlers associated to
 that event should be triggered and passed the data.
 The trick is, there is one type of data associated with each event.
 That's why I cannot use a Event datatype: how to associate a data type to
 each event value? This would be some sort of dependant typing if I'm not
 mistaken.
 That's why my events exists both on type level and value level:
 *data NewPlayer = NewPlayer
 *
 wich allows me to associate it a typf data with type indexing.*..
 *

 Regards
 Corentin


 On Wed, Jul 4, 2012 at 12:58 PM, Paolino paolo.verone...@gmail.comwrote:

 Hi
 How many handlers for each type of event in the list of handlers ?
 If you have only one handler for each type , it should go in the
 typeclass, and you don't need typeable.
 If you have more than one maybe you can avoid using type indexing at
 all, because it doesn't resolve the handler selection issue.
 By the way , it's not clear to me why you don't have a simple Event
 datatype describing all the possible events in advance.

 Regards

 paolino

 2012/7/3 Corentin Dupont corentin.dup...@gmail.com

 Hi all,
 I read somewhere (here:
 http://stackoverflow.com/questions/2300275/how-to-unpack-a-haskell-existential-type)
 that it's bad to try to unbox an existential type using a cast. OK, but
 without I really can't figure out how to do what I want:

 *data NewPlayer = NewPlayer deriving (Typeable, Eq)
 data NewRule = NewRule deriving (Typeable, Eq)

 class (Eq e, Typeable e) = Event e where
 data EventData e

 instance Event NewPlayer where
 data EventData NewPlayer = P Int

 instance Event NewRule where
 data EventData NewRule = R Int

 instance Typeable1 EventData where
 typeOf1 _ = mkTyConApp (mkTyCon EventData) []

 data EventHandler = forall e . (Event e) = EH e (EventData e - IO ())

 addEvent :: (Event e) = e - (EventData e - IO ()) - [EventHandler]
 - [EventHandler]
 addEvent e h ehs = (EH e h):ehs

 triggerEvent :: (Event e) = e - (EventData e) - [EventHandler] -
 IO ()
 triggerEvent e d ehs = do
 let r = find (\(EH myEvent _) - cast e == Just myEvent) ehs
 case r of
Nothing - return ()
Just (EH _ h) - case cast h of
 Just castedH - castedH d
 Nothing - return ()*

 How to remove the casts from triggerEvent? All that I want is to apply
 the handler found on the data passed in parameter.
 I tried to add a function apply in the class, without success:
 *apply :: (EventData e - 

Re: [Haskell-cafe] existential types and cast

2012-07-05 Thread Paolino
Sorry, drop the data Data  line, I was experimenting with a deeper
description.

paolino

2012/7/4 Paolino paolo.verone...@gmail.com

 Hi Corentin,
 This is how I would model your request (without concrete constructors for
 Player and Rule)
 I'm sure there are better descriptions also  as I'm not an expert.

 paolino

 {-# LANGUAGE DataKinds, GADTs, KindSignatures #-}

 data Player
 data Rule

 data Data = Player | Rule
 data EventKind  = Action | Reaction

 data Event :: EventKind - * where
   NewPlayer  :: Player - Event Action
   NewRule:: Rule - Event Action
   NewHandler :: (Event Action - IO ()) - Event Reaction

 handle ::  Event Action - Event Reaction - IO ()
 handle x (NewHandler f) = f x

 reaction :: Event a - [Event Reaction] - IO [Event Reaction]

 reaction f@(NewHandler _) es = return $ f:es
 reaction p@(NewPlayer _) es = mapM_ (handle p) es  return es
 reaction r@(NewRule _) es = mapM_ (handle r) es  return es


 2012/7/4 Corentin Dupont corentin.dup...@gmail.com

 Hi,
 for example, in my game (Nomic) if a new player arrives, I trigger a
 NewPlayer event. All handlers registered for that event should be
 triggered, and passed a structure Player containing all the infos of the
 incoming player.
 If there is a new rule submitted, that the same: the event NewRule is
 triggered and the handlers are passed a structure Rule. Thus I want the
 handlers registered on NewPlayer to have the type Player - xxx, and on
 NewRule to have the type Rule - xxx. I want to be able to associate an
 arbitrary data type (here Player and Rule) to an event.
 The handlers are inherently of different types, but I want to store them
 in a unique list hence the existential...


 On Wed, Jul 4, 2012 at 4:33 PM, Paolino paolo.verone...@gmail.comwrote:

 Hi Corentin,
 If you could explain *why* there should be a type associated to each
 event value, it would help, maybe.
 If it's a design choice , maybe it's wrong design. One reason to use
 dynamic typing would be to plug  in new type of events. But if you already
 have the events semantics , this is not useful.
 If the language of events is complex , possibly recursive, you can use
 GADTs to enforce their validity by construction and you don't need to
 typefy the event values, but some of their characteristics.
 Remember type machinery is good to give correctness at the compilation
 time which Typeable defeats moving checks at runtime. So lifting values to
 types and eliminating this information with existentials and casting seems
 wrong.

 paolino

 2012/7/4 Corentin Dupont corentin.dup...@gmail.com

  Hi Paolino,
 the user can add as many handlers he wants for each event.
 When a event is triggered along with a data, all handlers associated to
 that event should be triggered and passed the data.
 The trick is, there is one type of data associated with each event.
 That's why I cannot use a Event datatype: how to associate a data type to
 each event value? This would be some sort of dependant typing if I'm not
 mistaken.
 That's why my events exists both on type level and value level:
 *data NewPlayer = NewPlayer
 *
 wich allows me to associate it a typf data with type indexing.*..
 *

 Regards
 Corentin


 On Wed, Jul 4, 2012 at 12:58 PM, Paolino paolo.verone...@gmail.comwrote:

 Hi
 How many handlers for each type of event in the list of handlers ?
 If you have only one handler for each type , it should go in the
 typeclass, and you don't need typeable.
 If you have more than one maybe you can avoid using type indexing at
 all, because it doesn't resolve the handler selection issue.
 By the way , it's not clear to me why you don't have a simple Event
 datatype describing all the possible events in advance.

 Regards

 paolino

 2012/7/3 Corentin Dupont corentin.dup...@gmail.com

 Hi all,
 I read somewhere (here:
 http://stackoverflow.com/questions/2300275/how-to-unpack-a-haskell-existential-type)
 that it's bad to try to unbox an existential type using a cast. OK, but
 without I really can't figure out how to do what I want:

 *data NewPlayer = NewPlayer deriving (Typeable, Eq)
 data NewRule = NewRule deriving (Typeable, Eq)

 class (Eq e, Typeable e) = Event e where
 data EventData e

 instance Event NewPlayer where
 data EventData NewPlayer = P Int

 instance Event NewRule where
 data EventData NewRule = R Int

 instance Typeable1 EventData where
 typeOf1 _ = mkTyConApp (mkTyCon EventData) []

 data EventHandler = forall e . (Event e) = EH e (EventData e - IO
 ())

 addEvent :: (Event e) = e - (EventData e - IO ()) -
 [EventHandler] - [EventHandler]
 addEvent e h ehs = (EH e h):ehs

 triggerEvent :: (Event e) = e - (EventData e) - [EventHandler] -
 IO ()
 triggerEvent e d ehs = do
 let r = find (\(EH myEvent _) - cast e == Just myEvent) ehs
 case r of
Nothing - return ()
Just (EH _ h) - case cast h of
 Just castedH - castedH d
 Nothing - return ()*

 How to remove the casts from triggerEvent? All that I 

Re: [Haskell-cafe] Martin Odersky on What's wrong with Monads

2012-07-05 Thread Facundo Domínguez
 That precedent supports the view that e.g. a command-line flag
 shouldn't affect behavior without the type reflecting it, e.g. by
 doing IO, but the de facto use of the unsafe IO trick means not
 everyone agrees.

For those interested, here's [1] a case where treating command line
arguments as top level constants went wrong.
Look specifically at the section named Crime Doesn't Pay.

Best,
Facundo

[1] http://www.aosabook.org/en/ghc.html


 Date: Tue, 3 Jul 2012 17:49:48 -0400
 From: Alvaro Gutierrez radi...@google.com
 Subject: Re: [Haskell-cafe] Martin Odersky on What's wrong with
 Monads
 To: Dominique Devriese dominique.devri...@cs.kuleuven.be
 Cc: haskell-cafe@haskell.org
 Message-ID:
 cac6k+tpuidrtac_ccfa9ewawdpg1adaht96rgmc_s5wtvjw...@mail.gmail.com
 Content-Type: text/plain; charset=ISO-8859-1

 On Thu, Jun 28, 2012 at 2:53 PM, Dominique Devriese
 dominique.devri...@cs.kuleuven.be wrote:
 2012/6/27 Tillmann Rendel ren...@informatik.uni-marburg.de:
 How would you implement this requirement in Haskell without changing the
 line amount (Leaf x) = x?

 I may be missing the point here, but having worked on large code bases
 with a wide variety contributors before, I find it very advantageous
 that programmers are prevented from writing an amount function whose
 behaviour depends on command line arguments without at least an
 indication in the type. The fact that the function can not perform
 stuff like that is precisely the guarantee that the Haskell type gives
 me...

 I don't think there's an answer that's uniformly right; it depends on
 whether you think of the input to the program, e.g. the environment,
 command-line arguments, etc. as 'constant' and in some sense, pure.
 The latter are constant in the sense that they never change, but they
 are not fixed at compile-time. Other languages effectively treat them
 as pure (by passing them directly to main), whereas Haskell chooses
 not to, which is probably the reason why getArgs has IO in its type
 (something that seems unintuitive at first.)

 That precedent supports the view that e.g. a command-line flag
 shouldn't affect behavior without the type reflecting it, e.g. by
 doing IO, but the de facto use of the unsafe IO trick means not
 everyone agrees.


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


Re: [Haskell-cafe] existential types and cast

2012-07-05 Thread Corentin Dupont
Hi Paolino,
the user can add as many handlers he wants for each event.
When a event is triggered along with a data, all handlers associated to
that event should be triggered and passed the data.
The trick is, there is one type of data associated with each event. That's
why I cannot use a Event datatype: how to associate a data type to each
event value? This would be some sort of dependant typing if I'm not
mistaken.
That's why my events exists both on type level and value level:
*data NewPlayer = NewPlayer
*wich allows me to associate it a type of data with type indexing.*..
*
Regards
Corentin

On Wed, Jul 4, 2012 at 12:58 PM, Paolino paolo.verone...@gmail.com wrote:

 Hi
 How many handlers for each type of event in the list of handlers ?
 If you have only one handler for each type , it should go in the
 typeclass, and you don't need typeable.
 If you have more than one maybe you can avoid using type indexing at all,
 because it doesn't resolve the handler selection issue.
 By the way , it's not clear to me why you don't have a simple Event
 datatype describing all the possible events in advance.

 Regards

 paolino

 2012/7/3 Corentin Dupont corentin.dup...@gmail.com

 Hi all,
 I read somewhere (here:
 http://stackoverflow.com/questions/2300275/how-to-unpack-a-haskell-existential-type)
 that it's bad to try to unbox an existential type using a cast. OK, but
 without I really can't figure out how to do what I want:

 *data NewPlayer = NewPlayer deriving (Typeable, Eq)
 data NewRule = NewRule deriving (Typeable, Eq)

 class (Eq e, Typeable e) = Event e where
 data EventData e

 instance Event NewPlayer where
 data EventData NewPlayer = P Int

 instance Event NewRule where
 data EventData NewRule = R Int

 instance Typeable1 EventData where
 typeOf1 _ = mkTyConApp (mkTyCon EventData) []

 data EventHandler = forall e . (Event e) = EH e (EventData e - IO ())

 addEvent :: (Event e) = e - (EventData e - IO ()) - [EventHandler] -
 [EventHandler]
 addEvent e h ehs = (EH e h):ehs

 triggerEvent :: (Event e) = e - (EventData e) - [EventHandler] - IO ()
 triggerEvent e d ehs = do
 let r = find (\(EH myEvent _) - cast e == Just myEvent) ehs
 case r of
Nothing - return ()
Just (EH _ h) - case cast h of
 Just castedH - castedH d
 Nothing - return ()*

 How to remove the casts from triggerEvent? All that I want is to apply
 the handler found on the data passed in parameter.
 I tried to add a function apply in the class, without success:
 *apply :: (EventData e - IO ()) - (EventData e) - IO ()
 apply = ($)*


 Thanks!
 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] Inferring Safety

2012-07-05 Thread Joachim Breitner
Hi,

Am Mittwoch, den 04.07.2012, 21:10 +1000 schrieb Ivan Lazar Miljenovic:
 So what's going on here?

you are likely hit by
http://hackage.haskell.org/trac/ghc/ticket/5989

Greetings,
Joachim

-- 
Joachim nomeata Breitner
  m...@joachim-breitner.de  |  nome...@debian.org  |  GPG: 0x4743206C
  xmpp: nome...@joachim-breitner.de | http://www.joachim-breitner.de/



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Martin Odersky on What's wrong with Monads

2012-07-05 Thread Tom Murphy
In practice, the amount of time you have to spend testing each function, to
make sure its IO doesn't trip up in some corner case, is usually greater
than the amount of time a rewrite-for-IO would take.

Tom
On Jun 28, 2012 2:54 PM, Dominique Devriese 
dominique.devri...@cs.kuleuven.be wrote:

 2012/6/27 Tillmann Rendel ren...@informatik.uni-marburg.de:
  MightyByte wrote:
 
  Of course every line of your program that uses a Foo will change if you
  switch
  to IO Foo instead.
 
 
  But we often have to also change lines that don't use Foo at all. For
  example, here is the type of binary trees of integers:
 
   data Tree = Leaf Integer | Branch (Tree Integer) (Tree Integer)
 
  A function to add up all integers in a tree:
 
   amount:: Tree - Integer
   amount (Leaf x) = x
   amount (Branch t1 t2) = amountt1 + amountt2
 
  All fine so far. Now, consider the following additional requirement: If
 the
  command-line flag --multiply is set, the function amount computes the
  product instead of the sum.
 
  In a language with implicit side effects, it is easy to implement this.
 We
  just change the third line of the amount function to check whether to
 call
  (+) or (*). In particular, we would not touch the other two lines.
 
  How would you implement this requirement in Haskell without changing the
  line amount (Leaf x) = x?

 I may be missing the point here, but having worked on large code bases
 with a wide variety contributors before, I find it very advantageous
 that programmers are prevented from writing an amount function whose
 behaviour depends on command line arguments without at least an
 indication in the type. The fact that the function can not perform
 stuff like that is precisely the guarantee that the Haskell type gives
 me...

 Dominique

 ___
 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] Inferring Safety

2012-07-05 Thread Ivan Lazar Miljenovic
On 5 July 2012 01:35, Joachim Breitner m...@joachim-breitner.de wrote:
 Hi,

 Am Mittwoch, den 04.07.2012, 21:10 +1000 schrieb Ivan Lazar Miljenovic:
 So what's going on here?

 you are likely hit by
 http://hackage.haskell.org/trac/ghc/ticket/5989

Ahhh, that looks like it; thanks Joachim.


 Greetings,
 Joachim

 --
 Joachim nomeata Breitner
   m...@joachim-breitner.de  |  nome...@debian.org  |  GPG: 0x4743206C
   xmpp: nome...@joachim-breitner.de | http://www.joachim-breitner.de/


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




-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
http://IvanMiljenovic.wordpress.com

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


[Haskell-cafe] Cabal problem re. haskelldb-hdbc-mysql

2012-07-05 Thread Yves Parès
Hi,
the package http://hackage.haskell.org/package/haskelldb-hdbc-mysql/ the
use of HDBC 2.3.0
I'm using cabal-install 0.14, and with a fresh install (no packages already
installed), cabal-install tries to install HDBC-2.1.1 instead of, say,
HDBC-2.2.7.0.

The problem is that HDBC-2.1.1 is old (2009) and does not compile.

When I download haskelldb-hdbc-mysql manually, change the dependency and
then install, it compiles fine.

Is the dependency ill-declared, or is that a cabal problem?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] HUnit/cabal integration

2012-07-05 Thread Richard Cobbe
I'm working on a little library package (purely for my own consumption)
that's built with Cabal, and I have a couple of questions about the
pragmatics of using HUnit for it.

First, I'd like to be able to run my tests via cabal test from the shell
prompt.  I've seen
http://hackage.haskell.org/trac/hackage/wiki/UpgradingTests and followed
that, and it basically works.  I'm curious if I'm doing it in the best (or
at least most idiomatic) way.  I've included my cabal file and test driver
below, for specifics.

Two questions:

First: the web page I cite above describes the interface that the test
binary must support to work with cabal, specifically w.r.t. the binary's
exit code.  Your test suites likely already fit this model.  However, if
you are using an old version of QuickCheck or HUnit, your executable may
not be returning the correct error code.

This seems to me to suggest that recent versions of HUnit automatically
take care of generating the exit code, but I've found that I have to
examine HUnit's results and synthesize the exit code manually, as in the
driver program below.  (I'm running HUnit 1.2.4.2, but the interface for
1.2.4.3 doesn't appear to differ on this point.)  Am I misinterpreting the
wiki page, or am I missing something in HUnit's API that generates the exit
code automatically?

Second: Am I specifying the Build-Depends correctly for the Test-Suite?
Specifically: do I need to state a dependency on the library defined in the
same package, or does it pick that up automatically?  Further, foo-tests
doesn't use parsec directly.  Is the transitive dependency automatically
provided for me, or do I need to list it explicitly as below?

Thanks much,

Richard

My cabal file:

Name:   foo
Version:0.0
Cabal-Version:  = 1.2
Author: Richard Cobbe
Synopsis:   Sample cabal package for HUnit integration
Build-Type: Simple

Library
  Exposed-Modules:
Foo,
Foo.Parser,
Foo.Show
  Build-Depends:
base = 4.3.1.0   5,
parsec = 3.1.2

Test-Suite foo-tests
  main-is: foo-tests.hs
  type: exitcode-stdio-1.0
  Build-Depends:
base = 4.3.1.0   5,
parsec = 3.1.2,
HUnit = 1.2.4.2

and foo-tests.hs:

module Main where

import Test.HUnit
import qualified Foo.Parser
import System.Exit

main :: IO ()
main =
  do c - runTestTT (Foo ~: Foo.Parser.tests)
 if (errors c == 0  failures c == 0)
   then exitWith ExitSuccess
   else exitWith (ExitFailure (-1))


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


Re: [Haskell-cafe] existential types and cast

2012-07-05 Thread Paolino
Hi Corentin,
If you could explain *why* there should be a type associated to each event
value, it would help, maybe.
If it's a design choice , maybe it's wrong design. One reason to use
dynamic typing would be to plug  in new type of events. But if you already
have the events semantics , this is not useful.
If the language of events is complex , possibly recursive, you can use
GADTs to enforce their validity by construction and you don't need to
typefy the event values, but some of their characteristics.
Remember type machinery is good to give correctness at the compilation time
which Typeable defeats moving checks at runtime. So lifting values to types
and eliminating this information with existentials and casting seems wrong.

paolino

2012/7/4 Corentin Dupont corentin.dup...@gmail.com

 Hi Paolino,
 the user can add as many handlers he wants for each event.
 When a event is triggered along with a data, all handlers associated to
 that event should be triggered and passed the data.
 The trick is, there is one type of data associated with each event. That's
 why I cannot use a Event datatype: how to associate a data type to each
 event value? This would be some sort of dependant typing if I'm not
 mistaken.
 That's why my events exists both on type level and value level:
 *data NewPlayer = NewPlayer
 *wich allows me to associate it a typf data with type indexing.*..
 *
 Regards
 Corentin


 On Wed, Jul 4, 2012 at 12:58 PM, Paolino paolo.verone...@gmail.comwrote:

 Hi
 How many handlers for each type of event in the list of handlers ?
 If you have only one handler for each type , it should go in the
 typeclass, and you don't need typeable.
 If you have more than one maybe you can avoid using type indexing at all,
 because it doesn't resolve the handler selection issue.
 By the way , it's not clear to me why you don't have a simple Event
 datatype describing all the possible events in advance.

 Regards

 paolino

 2012/7/3 Corentin Dupont corentin.dup...@gmail.com

 Hi all,
 I read somewhere (here:
 http://stackoverflow.com/questions/2300275/how-to-unpack-a-haskell-existential-type)
 that it's bad to try to unbox an existential type using a cast. OK, but
 without I really can't figure out how to do what I want:

 *data NewPlayer = NewPlayer deriving (Typeable, Eq)
 data NewRule = NewRule deriving (Typeable, Eq)

 class (Eq e, Typeable e) = Event e where
 data EventData e

 instance Event NewPlayer where
 data EventData NewPlayer = P Int

 instance Event NewRule where
 data EventData NewRule = R Int

 instance Typeable1 EventData where
 typeOf1 _ = mkTyConApp (mkTyCon EventData) []

 data EventHandler = forall e . (Event e) = EH e (EventData e - IO ())

 addEvent :: (Event e) = e - (EventData e - IO ()) - [EventHandler]
 - [EventHandler]
 addEvent e h ehs = (EH e h):ehs

 triggerEvent :: (Event e) = e - (EventData e) - [EventHandler] - IO
 ()
 triggerEvent e d ehs = do
 let r = find (\(EH myEvent _) - cast e == Just myEvent) ehs
 case r of
Nothing - return ()
Just (EH _ h) - case cast h of
 Just castedH - castedH d
 Nothing - return ()*

 How to remove the casts from triggerEvent? All that I want is to apply
 the handler found on the data passed in parameter.
 I tried to add a function apply in the class, without success:
 *apply :: (EventData e - IO ()) - (EventData e) - IO ()
 apply = ($)*


 Thanks!
 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] existential types and cast

2012-07-05 Thread Corentin Dupont
Thanks Paolino, I will try to see how I can use your implementation!
Corentin

On Wed, Jul 4, 2012 at 9:24 PM, Paolino
paowolo.verone...@gmail.compaolo.verone...@gmail.com
 wrote:

 Hi Corentin,
 This is how I would model your request (without concrete constructors for
 Player and Rule)
 I'm sure there are better descriptions also  as I'm not an expert.

 paolino

 {-# LANGUAGE DataKinds, GADTs, KindSignatures #-}

 data Player
 data Rule

 data Data = Player | Rule
 data EventKind  = Action | Reaction

 data Event :: EventKind - * where
   NewPlayer  :: Player - Event Action
   NewRule:: Rule - Event Action
   NewHandler :: (Event Action - IO ()) - Event Reaction

 handle ::  Event Action - Event Reaction - IO ()
 handle x (NewHandler f) = f x

 reaction :: Event a - [Event Reaction] - IO [Event Reaction]

 reaction f@(NewHandler _) es = return $ f:es
 reaction p@(NewPlayer _) es = mapM_ (handle p) es  return es
 reaction r@(NewRule _) es = mapM_ (handle r) es  return es


 2012/7/4 Corentin Dupont corentin.dup...@gmail.com

 Hi,
 for example, in my game (Nomic) if a new player arrives, I trigger a
 NewPlayer event. All handlers registered for that event should be
 triggered, and passed a structure Player containing all the infos of the
 incoming player.
 If there is a new rule submitted, that the same: the event NewRule is
 triggered and the handlers are passed a structure Rule. Thus I want the
 handlers registered on NewPlayer to have the type Player - xxx, and on
 NewRule to have the type Rule - xxx. I want to be able to associate an
 arbitrary data type (here Player and Rule) to an event.
 The handlers are inherently of different types, but I want to store them
 in a unique list hence the existential...


 On Wed, Jul 4, 2012 at 4:33 PM, Paolino paolo.verone...@gmail.comwrote:

 Hi Corentin,
 If you could explain *why* there should be a type associated to each
 event value, it would help, maybe.
 If it's a design choice , maybe it's wrong design. One reason to use
 dynamic typing would be to plug  in new type of events. But if you already
 have the events semantics , this is not useful.
 If the language of events is complex , possibly recursive, you can use
 GADTs to enforce their validity by construction and you don't need to
 typefy the event values, but some of their characteristics.
 Remember type machinery is good to give correctness at the compilation
 time which Typeable defeats moving checks at runtime. So lifting values to
 types and eliminating this information with existentials and casting seems
 wrong.

 paolino

 2012/7/4 Corentin Dupont corentin.dup...@gmail.com

  Hi Paolino,
 the user can add as many handlers he wants for each event.
 When a event is triggered along with a data, all handlers associated to
 that event should be triggered and passed the data.
 The trick is, there is one type of data associated with each event.
 That's why I cannot use a Event datatype: how to associate a data type to
 each event value? This would be some sort of dependant typing if I'm not
 mistaken.
 That's why my events exists both on type level and value level:
 *data NewPlayer = NewPlayer
 *
 wich allows me to associate it a typf data with type indexing.*..
 *

 Regards
 Corentin


 On Wed, Jul 4, 2012 at 12:58 PM, Paolino paolo.verone...@gmail.comwrote:

 Hi
 How many handlers for each type of event in the list of handlers ?
 If you have only one handler for each type , it should go in the
 typeclass, and you don't need typeable.
 If you have more than one maybe you can avoid using type indexing at
 all, because it doesn't resolve the handler selection issue.
 By the way , it's not clear to me why you don't have a simple Event
 datatype describing all the possible events in advance.

 Regards

 paolino

 2012/7/3 Corentin Dupont corentin.dup...@gmail.com

 Hi all,
 I read somewhere (here:
 http://stackoverflow.com/questions/2300275/how-to-unpack-a-haskell-existential-type)
 that it's bad to try to unbox an existential type using a cast. OK, but
 without I really can't figure out how to do what I want:

 *data NewPlayer = NewPlayer deriving (Typeable, Eq)
 data NewRule = NewRule deriving (Typeable, Eq)

 class (Eq e, Typeable e) = Event e where
 data EventData e

 instance Event NewPlayer where
 data EventData NewPlayer = P Int

 instance Event NewRule where
 data EventData NewRule = R Int

 instance Typeable1 EventData where
 typeOf1 _ = mkTyConApp (mkTyCon EventData) []

 data EventHandler = forall e . (Event e) = EH e (EventData e - IO
 ())

 addEvent :: (Event e) = e - (EventData e - IO ()) -
 [EventHandler] - [EventHandler]
 addEvent e h ehs = (EH e h):ehs

 triggerEvent :: (Event e) = e - (EventData e) - [EventHandler] -
 IO ()
 triggerEvent e d ehs = do
 let r = find (\(EH myEvent _) - cast e == Just myEvent) ehs
 case r of
Nothing - return ()
Just (EH _ h) - case cast h of
 Just castedH - castedH d
 Nothing - return ()*

 How to 

Re: [Haskell-cafe] existential types and cast

2012-07-05 Thread Corentin Dupont
Hi,
for example, in my game (Nomic) if a new player arrives, I trigger a
NewPlayer event. All handlers registered for that event should be
triggered, and passed a structure Player containing all the infos of the
incoming player.
If there is a new rule submitted, that the same: the event NewRule is
triggered and the handlers are passed a structure Rule. Thus I want the
handlers registered on NewPlayer to have the type Player - xxx, and on
NewRule to have the type Rule - xxx. I want to be able to associate an
arbitrary data type (here Player and Rule) to an event.
The handlers are inherently of different types, but I want to store them in
a unique list hence the existential...

On Wed, Jul 4, 2012 at 4:33 PM, Paolino paolo.verone...@gmail.com wrote:

 Hi Corentin,
 If you could explain *why* there should be a type associated to each event
 value, it would help, maybe.
 If it's a design choice , maybe it's wrong design. One reason to use
 dynamic typing would be to plug  in new type of events. But if you already
 have the events semantics , this is not useful.
 If the language of events is complex , possibly recursive, you can use
 GADTs to enforce their validity by construction and you don't need to
 typefy the event values, but some of their characteristics.
 Remember type machinery is good to give correctness at the compilation
 time which Typeable defeats moving checks at runtime. So lifting values to
 types and eliminating this information with existentials and casting seems
 wrong.

 paolino

 2012/7/4 Corentin Dupont corentin.dup...@gmail.com

 Hi Paolino,
 the user can add as many handlers he wants for each event.
 When a event is triggered along with a data, all handlers associated to
 that event should be triggered and passed the data.
 The trick is, there is one type of data associated with each event.
 That's why I cannot use a Event datatype: how to associate a data type to
 each event value? This would be some sort of dependant typing if I'm not
 mistaken.
 That's why my events exists both on type level and value level:
 *data NewPlayer = NewPlayer
 *
 wich allows me to associate it a typf data with type indexing.*..
 *

 Regards
 Corentin


 On Wed, Jul 4, 2012 at 12:58 PM, Paolino paolo.verone...@gmail.comwrote:

 Hi
 How many handlers for each type of event in the list of handlers ?
 If you have only one handler for each type , it should go in the
 typeclass, and you don't need typeable.
 If you have more than one maybe you can avoid using type indexing at
 all, because it doesn't resolve the handler selection issue.
 By the way , it's not clear to me why you don't have a simple Event
 datatype describing all the possible events in advance.

 Regards

 paolino

 2012/7/3 Corentin Dupont corentin.dup...@gmail.com

 Hi all,
 I read somewhere (here:
 http://stackoverflow.com/questions/2300275/how-to-unpack-a-haskell-existential-type)
 that it's bad to try to unbox an existential type using a cast. OK, but
 without I really can't figure out how to do what I want:

 *data NewPlayer = NewPlayer deriving (Typeable, Eq)
 data NewRule = NewRule deriving (Typeable, Eq)

 class (Eq e, Typeable e) = Event e where
 data EventData e

 instance Event NewPlayer where
 data EventData NewPlayer = P Int

 instance Event NewRule where
 data EventData NewRule = R Int

 instance Typeable1 EventData where
 typeOf1 _ = mkTyConApp (mkTyCon EventData) []

 data EventHandler = forall e . (Event e) = EH e (EventData e - IO ())

 addEvent :: (Event e) = e - (EventData e - IO ()) - [EventHandler]
 - [EventHandler]
 addEvent e h ehs = (EH e h):ehs

 triggerEvent :: (Event e) = e - (EventData e) - [EventHandler] - IO
 ()
 triggerEvent e d ehs = do
 let r = find (\(EH myEvent _) - cast e == Just myEvent) ehs
 case r of
Nothing - return ()
Just (EH _ h) - case cast h of
 Just castedH - castedH d
 Nothing - return ()*

 How to remove the casts from triggerEvent? All that I want is to apply
 the handler found on the data passed in parameter.
 I tried to add a function apply in the class, without success:
 *apply :: (EventData e - IO ()) - (EventData e) - IO ()
 apply = ($)*


 Thanks!
 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] haskell.org website ?

2012-07-05 Thread Qi Qi
Hi,

Haskell.org website seems dropping offline at this moment. Anyone know
what's happening to it?

Thanks,
Qi


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


[Haskell-cafe] Is there a GHC flag that will allow mutable top level state while you are debugging and then ...

2012-07-05 Thread KC
you can turn the flag off when you are ready to do the computational heavy
lifting so that you don't have to modify your code base?

That is, GHC can then apply its algebraic transformation optimizations to
the code algebra of the pure functions.

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


Re: [Haskell-cafe] HUnit/cabal integration

2012-07-05 Thread Simon Hengel
 First: the web page I cite above describes the interface that the test
 binary must support to work with cabal, specifically w.r.t. the binary's
 exit code.  Your test suites likely already fit this model.  However, if
 you are using an old version of QuickCheck or HUnit, your executable may
 not be returning the correct error code.
 
 This seems to me to suggest that recent versions of HUnit automatically
 take care of generating the exit code, but I've found that I have to
 examine HUnit's results and synthesize the exit code manually, as in the
 driver program below.  (I'm running HUnit 1.2.4.2, but the interface for
 1.2.4.3 doesn't appear to differ on this point.)  Am I misinterpreting the
 wiki page, or am I missing something in HUnit's API that generates the exit
 code automatically?

AFAIK, you have to do it explicitly.  But you can shorten it to
something like this:

when (errors c /= 0 || failures c /= 0)
  exitFailure

Personally I'd use some test framework that is build on top of HUnit and
QuickCheck.  My weapon of choice is Hspec [1], but there are other
options.

 Second: Am I specifying the Build-Depends correctly for the Test-Suite?
 Specifically: do I need to state a dependency on the library defined in the
 same package, or does it pick that up automatically?  Further, foo-tests
 doesn't use parsec directly.  Is the transitive dependency automatically
 provided for me, or do I need to list it explicitly as below?

You only have to add dependencies on what you actually use, so if you
depend on your library and only use stuff from your library, you do not
need to depend on parsec.

On a broader scope, you have two options, either

(a) Depend on your library in your Cabal test section.

or

(b) Include the source files of your library in your Cabal test section.

Whether you want (a) or (b) depends on the circumstances.  Here is a
(possibly not complete) list of differences:


 - (a) Is suitable when you only want to test the public interface of
   your library, but it does not allow you to test stuff that is not
   exposed.  In contrast, (b) allows you to test stuff that is not
   exposed.

 - (a) usually gives you a short test section in your Cabal file (and is
   more DRY). (b) requires you to repeat all dependencies, options, etc.
   of your library section in your test section.

 - Compilation is slower with (b), because the source files of your
   library are compiled twice.

 - (b) even works in the rare case, when your test framework depends on
   your library (e.g. if you use HUnit to test a dependency of HUnit).

I'm assuming here, that your library sources and test sources live in
different directory hierarchies, and I'm not sure what the exact
behavior is, if they don't!

Let's look at an example.  If your library sources are in '.' and your
test sources are in 'test' option (a) looks like so:

  test-suite foo-tests
type:
exitcode-stdio-1.0
main-is:
foo-tests.hs
hs-source-dirs:
test
build-depends:
base = 4.3.1.0   5
  , foo-- depend on your library
  , HUnit = 1.2.4.2

And option (b) looks like so:

  test-suite foo-tests
type:
exitcode-stdio-1.0
main-is:
foo-tests.hs
hs-source-dirs:
.  -- include the sources of your library
  , test
build-depends:
base = 4.3.1.0   5
  , parsec = 3.1.2-- inculde the depencencies of your library
  , HUnit = 1.2.4.2

Hope that helps.  Feel free to ask, if anything is unclear.

Cheers,
Simon

[1] http://hspec.github.com/

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


[Haskell-cafe] Call to arms: lambda-case is stuck and needs your help

2012-07-05 Thread Mikhail Vorozhtsov

Hi.

After 21 months of occasional arguing the lambda-case proposal(s) is in 
danger of being buried under its own trac ticket comments. We need fresh 
blood to finally reach an agreement on the syntax. Read the wiki 
page[1], take a look at the ticket[2], vote and comment on the proposals!


P.S. I'm CC-ing Cafe to attract more people, but please keep the 
discussion to the GHC Users list.


[1] http://hackage.haskell.org/trac/ghc/wiki/LambdasVsPatternMatching
[2] http://hackage.haskell.org/trac/ghc/ticket/4359

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


Re: [Haskell-cafe] Is there a GHC flag that will allow mutable top level state while you are debugging and then ...

2012-07-05 Thread Francesco Mazzoli
At Wed, 4 Jul 2012 09:06:32 -0700,
KC  wrote:
 you can turn the flag off when you are ready to do the computational
 heavy lifting so that you don't have to modify your code base?
 
 That is, GHC can then apply its algebraic transformation
 optimizations to the code algebra of the pure functions.

What do you mean allow mutable top level state? As in

 import Foreign.Ptr
 import Foreign.StablePtr
 import Foreign.Storable
 import System.IO.Unsafe
 
 destructiveUpdate :: Storable a = a - a - ()
 destructiveUpdate x y =
 unsafePerformIO $ do ptr - newStablePtr x
  poke (castPtr (castStablePtrToPtr ptr)) y
  freeStablePtr ptr

? The only problem that the above function does not work - you can't
poke or peek off StablePtrs.

If that's what you mean, no. And I doubt it'll ever exist, since it
breaks the most important invariant in Haskell - that is, that values
don't change. An Haskell compiler will rely on this assumption quite
heavily, so changes to that are likely to disrupt things seriously.

Also, I don't see how destructive updates help debugging.

--
Francesco * Often in error, never in doubt

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


[Haskell-cafe] Haskell Weekly News: Issue 234

2012-07-05 Thread Daniel Santa Cruz
Welcome to issue 234 of the HWN, an issue covering crowd-sourced bits
of information about Haskell from around the web. This issue covers the
week of June 24 to 30, 2012.

Quotes of the Week

   * monochrom: shae ericsson is shae erisson's evil twin who prefers
erlang to haskell :)

   * shapr: If I were to do this in Python, it would be done by now. and
it would be full of bugs.

Top Reddit Stories

   * Performance: yes, it’s worth looking at the small stuff
 Domain: serpentine.com, Score: 61, Comments: 11
 On Reddit: [1] http://goo.gl/x2pGf
 Original: [2] http://goo.gl/SHBNB

   * Awesome Haskell plugins for Vim!
 Domain: self.haskell, Score: 61, Comments: 32
 On Reddit: [3] http://goo.gl/Bm6wI
 Original: [4] http://goo.gl/Bm6wI

   * Galois is Hiring!
 Domain: haskell.org, Score: 56, Comments: 7
 On Reddit: [5] http://goo.gl/c7zj8
 Original: [6] http://goo.gl/y7nBd

   * Haskell Symposium 2012 list of accepted papers
 Domain: haskell.org, Score: 43, Comments: 12
 On Reddit: [7] http://goo.gl/Fq0rD
 Original: [8] http://goo.gl/CGZV3

   * Live coding the game of Sokoban with GUI.
 Please give me your input for future sessions.
 Domain: youtu.be, Score: 42, Comments: 38
 On Reddit: [9] http://goo.gl/HslD9
 Original: [10] http://goo.gl/0ZeMA

   * Mirrored Lenses
 Domain: comonad.com, Score: 36, Comments: 30
 On Reddit: [11] http://goo.gl/UyGco
 Original: [12] http://goo.gl/9ltWW

   * The Game of Distributed Systems Programming. Which Level Are You?
 Incubaid Research
 Domain: blog.incubaid.com, Score: 30, Comments: 7
 On Reddit: [13] http://goo.gl/EYWj7
 Original: [14] http://goo.gl/P0vhZ

   * SugarHaskell: language extensions in sugar modules[pdf]
 Domain: informatik.uni-marburg.de, Score: 27, Comments: 7
 On Reddit: [15] http://goo.gl/Z4fL5
 Original: [16] http://goo.gl/I78Md

   * parallel cabal-install patches
 Domain: haskell.org, Score: 26, Comments: 4
 On Reddit: [17] http://goo.gl/Yr1JR
 Original: [18] http://goo.gl/P9WPK

   * Is anybody using Sublime Text for their Haskell editing?
 Domain: self.haskell, Score: 19, Comments: 16
 On Reddit: [19] http://goo.gl/pmor9
 Original: [20] http://goo.gl/pmor9

   * Runge–Kutta in Haskell (RK4)
 Domain: stochastix.wordpress.com, Score: 19, Comments: 7
 On Reddit: [21] http://goo.gl/9Bd2b
 Original: [22] http://goo.gl/H27Fv

   * How to build an example proxy server using conduit 0.5
 Domain: yesodweb.com, Score: 19, Comments: 14
 On Reddit: [23] http://goo.gl/BHLRd
 Original: [24] http://goo.gl/PtOxh

   * Found myself wanting lambda-case again
 Domain: self.haskell, Score: 16, Comments: 13
 On Reddit: [25] http://goo.gl/LIOKa
 Original: [26] http://goo.gl/LIOKa

   * What is the advantage of monad transformers over monad coproducts?
 Domain: self.haskell, Score: 16, Comments: 28
 On Reddit: [27] http://goo.gl/lxX2D
 Original: [28] http://goo.gl/lxX2D

   * Elm 0.3.5: JavaScript Integration, Signal Filters, space savings, ...
 Domain: testblogpleaseignore.com, Score: 15, Comments: 2
 On Reddit: [29] http://goo.gl/jTwAz
 Original: [30] http://goo.gl/UzoZL

   * Scribd's AI Challenge Now Supports Haskell
 Domain: groups.google.com, Score: 14, Comments: 6
 On Reddit: [31] http://goo.gl/xmuwG
 Original: [32] http://goo.gl/oQsTG

   * EclipseFP: integrating stylish-haskell
 Domain: jpmoresmau.blogspot.fr, Score: 11, Comments:
 On Reddit: [33] http://goo.gl/reK9T
 Original: [34] http://goo.gl/2416v

Top StackOverflow Questions

   * Bug in Data.Map implementation?
 votes: 15, answers: 1
 Read on SO: [35] http://goo.gl/xcgC1

   * Monads with Join() instead of Bind()
 votes: 15, answers: 6
 Read on SO: [36] http://goo.gl/phgVU

   * Haskell numbers and type system?
 votes: 11, answers: 2
 Read on SO: [37] http://goo.gl/nv7Be

   * How to put constraints on the associated data?
 votes: 10, answers: 2
 Read on SO: [38] http://goo.gl/6zOr9

   * How to run Snap haskell webapp in production?
 votes: 9, answers: 3
 Read on SO: [39] http://goo.gl/kx2DR

   * How can I search a hackage package for a function?
 votes: 8, answers: 2
 Read on SO: [40] http://goo.gl/9fm4O

   * In Haskell, + is a function, (+ 2) is a function, (+ 2 3) is 5.
 What exactly is going on there?
 votes: 8, answers: 4
 Read on SO: [41] http://goo.gl/PP2X2

   * How can I emulate pointers in Haskell?
 votes: 8, answers: 1
 Read on SO: [42] http://goo.gl/Yq01G

   * Haskell Precedence: Lambda and operator
 votes: 8, answers: 2
 Read on SO: [43] http://goo.gl/X8yvV

   * Binding name in type signature using DataKind
 votes: 8, answers: 2
 Read on SO: [44] http://goo.gl/rYcS8

   * Missing something with Reader monad - passing the damn thing
 around everywhere
 votes: 7, 

[Haskell-cafe] OpenShift a free PaaS from RedHat

2012-07-05 Thread C K Kashyap
Hi Folks,

I just found out about OpenShift - its a free PaaS from RedHat. It has some
interesting offerings. It does not support Haskell out of the box as of now.
Please do check it out and if you like it - vote for Haskell support on it
here - https://openshift.redhat.com/community/content/support-for-haskell

Meanwhile, I am trying to get complied Haskell executable to run on that
platform.

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


Re: [Haskell-cafe] Is haskell.org down?

2012-07-05 Thread C K Kashyap
Thanks!
Regards,
Kashyap

On Thu, Jul 5, 2012 at 4:20 PM, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:

 Not anymore!

 On 5 July 2012 15:13, C K Kashyap ckkash...@gmail.com wrote:
  Regards,
  Kashyap
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 http://IvanMiljenovic.wordpress.com

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


[Haskell-cafe] Parallel Haskell Digest 11

2012-07-05 Thread Eric Kow
Parallel Haskell Digest 11
==
HTML version: http://www.well-typed.com/blog/67

Hello Haskellers!

It's time for another Parallel Haskell Digest! Unfortunately, this may
just be our last one, at least within the context of the Parallel GHC
project. That said, we may as a community be at the very beginnings of
Haskell as *the* language of choice for your parallel and concurrent
needs. Maybe we need to keep something like the Digest going to help our
little FP monster through its infancy? Any volunteers in the community?
If you're interested in picking up the torch, please give us a shout!

Otherwise, if you can't take on a (perhaps rotating) digest commitment,
but still want to help, would you be kind enough to fill out a small
[survey](http://goo.gl/bP2fn) on the digest? There are just five
questions on it, plus a feedback form. Anything you can say will help
those of us in the Secret Haskell Propaganda Commitee to fine tune our
efforts:

http://goo.gl/bP2fn

It's been a fantastic year for me, working on the Parallel GHC project,
learning about all sorts of neat ideas and technologies (as a basic
parallel-naive Haskeller), and trying to reflect them back in a way that
hopefully helps the broader community.  Thanks to all of you in the
parallel Haskell world first for cranking out all this great stuff for
us to use, and second for your patience and support.  Thanks especially
to my follow Well-Typed-ers for all the fun chats, the feedback on
drafts, and help getting up to speed.

One last thing before signing off as your Parallel Haskell Digester.
While the digest may be coming to an end, there will at least be one
encore! It turns out we had so much to say in our last word of the
month, that we'll have to put in in a follow-up posting. In the
meantime, we'll just leave you with a little teaser…

News
--
*[Announce: Haskell Platform 2012.2.0.0][n1] (3 Jun)

 The new Haskell Platform is out! If you've been waiting for Haskell
 Platform before moving on GHC 7.4, now's a great time to upgrade.
 Of particular interest to parallel Haskellers, this latest GHC
 offers better profiling flags, multicore profiling, vastly improved
 DPH, event logging [allows ThreadScope spark profiling], and more
 convenient RTS flags.

*[Introducing FP Complete][n2] (6 Jun)

 You might have Bartosz Milewski around. If not, have a look at the
 [Downfall of Imperative Programming][downfall]. Bartosz posted a
 quick message introducing himself to the community along with the
 new company FP Complete, which aims to commercialise Haskell.
 Bartosz believes that “now is the right time for Haskell to become
 a strong software industry player, especially that functional
 programming is being widely recognized as the answer to the recent
 multicore and GPU explosion.” We'll hopefully find out more about
 FP Complete have in mind as their plans stabilise a bit.

*[3 year Bioinformatics RD position in Granada, Spain][n3]

 Love Functional Programming and concurrency? If you are a
 CS/Math/IT graduate without a PhD, and have had no more
 than 4 years of research experience, and have not lived in
 Spain for more than 12 months (within the last 3 years),
 Era7 has a position for you! You'll be hacking Scala and
 using AWS for everything. So if Akka is the sort of thing
 you're into, this could be the job for you.

Word of the month (teaser!)
--
The word of the month series has given us a chance to survey the arsenal
of Haskell parallelism and concurrency constructs:

*some low level foundations (sparks and threads),
*three ways to do parallelism (parallel arrays, strategies, dataflow),
*and some concurrency abstractions (locks, transactions, channels)

The Haskell approach has been to explicitly recognise the vastness of
the parallelism/concurrency space, in other words, to provide a
multitude of right tools for a multitude of right jobs. Better still,
the tools we have are largely interoperable, should we find ourselves
with jobs that don't neatly fit into a single category.

The Haskell of 2012 may be in a great place for parallelism and
concurrency, but don't think this is the end of the story! What we've
seen so far is only a snapshot of the technology as it hurtles through
the twenty-tens (How quaint are we, Future Haskeller?). While we can't
say what exactly the future will bring, we can look at one of the
directions that Haskell might branch into in the coming decade.
The series so far has focused on things you might do with a single
computer, using parallelism to speed up your software, or using
concurrency abstractions to preserve your sanity in the face of
non-determinism. But now what if you have more than one computer?

Our final word of the month is *actor*. Actors 

[Haskell-cafe] arbitrary rank polymorphism and ghc language pragmas

2012-07-05 Thread rickmurphy
Hi All:

I've been working through some details in these papers [1], [2] and
noticed a language pragma configuration that I hope you can confirm.

When using explicit foralls in a data constructor, it appears that GHC
7.4.2 requires Rank2Types in the Language pragma for what the papers
consider rank 1 types. 

Here's an example:

data T = TC (forall a b. a - b - a)

Am I correct, or is there another extension? The ExplicitForAll does not
appear to support rank 1 types in data constructors.

1. Practical Type Inference for Arbitrary-Rank Types.
2. A Direct Algorithm for Type Inference in the Rank 2 Fragment of the
Second-Order Lambda Calculus.

--
Rick


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


Re: [Haskell-cafe] Call to arms: lambda-case is stuck and needs your help

2012-07-05 Thread Christopher Done
I like \case as is proposed. It seems the least controversial one and
there's curry (\case ) for two-args, but even that seems a rare case.

For what it's worth, I like the idea of omission being partiality, as
in case of and if then. It seems perfectly natural to me, I don't need
a \ to tell me that an expression will result in a function. But some
do. So I'll go along with and vote for \case. The lack of a lambda
case is one of the few legitimate complaints I have about Haskell's
syntax so it would be marvey to see it in GHC.

P.S. \if then … else …?

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


Re: [Haskell-cafe] arbitrary rank polymorphism and ghc language pragmas

2012-07-05 Thread Francesco Mazzoli
At Thu, 05 Jul 2012 11:18:00 -0400,
rickmurphy  wrote:
 data T = TC (forall a b. a - b - a)

The type of `TC' will be `(forall a b. a - b - a) - T', a Rank-2
type.

--
Francesco * Often in error, never in doubt

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


Re: [Haskell-cafe] arbitrary rank polymorphism and ghc language pragmas

2012-07-05 Thread Twan van Laarhoven

On 05/07/12 17:18, rickmurphy wrote:

Hi All:

I've been working through some details in these papers [1], [2] and
noticed a language pragma configuration that I hope you can confirm.

When using explicit foralls in a data constructor, it appears that GHC
7.4.2 requires Rank2Types in the Language pragma for what the papers
consider rank 1 types.

Here's an example:

data T = TC (forall a b. a - b - a)

Am I correct, or is there another extension? The ExplicitForAll does not
appear to support rank 1 types in data constructors.


There is the PolymorphicComponents extension precisely for this use case.


Twan



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


Re: [Haskell-cafe] OpenShift a free PaaS from RedHat

2012-07-05 Thread Shakthi Kannan
Hi,

--- On Thu, Jul 5, 2012 at 8:41 PM, C K Kashyap ckkash...@gmail.com wrote:
| I just found out about OpenShift - its a free PaaS from RedHat. It has some
| interesting offerings. It does not support Haskell out of the box as of now.
| Please do check it out and if you like it - vote for Haskell support on it
| here - https://openshift.redhat.com/community/content/support-for-haskell
|
| Meanwhile, I am trying to get complied Haskell executable to run on that
| platform.
\--

We already have a Fedora Haskell SIG [1] where we are working on
shipping Haskell packages in Fedora. Recently, support for EL-6 was
added, and one can get Haskell packages through the EPEL [2]
repository.

Please feel free to ping us on #fedora-haskell on irc.freenode.net.

SK

[1] Fedora Haskell SIG. http://fedoraproject.org/wiki/Haskell_SIG

[2] Extra Packages for Enterprise Linux (EPEL).
http://fedoraproject.org/wiki/EPEL

-- 
Shakthi Kannan
http://www.shakthimaan.com

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


Re: [Haskell-cafe] Cabal problem re. haskelldb-hdbc-mysql

2012-07-05 Thread Nicolas Wu
On Wed, Jul 4, 2012 at 3:58 PM, Yves Parès yves.pa...@gmail.com wrote:
 Hi,
 the package http://hackage.haskell.org/package/haskelldb-hdbc-mysql/ the use
 of HDBC 2.3.0
 I'm using cabal-install 0.14, and with a fresh install (no packages already
 installed), cabal-install tries to install HDBC-2.1.1 instead of, say,
 HDBC-2.2.7.0.

 The problem is that HDBC-2.1.1 is old (2009) and does not compile.

 When I download haskelldb-hdbc-mysql manually, change the dependency and
 then install, it compiles fine.

 Is the dependency ill-declared, or is that a cabal problem?

Apart from the change of license, there were no serious changes to the
HDBC interface between the 2.2.* and 2.3.* series: as far as I know,
it should be fine to change the dependency. That said, I've not worked
with haskelldb-hdbc-mysql, so I can't say for sure.

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


Re: [Haskell-cafe] arbitrary rank polymorphism and ghc language pragmas

2012-07-05 Thread rickmurphy
Thanks Francesco. And I did verify that ExplicitForAll does in fact
allow Rank 1 Types in functions like the following ...

f :: (forall a. a - a)

--
Rick

On Thu, 2012-07-05 at 16:28 +0100, Francesco Mazzoli wrote:
 At Thu, 05 Jul 2012 11:18:00 -0400,
 rickmurphy  wrote:
  data T = TC (forall a b. a - b - a)
 
 The type of `TC' will be `(forall a b. a - b - a) - T', a Rank-2
 type.
 
 --
 Francesco * Often in error, never in doubt
 
 ___
 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] Bad interface problem.

2012-07-05 Thread Albert Y. C. Lai

On 12-07-03 04:19 AM, Magicloud Magiclouds wrote:

$ cabal --upgrade-dependencies --enable-documentation
--force-reinstalls --solver=topdown QuickCheck-2.5
Test/QuickCheck/All.hs:15:1:
 Bad interface file:
/home/magicloud/.cabal/lib/template-haskell-2.6.0.0/ghc-7.4.2/Language/Haskell/TH.hi
 Something is amiss; requested module
template-haskell-2.6.0.0:Language.Haskell.TH differs from name found
in the interface file template-haskell:Language.Haskell.TH


I think things are so messed up that it is time to clean out everything. 
See my

http://www.vex.net/~trebla/haskell/sicp.xhtml#remove

In fact, time to read the whole article and avoid unsafe re-installs and 
upgrades.


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


[Haskell-cafe] Posting jobs on Haskellers.com

2012-07-05 Thread Bartosz Milewski
There are no job postings on Haskellers.com and I'm wondering whether it's 
because you have to wait for the verified status before you can post (and 
that's after you have successfully verified your email). Posting the job on 
the CUFP site, on the other hand, was painless:  
http://cufp.org/jobs/haskell-systems-administrator .___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Plain lambda inside banana brackets in the arrow notation

2012-07-05 Thread Tsuyoshi Ito
Hello,

In a program, I have an arrow MyArr and a combinator called repeat of
the following type:

repeat :: Int - (Int - MyArr e a) - MyArr e a

My problem is that the code becomes messy when I use this combinator
inside the arrow notation, and I am looking for a way to write the
code in a more readable way.

To explain the problem, first consider the following combinator
repeat', which is less general than repeat:

repeat' :: Int - MyArr (e, Int) a - MyArr e a
repeat' n f = repeat n g
  where g i = arr (\e - (e, i))  f

Combinator repeat' is nice to use in the arrow notation, thanks to
banana brackets and the interpretation of lambda:

test1 :: MyArr [Double] String
test1 = proc xs - do
let y = func1 xs
z - job1 - xs
(|(repeat' 100) (\i - job2 - xs !! i + y + z)|)

-- func1 :: [Double] - Double
-- job1 :: MyArr [Double] Double
-- job2 :: MyArr Double String

However, in my program, I often have to use repeat instead of repeat' like:

test2 :: MyArr [Double] String
test2 = proc xs - do
let y = func1 xs
z - job1 - xs
repeat 100 (\i - proc (xs, y, z) - job3 (i * 2) - xs !! i +
y + z) - (xs, y, z)

-- job3 :: Int - MyArr Double String

Note that variable i is used as an argument to function job3 outside
MyArr, and this cannot be done with repeat'.

The code for test2 looks messy to me because I have to write “(xs, y,
z)”, that is, the list of variables used inside the subcomputation
explicitly (and twice).  It does not seem possible to use banana
brackets here because the type of the subcomputation does not meet the
requirements stated in
http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/arrow-notation.html#id686230.

How can I use combinators like repeat, which takes a plain function as
an argument, in the arrow notation in a more readable way?  Or am I
trying to do an impossible thing?

Best regards,
  Tsuyoshi

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


Re: [Haskell-cafe] Cabal problem re. haskelldb-hdbc-mysql

2012-07-05 Thread Albert Y. C. Lai

On 12-07-04 10:58 AM, Yves Parès wrote:

the package http://hackage.haskell.org/package/haskelldb-hdbc-mysql/ the
use of HDBC 2.3.0
I'm using cabal-install 0.14, and with a fresh install (no packages
already installed), cabal-install tries to install HDBC-2.1.1 instead
of, say, HDBC-2.2.7.0.


HDBC 2.2.* all want time=1.1.2.4  =1.2.0.3, GHC 7.4.1 comes with 
time-1.4, therefore HDBC 2.2.* are all rejected. 2.1.1 is the topmost 
one without the upper bound.


This analysis is made possible by cabal install --dry-run -v3 
haskelldb-hdbc-mysql of cabal-install 0.14. Now with actually relevant 
output! (As part of the new modular solver, I guess.)


P.S. haskelldb-hdbc wants mtl-2.0.*, but you already have mtl-2.1 
because you have cabal-install 0.14. mtl-2.0.1.0 in turn wants 
transformers-0.2.*, but you already have transformers-0.3.0.0 again 
because you have cabal-install 0.14. Expect mysterious problems in the 
future.



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


Re: [Haskell-cafe] HUnit/cabal integration

2012-07-05 Thread Richard Cobbe
On Thu, Jul 05, 2012 at 04:17:33PM +0200, Simon Hengel wrote:
  First: the web page I cite above describes the interface that the test
  binary must support to work with cabal, specifically w.r.t. the binary's
  exit code.  Your test suites likely already fit this model.  However, if
  you are using an old version of QuickCheck or HUnit, your executable may
  not be returning the correct error code.
 
  This seems to me to suggest that recent versions of HUnit automatically
  take care of generating the exit code, but I've found that I have to
  examine HUnit's results and synthesize the exit code manually, as in the
  driver program below.  (I'm running HUnit 1.2.4.2, but the interface for
  1.2.4.3 doesn't appear to differ on this point.)  Am I misinterpreting the
  wiki page, or am I missing something in HUnit's API that generates the exit
  code automatically?

 AFAIK, you have to do it explicitly.  But you can shorten it to
 something like this:

 when (errors c /= 0 || failures c /= 0)
   exitFailure

Ah, good suggestion.  Thanks!

  Second: Am I specifying the Build-Depends correctly for the Test-Suite?
  Specifically: do I need to state a dependency on the library defined in the
  same package, or does it pick that up automatically?  Further, foo-tests
  doesn't use parsec directly.  Is the transitive dependency automatically
  provided for me, or do I need to list it explicitly as below?

snip

 Let's look at an example.

Many thanks for your advice -- and I particularly appreciate the examples!
I haven't had a chance to try them out yet, but I hope to be able to soon.

Thanks a bunch for your help,

Richard

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


[Haskell-cafe] ANNOUNCE: Sifflet visual programming language, release 2.0.0.0

2012-07-05 Thread gdweber
I don't usually get this excited about a release, but after
nearly a year of not being able to do any work on Sifflet, I am now
*Extremely Happy* to announce --

Sifflet and sifflet-lib 2.0.0.0, now available on Hackage!

This version introduces a type checker and partial support
for higher order functions in Sifflet, the visual, functional 
programming language and support system for students learning 
about recursion.  Sifflet programmers define functions by drawing 
diagrams, and the Sifflet interpreter uses the diagrams to show how
function calls are evaluated.

Sifflet-lib is the library containing many modules of the Sifflet 
application.

What's New
--

July 5, 2012, Version 2.0.0.0:

*   Partial support for higher order functions, like map and filter.
See Lesson 10 in the Sifflet Tutorial.

*   Sifflet now provides type checking and type inference.
This should make it possible to provide exporters to
languages, like Java, that require type declarations.
(Unfortunately, the error messages for incorrectly typed
functions are not yet friendly for novice programmers.)

*   Added a menu command (File / Save image ...) to save
vector graphic images of functions in the Sifflet Workspace
or Edit function windows.  Images can be saved in SVG,
Postscript, and PDF formats.

*   Reorganized hierarchical modules in the library
to conform to the recommended practice.  See the
RELEASE-NOTES for details.

*   Several bugs are fixed, including one which crashed
Sifflet when applying a function definition with an
incomplete `if` tree.  See ISSUES for details.

*   There is a new file format for saving function definitions
to support higher-order function types.  The new format,
siffml 2.0, has a RELAX NG schema; siffml 1.0 files can
still be opened in Sifflet 2.0.

About Sifflet
-

Sifflet is a visual, functional programming language
intended as an aid for learning about recursion.

*   A picture explains Sifflet better than words:
please see the screenshot showing how to evaluate 3!:
http://mypage.iu.edu/~gdweber/software/sifflet/home.html

*   Features:
-   Visual editor.
-   Visual tracer/debugger which shows how recursive and
other function calls are evaluated.  To support active learning
and avoid screen clutter, Sifflet displays only
as much of the computation as the user requests.
-   Carefully crafted tutorial with 44 pictures,
about 26 pages if printed.
-   Number, string, and list data types.
-   Small collection of primitive functions.
-   Runnable examples of compound functions.
-   Sifflet functions can be exported to Scheme, Python 3, and Haskell.

References
--

*   Download:
http://hackage.haskell.org/package/sifflet-lib
http://hackage.haskell.org/package/sifflet

*   Home page:
http://mypage.iu.edu/~gdweber/software/sifflet/home.html

*   Sifflet Tutorial:
http://mypage.iu.edu/~gdweber/software/sifflet/doc/tutorial.html

*   RELEASE-NOTES:
http://mypage.iu.edu/~gdweber/software/sifflet/RELEASE-NOTES

*   ISSUES:
http://mypage.iu.edu/~gdweber/software/sifflet/ISSUES




-- 
Gregory D. Weber, Ph. D.:
Associate Professor of Informatics / \
Indiana University East   0   :
Tel. (765) 973-8420; FAX (765) 973-8550  / \
http://mypage.iu.edu/~gdweber/  1  []

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


Re: [Haskell-cafe] OpenShift a free PaaS from RedHat

2012-07-05 Thread C K Kashyap
Hey Shakti,
OpenShift gives access to Linux virtual machines on the cloud. However, we
do not have root access so we cannot install any new package.
I was trying to get my haskell code compiled into native on my local linux
box and taking it to those machines. That does not seem to work because of
two things -
1. GLIBC version mismatch
2. libgmp missing on the openshift box
Regards,
Kashyap

On Thu, Jul 5, 2012 at 9:19 PM, Shakthi Kannan shakthim...@gmail.comwrote:

 Hi,

 --- On Thu, Jul 5, 2012 at 8:41 PM, C K Kashyap ckkash...@gmail.com
 wrote:
 | I just found out about OpenShift - its a free PaaS from RedHat. It has
 some
 | interesting offerings. It does not support Haskell out of the box as of
 now.
 | Please do check it out and if you like it - vote for Haskell support on
 it
 | here -
 https://openshift.redhat.com/community/content/support-for-haskell
 |
 | Meanwhile, I am trying to get complied Haskell executable to run on that
 | platform.
 \--

 We already have a Fedora Haskell SIG [1] where we are working on
 shipping Haskell packages in Fedora. Recently, support for EL-6 was
 added, and one can get Haskell packages through the EPEL [2]
 repository.

 Please feel free to ping us on #fedora-haskell on irc.freenode.net.

 SK

 [1] Fedora Haskell SIG. http://fedoraproject.org/wiki/Haskell_SIG

 [2] Extra Packages for Enterprise Linux (EPEL).
 http://fedoraproject.org/wiki/EPEL

 --
 Shakthi Kannan
 http://www.shakthimaan.com

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


Re: [Haskell-cafe] OpenShift a free PaaS from RedHat

2012-07-05 Thread Michael Snoyman
Hi Kashyap,

I'm not sure if it will solve the problem, but I ran across a tool[1]
the other day that bundles up applications with all of the libraries
and other resources they need. I wouldn't be surprised if, with this,
you can get your code to run on OpenShift.

Michael

[1] http://www.pgbovine.net/cde.html

On Fri, Jul 6, 2012 at 7:51 AM, C K Kashyap ckkash...@gmail.com wrote:
 Hey Shakti,
 OpenShift gives access to Linux virtual machines on the cloud. However, we
 do not have root access so we cannot install any new package.
 I was trying to get my haskell code compiled into native on my local linux
 box and taking it to those machines. That does not seem to work because of
 two things -
 1. GLIBC version mismatch
 2. libgmp missing on the openshift box
 Regards,
 Kashyap


 On Thu, Jul 5, 2012 at 9:19 PM, Shakthi Kannan shakthim...@gmail.com
 wrote:

 Hi,

 --- On Thu, Jul 5, 2012 at 8:41 PM, C K Kashyap ckkash...@gmail.com
 wrote:
 | I just found out about OpenShift - its a free PaaS from RedHat. It has
 some
 | interesting offerings. It does not support Haskell out of the box as of
 now.
 | Please do check it out and if you like it - vote for Haskell support on
 it
 | here -
 https://openshift.redhat.com/community/content/support-for-haskell
 |
 | Meanwhile, I am trying to get complied Haskell executable to run on that
 | platform.
 \--

 We already have a Fedora Haskell SIG [1] where we are working on
 shipping Haskell packages in Fedora. Recently, support for EL-6 was
 added, and one can get Haskell packages through the EPEL [2]
 repository.

 Please feel free to ping us on #fedora-haskell on irc.freenode.net.

 SK

 [1] Fedora Haskell SIG. http://fedoraproject.org/wiki/Haskell_SIG

 [2] Extra Packages for Enterprise Linux (EPEL).
 http://fedoraproject.org/wiki/EPEL

 --
 Shakthi Kannan
 http://www.shakthimaan.com



 ___
 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] OpenShift a free PaaS from RedHat

2012-07-05 Thread satvik chauhan


 OpenShift gives access to Linux virtual machines on the cloud. However, we
 do not have root access so we cannot install any new package.
 I was trying to get my haskell code compiled into native on my local linux
 box and taking it to those machines. That does not seem to work because of
 two things -
 1. GLIBC version mismatch
 2. libgmp missing on the openshift box
 Regards,
 Kashyap


I think you might want to check out CDE.
http://www.pgbovine.net/cde.html

This will take care of the version mismatch of the libraries.

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


Re: [Haskell-cafe] OpenShift a free PaaS from RedHat

2012-07-05 Thread C K Kashyap
Thank you Micheal and Satvik. I think cde should solve the problem - I'll
confirm later - for some reason, I do not have SSH connectivity from my
office.

What'll be best though is - yesod on OpenShift :)

Regards,
Kashyap

On Fri, Jul 6, 2012 at 10:51 AM, satvik chauhan mystic.sat...@gmail.comwrote:


 OpenShift gives access to Linux virtual machines on the cloud. However,
 we do not have root access so we cannot install any new package.
 I was trying to get my haskell code compiled into native on my local
 linux box and taking it to those machines. That does not seem to work
 because of two things -
 1. GLIBC version mismatch
 2. libgmp missing on the openshift box
 Regards,
 Kashyap


 I think you might want to check out CDE.
 http://www.pgbovine.net/cde.html

 This will take care of the version mismatch of the libraries.

 - Satvik

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


Re: [Haskell-cafe] OpenShift a free PaaS from RedHat

2012-07-05 Thread Shakthi Kannan
Hi,

--- On Fri, Jul 6, 2012 at 11:16 AM, C K Kashyap ckkash...@gmail.com wrote:
| What'll be best though is - yesod on OpenShift :)
\--

The review is pending due to dependencies that need to be reviewed first.

  https://bugzilla.redhat.com/show_bug.cgi?id=630303

SK

-- 
Shakthi Kannan
http://www.shakthimaan.com

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