Re: [Haskell-cafe] MonadBaseControl IO instance for conduits ?

2013-10-11 Thread John Wiegley
 Aleksey Uymanov s9gf4...@gmail.com writes:

 Is it posible to create instance of MonadBaseControl IO (ConduitM i o m) ?

No, it is not, for approximately the same reason that you cannot create one
for ContT (or any form of continuation).

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lifting IO actions into Applicatives

2013-10-07 Thread John Wiegley
 Daniil Frumin difru...@gmail.com writes:

 Isn't it the case that there could be more than one natural transformation
 between functors?

Yes, I imagine there would have to be some newtype wrappers to distinguish in
those cases.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Poll plea: State of GUI graphics libraries in Haskell

2013-10-05 Thread John Lato
I think you've misunderstood Robin's point. The problem is that each of
these libraries is platform-specific. Writing an api on top of one is work
enough, but writing a cross-platform api that binds to the appropriate
platform-specific backend is a major undertaking.

On Oct 4, 2013 7:12 PM, Alp Mestanogullari alpmes...@gmail.com wrote:

 If these said libraries let us write a good API on top, then perfect! The
problem is to actually pick the ones fulfilling our needs I think, all the
major candidatures have pretty serious drawbacks, AFAIK.


 On Sat, Oct 5, 2013 at 12:36 AM, Robin KAY komad...@gekkou.co.uk wrote:

 Dear Alp,

 Alp Mestanogullari wrote:
 [snip]

 I have been willing to have a nice GUI DSEL with good aesthetics for a
while. I think the hardest part wouldn't be the API, but really what
library we use underneath so that it's cross-platform and easy to install
for everyone. But I would love for something like that to happen and am
very interested in this.

 Herein lies, for my purposes, the downfall of attempts to build GUI
tool-kits on top of a blank canvas. From the perspective of binding to the
platform, getting the basic functionality of a cross-platform GLUT or SDL
equivalent isn't terribly difficult. You can layer your own widget system
on top but even if you don't care about native look and feel (and I don't
particularly), there are still three big functionality hurdles in my mind
to building serious applications:-

 i) Proper text rendering is more difficult than placing one glyph after
another on a line. You need to bind to each platform's text rendering
engine: Pango/others, Uniscribe, and Core Text.
 ii) Proper text input is more difficult than listening for key press and
release events. You need to bind to the each platform's input method
system: XIM/IBus/others, IMM, and NSTextInputClient.
 iii) Proper accessibility is just difficult.

 There are plenty of applications where that doesn't matter and there are
lots of attractive things about a pure Haskell implementation with
beautiful high-level API. However, from my perspective, there are also
attractions to outsourcing as much of that work as possible to existing
libraries on the other side of the FFI even though that seems to bring us
down to lower-level.

 Regards,

 --
 Robin KAY


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




 --
 Alp Mestanogullari

 ___
 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] Newclasses

2013-10-03 Thread John Lato
I don't really understand what a newclass is supposed to be.


On Thu, Oct 3, 2013 at 2:15 PM, Wvv vite...@rambler.ru wrote:


 newclass Bind a = Monad a = BMonad a where { (=) = (-) }


I think this means that `BMonad` is supposed to be a new class that has
both Bind and Monad in scope, the same as

  class (Bind a, Monad a) = BMonad a

except that the Monad instance's (=) is replaced by (-).

If that's what newclass means, it seems absolutely pointless.

Does it instead mean that one could write

  instance Bind MyType where

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


Re: [Haskell-cafe] Newclasses

2013-10-03 Thread John Lato
Apologies, that wasn't finished.  I meant to say, does it mean that by
writing a BMonad instance a Monad instance would be automatically
generated?  If so, that seems like it would cause conflicts in many cases.
Regardless, I think newclass needs to be better specified if you want
other people to be able to support it.


On Thu, Oct 3, 2013 at 7:53 PM, John Lato jwl...@gmail.com wrote:

 I don't really understand what a newclass is supposed to be.


 On Thu, Oct 3, 2013 at 2:15 PM, Wvv vite...@rambler.ru wrote:


 newclass Bind a = Monad a = BMonad a where { (=) = (-) }


 I think this means that `BMonad` is supposed to be a new class that has
 both Bind and Monad in scope, the same as

   class (Bind a, Monad a) = BMonad a

 except that the Monad instance's (=) is replaced by (-).

 If that's what newclass means, it seems absolutely pointless.

 Does it instead mean that one could write

   instance Bind MyType where

   instance BMonad MyType

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


Re: [Haskell-cafe] Lifting IO actions into Applicatives

2013-10-01 Thread John Lato
It's not a solution per se, but it seems to me that there's no need for the
Monad superclass constraint on MonadIO.  If that were removed, we could
just have

class LiftIO t where
liftIO :: IO a - t a

and it would Just Work.


On Tue, Oct 1, 2013 at 1:58 AM, Michael Snoyman mich...@snoyman.com wrote:

 I'm wondering if anyone's run into this problem before, and if there's a
 common solution.

 In Yesod, we have applicative forms (based originally on formlets). These
 forms are instances of Applicative, but not of Monad. Let's consider a
 situation where we want to get some user input to fill out a blog post
 datatype, which includes the current time:

 data Blog = Blog Title UTCTime Contents

 myBlogForm :: Form Blog
 myBlogForm = Blog $ titleForm * something * contentsForm

  The question is: what goes in something? Its type has to be:

 something :: Form UTCTime

 Ideally, I'd call getCurrentTime. The question is: how do I lift that into
 a Form? Since Form is only an Applicative, not a Monad, I can't create a
 MonadIO instance. However, Form is in fact built on top of IO[1]. And it's
 possible to create a MonadTrans instance for Form, since it's entirely
 possible to lift actions from the underlying functor/monad into Form. So
 something can be written as:

 something = lift $ liftIO getCurrentTime

 This works, but is unintuitive. One solution would be to have an
 ApplicativeIO typeclass and then use liftIOA. My questions here are:

 1. Has anyone else run into this issue?
 2. Is there an existing solution out there?

 Michael

 [1] Full crazy definition is at:
 http://haddocks.fpcomplete.com/fp/7.4.2/20130922-179/yesod-form/Yesod-Form-Types.html#t:AForm

 ___
 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] Lifting IO actions into Applicatives

2013-10-01 Thread John Wiegley
 Yitzchak Gale g...@sefer.org writes:

 In fact, it even makes sense to define it as FunctorIO, with the only laws
 being that liftIO commutes with fmap and preserves id, i.e., that it is a
 natural transformation. (Those laws are also needed for ApplicativeIO and
 MonadIO.)

Given that we are moving toward Applicative (and thus Functor) as a superclass
of Monad, why not just solve the MonadIO problem and similar type classes with
natural transformations?  It requires 3 extensions, but these are extensions I
believe should become part of Haskell anyway:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}

module NatTrans where

import Control.Monad.IO.Class
import Control.Monad.Trans.Maybe

class (Functor s, Functor t) = NatTrans s t where
nmap :: forall a. s a - t a
-- Such that: nmap . fmap f = fmap f . nmap

-- In 7.10, this Functor constraint becomes redundant
instance (Functor m, MonadIO m) = NatTrans IO m where
nmap = liftIO

main :: IO ()
main = void $ runMaybeT $ nmap $ print (10 :: Int)

Now if I have a functor of one kind and need another, I reach for nmap in the
same way that I reach for fmap to transform the mapped type.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Poll plea: State of GUI graphics libraries in Haskell

2013-09-27 Thread John Lato
Hi Conal,

If there is a system like you describe, I'm not aware of it.  Part of the
problem is the state of the underlying C libraries:

gtk+ - possible, but suffers from the drawbacks you mention on OSX and is
reportedly difficult to install on windows
wx - somehow I've never been able to build this to my satisfaction on OSX
(meaning a 64-bit build with working wxHaskell)
QT - never tried this, but my impression is the Haskell-QT bindings are a
bit stale

FLTK is probably the surest approach, but it will definitely not look like
a native Mac app.  IMHO FLTK is hideously ugly on any system.  But it is
relatively easy to build.

How much windowing are you looking for?  Would GLFW be an acceptable
starting point?

John L.


On Fri, Sep 27, 2013 at 12:40 AM, Conrad Parker con...@metadecks.orgwrote:

 Hi Conal!

 Yes. I'd be very interested to help get Pan and Vertigo working. Do you
 have a repo somewhere?

 Conrad.


 On 27 September 2013 13:32, Conal Elliott co...@conal.net wrote:

 I'm polling to see whether there are will and expertise to reboot
 graphics and GUIs work in Haskell. I miss working on functional graphics
 and GUIs in Haskell, as I've been blocked for several years (eight?) due to
 the absence of low-level foundation libraries having the following
 properties:

 * cross-platform,
 * easily buildable,
 * GHCi-friendly, and
 * OpenGL-compatible.

 The last several times I tried Gtk2hs, I was unable to compile it on my
 Mac. Years ago when I was able to compile, the GUIs looked and interacted
 like a Linux app, which made them awkward and upleasant to use. wxHaskell
 (whose API and visual appearance I prefered) has for years been
 incompatible with GHCi, in that the second time I open a top-level window,
 the host process (GHCi) dies abruptly. Since my GUI  graphics programs are
 often one-liners, and I tend to experiment a lot, using a full compilation
 greatly thwarts my flow. For many years, I've thought that the situation
 would eventually improve, since I'm far from the only person who wants GUIs
 or graphics from Haskell.

 About three years ago, I built a modern replacement of my old Pan and
 Vertigo systems (optimized high-level functional graphics in 2D and 3D),
 generating screamingly fast GPU rendering code. I'd love to share it with
 the community, but I'm unable to use it even myself.

 Two questions:

 * Am I mistaken about the current status? I.e., is there a solution for
 Haskell GUI  graphics programming that satisfies the properties I'm
 looking for (cross-platform, easily buildable, GHCi-friendly, and
 OpenGL-compatible)?
 * Are there people willing and able to fix this situation? My own
 contributions would be to test and to share high-level composable and
 efficient GUI and graphics libraries on top of a working foundation.

 Looking forward to replies. Thanks,

 -- Conal

 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mystery of an Eq instance

2013-09-24 Thread John Lato
On Tue, Sep 24, 2013 at 11:36 AM, Stijn van Drongelen rhym...@gmail.comwrote:

 On Tue, Sep 24, 2013 at 5:39 PM, Sven Panne svenpa...@gmail.com wrote:

 2013/9/22 Mike Meyer m...@mired.org:
  On Sat, Sep 21, 2013 at 5:28 PM, Bardur Arantsson s...@scientician.net
 
  wrote:
  Trying to make something whose name is Not A Number act like a
  number sounds broken from the start.

 The point here is that IEEE floats are actually more something like a
 Maybe Float, with various Nothings, i.e. the infinities and NaNs,
 which all propagate in a well-defined way.


 So, `Either IeeeFault Float`? ;)


Sort of, but IeeeFault isn't really a zero.   Sometimes they can get back
to a normal Float value:

  Prelude let x = 1.0/0
  Prelude x
  Infinity
  Prelude 1/x
  0.0

Also, IEEE float support doesn't make sense as a library, it needs to be
built into the compiler (ignoring extensible compiler support via the
FFI).  The whole point of IEEE floats is that they're very fast, but in
order to take advantage of that the compiler needs to know about them in
order to use the proper CPU instructions.  Certainly you could emulate them
in software, but then they'd no longer be fast, so there'd be no point to
it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why superclass' instances are bad idea?

2013-09-24 Thread John Lato
This line

instance Monad m = Applicative m where

tells the compiler Every type (of the appropriate kind) is an instance of
Applicative.  And it needs to have a Monad instance as well.

That's what Edward means when he said that it means every Applicative is a
Monad.  Theoretically the statement makes no sense, but that's what this
instance head means.  Everything is Applicative, and it also needs a Monad
instance to use that Applicative.

Consider what happens for something that isn't a Monad, e.g. ZipList.
Since it's not a Monad, it would need its own instance

instance Applicative ZipList where
...

But now you'd need to enable OverlappingInstances, because ZipList matches
both this instance and the general one you've defined above (GHC doesn't
consider constraints when matching instance heads).  OverlappingInstances
is much more problematic than the other extensions because it could (and
almost certainly would in this case) give rise to incoherence (see the
warning under
http://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-extensions.html#instance-overlap
).

You might want to read the wiki page on default superclass instances (
http://ghc.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances) for
further discussion of this problem.

John L.

On Tue, Sep 24, 2013 at 12:17 PM, Wvv vite...@rambler.ru wrote:

 I suggest to add superclass' instances into  libraries.

 http://ghc.haskell.org/trac/ghc/ticket/8348

 In brief, we could write next:

 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE UndecidableInstances #-}
 
 instance Monad m = Applicative m where
 pure  = return
 (*) = ap
 
 instance Monad m = Functor m where
 fmap = liftM
 
 instance Monad m = Bind m where
 (-) = flip (=)
 B.join = M.join

 this code is valid!

 I've already defined 3 superclassses for Monad: Functor, Applicative and
 Bind!

 Similar idea said Edward Kmett in 2010 (founded by monoidal) (

 http://stackoverflow.com/questions/3213490/how-do-i-write-if-typeclass-a-then-a-is-also-an-instance-of-b-by-this-definit/3216937#3216937
 )

 And he said but effectively what this instance is saying is that every
 Applicative should be derived by first finding an instance for Monad, and
 then dispatching to it. So while it would have the intention of saying that
 every Monad is Applicative (by the way the implication-like = reads) what
 it actually says is that every Applicative is a Monad, because having an
 instance head 't' matches any type. In many ways, the syntax for 'instance'
 and 'class' definitions is backwards.

 Why? I don't understand.
 Not every Applicative is a Monad, but every Monad is Applicative



 --
 View this message in context:
 http://haskell.1045720.n5.nabble.com/Why-superclass-instances-are-bad-idea-tp5737056.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.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] Creating a local Hoogle ...

2013-09-23 Thread John Wiegley
 aditya siram aditya.si...@gmail.com writes:

 Combining 4263 databases hoogle: embroidery.hoo: openFile: resource
 exhausted (Too many open files)

 Any help is appreciated. Thanks!

I created the 'rehoo' utility to solve this very problem.  Change directory to
where your .hoo files are, and run:

rehoo -j4 -c64 .

Where 4 is for a 4-core machine.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-16 Thread John Lato
On Fri, Sep 13, 2013 at 12:48 AM, Michael Snoyman mich...@snoyman.comwrote:




 On Thu, Sep 12, 2013 at 2:37 AM, John Lato jwl...@gmail.com wrote:

 I didn't see this message and replied privately to Michael earlier, so
 I'm replicating my comments here.


 Sorry about that, I wrote to you privately first and then thought this
 might be a good discussion for the cafe.


 1.  Sooner or later I expect you'll want something like this:

 class LooseMap c el el' where

   lMap :: (el - el') - c el - c el'



  It covers the case of things like hashmaps/unboxed vectors that have
 class constraints on elements.  Although maybe LooseFunctor or LFunctor is
 a better name.

 Probably something similar for Traversable would be good also, as would a
 default instance in terms of Functor.


 That's interesting. It's quite similar to the CanMap[1] class in
 classy-prelude or Each from lens, except it can drop a type parameter and
 the fundeps by requiring the container to be polymorphic. If we're willing
 to use more exotic extensions, ConstraintKinds could be useful as well:

 class ConstrainedMap t where
 type MapConstraint t e :: Constraint
 cMap :: (MapConstraint t e1, MapConstraint t e2) = (e1 - e2) - t e1
 - t e2
 instance ConstrainedMap Set.Set where
 type MapConstraint Set.Set e = Ord e
 cMap = Set.map

 One reason I'd definitely not want to call this anything with the name
 Functor in it is because Set.map can violate the Functor laws, in
 particular:

 Set.map (f . g) /= Set.map f . Set.map g

 I believe the only law that could be applied to Set.map would be:

 Set.map f = Set.fromList . List.map f . Set.toList

 I would presume this would generalize to any other possible instance.


Would it make more sense to just say that all instances must obey the
Functor laws, thereby not allowing the Set instance?  That might make it
easier to reason about using the class.  Although I've never needed that
when I've used it in the past, so I guess whichever you think is more
useful is fine by me.



 One final idea would be to take your LooseMap and apply the same kind of
 monomorphic conversion the rest of the library uses:

 class MonoLooseMap c1 c2 | c1 - c2, c2 - c1 where
 mlMap :: (Element c1 - Element c2) - c1 - c2
 instance (Ord e1, Ord e2) = MonoLooseMap (Set.Set e1) (Set.Set e2) where
 mlMap = Set.map

 Of all of them, ConstrainedMap seems like it would be the most
 user-friendly, as error messages would just have a single type parameter.
 But I don't have any strong leanings.


I agree that ConstrainedMap would likely be the most user-friendly.  It
also seems to best express the actual relationship between the various
components, so it would be my preferred choice.


 [1]
 http://haddocks.fpcomplete.com/fp/7.4.2/20130829-168/classy-prelude/ClassyPrelude-Classes.html#t:CanMap


 2.  IMHO cMapM_ (and related) should be part of the Foldable class.  This
 is entirely for performance reasons, but there's no downside since you can
 just provide a default instance.


 Makes sense to me, done. By the way, this can't be done for sum/product,
 because those require a constraint on the Element.


 3.  I'm not entirely sure that the length* functions belong here.  I
 understand why, and I think it's sensible reasoning, and I don't have a
 good argument against it, but I just don't like it.  With those, and
 mapM_-like functions, it seems that the foldable class is halfway to being
 another monolithic ListLike.  But I don't have any better ideas either.


 I agree here, but like you said in (2), it's a performance concern. The
 distinction I'd make from ListLike is that you only have to define
 foldr/foldl to get a valid instance (and even that could be dropped to just
 foldr, except for conflicts with the default signatures extension).




 As to the bikeshed color, I would prefer to just call the classes
 Foldable/Traversable.  People can use qualified imports to disambiguate
 when writing instances, and at call sites client code would never need
 Data.{Foldable|Traversable} and can just use these versions instead.  I'd
 still want a separate name for Functor though, since it's in the Prelude,
 so maybe it's better to be consistent.  My $.02.


 I prefer avoiding the name conflict, for a few reasons:

- In something like ClassyPrelude, we can export both typeclasses
without a proper if they have separate names.
- Error messages and documentation will be clearer. Consider how the
type signature `ByteString - foo` doesn't let you know whether it's a
strict or lazy bytestring.
- I got specific feedback from Edward that it would be easier to
include instances for these classes if the names didn't clash with standard
terminology.
- It leaves the door open for including this concept upstream in the
future, even if that's not the goal for now.

 Sounds reasonable.




 On Wed, Sep 11, 2013 at 3:25 PM, Michael Snoyman mich...@snoyman.comwrote:

 That's

Re: [Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-16 Thread John Lato
On Mon, Sep 16, 2013 at 4:57 AM, Michael Snoyman mich...@snoyman.comwrote:




 On Mon, Sep 16, 2013 at 10:34 AM, John Lato jwl...@gmail.com wrote:

 On Fri, Sep 13, 2013 at 12:48 AM, Michael Snoyman mich...@snoyman.comwrote:




 On Thu, Sep 12, 2013 at 2:37 AM, John Lato jwl...@gmail.com wrote:

 I didn't see this message and replied privately to Michael earlier, so
 I'm replicating my comments here.


 Sorry about that, I wrote to you privately first and then thought this
 might be a good discussion for the cafe.


 1.  Sooner or later I expect you'll want something like this:

 class LooseMap c el el' where

   lMap :: (el - el') - c el - c el'






  It covers the case of things like hashmaps/unboxed vectors that have
 class constraints on elements.  Although maybe LooseFunctor or LFunctor is
 a better name.

 Probably something similar for Traversable would be good also, as would
 a default instance in terms of Functor.


 That's interesting. It's quite similar to the CanMap[1] class in
 classy-prelude or Each from lens, except it can drop a type parameter and
 the fundeps by requiring the container to be polymorphic. If we're willing
 to use more exotic extensions, ConstraintKinds could be useful as well:

 class ConstrainedMap t where
 type MapConstraint t e :: Constraint
 cMap :: (MapConstraint t e1, MapConstraint t e2) = (e1 - e2) - t
 e1 - t e2
 instance ConstrainedMap Set.Set where
 type MapConstraint Set.Set e = Ord e
 cMap = Set.map

 One reason I'd definitely not want to call this anything with the name
 Functor in it is because Set.map can violate the Functor laws, in
 particular:

 Set.map (f . g) /= Set.map f . Set.map g

 I believe the only law that could be applied to Set.map would be:

 Set.map f = Set.fromList . List.map f . Set.toList

 I would presume this would generalize to any other possible instance.


 Would it make more sense to just say that all instances must obey the
 Functor laws, thereby not allowing the Set instance?  That might make it
 easier to reason about using the class.  Although I've never needed that
 when I've used it in the past, so I guess whichever you think is more
 useful is fine by me.



 I think I just made a bad assumption about what you were proposing. If I
 was going to introduce a typeclass like this, I'd want it to support `Set`,
 since IME it's the most commonly used polymorphic `map` operation that has
 constraints. (Note that HashMap and Map are in fact Functors, since mapping
 only affects their values, which are unconstrained.) I don't really have
 any strong feelings on this topic, just that it would be nice to have *
 some* kind of a map-like function that worked on Set and HashSet.


Ok, understood.  I most often use this with Data.Vector.Unboxed and
Data.Vector.Storable, and that it would be useful for Set didn't really
occur to me.

Given that, I agree that a non-Functor name is a workable choice.





 One final idea would be to take your LooseMap and apply the same kind of
 monomorphic conversion the rest of the library uses:

 class MonoLooseMap c1 c2 | c1 - c2, c2 - c1 where
 mlMap :: (Element c1 - Element c2) - c1 - c2
 instance (Ord e1, Ord e2) = MonoLooseMap (Set.Set e1) (Set.Set e2) where
 mlMap = Set.map

 Of all of them, ConstrainedMap seems like it would be the most
 user-friendly, as error messages would just have a single type parameter.
 But I don't have any strong leanings.


 I agree that ConstrainedMap would likely be the most user-friendly.  It
 also seems to best express the actual relationship between the various
 components, so it would be my preferred choice.


 [1]
 http://haddocks.fpcomplete.com/fp/7.4.2/20130829-168/classy-prelude/ClassyPrelude-Classes.html#t:CanMap


 2.  IMHO cMapM_ (and related) should be part of the Foldable class.
 This is entirely for performance reasons, but there's no downside since you
 can just provide a default instance.


 Makes sense to me, done. By the way, this can't be done for sum/product,
 because those require a constraint on the Element.


 3.  I'm not entirely sure that the length* functions belong here.  I
 understand why, and I think it's sensible reasoning, and I don't have a
 good argument against it, but I just don't like it.  With those, and
 mapM_-like functions, it seems that the foldable class is halfway to being
 another monolithic ListLike.  But I don't have any better ideas either.


 I agree here, but like you said in (2), it's a performance concern. The
 distinction I'd make from ListLike is that you only have to define
 foldr/foldl to get a valid instance (and even that could be dropped to just
 foldr, except for conflicts with the default signatures extension).




 As to the bikeshed color, I would prefer to just call the classes
 Foldable/Traversable.  People can use qualified imports to disambiguate
 when writing instances, and at call sites client code would never need
 Data.{Foldable|Traversable} and can just use

Re: [Haskell-cafe] Bytestring map/zipWith rationale

2013-09-12 Thread John Lato
Carter: we don't have both.  We have one function from each category.  My
guess is nobody's ever really needed a really fast zipWith ::
(Word8-Word8-Word8) - ByteString - ByteString - ByteString; that's the
only reason I can think of for its omission.


On Thu, Sep 12, 2013 at 10:45 AM, Carter Schonwald 
carter.schonw...@gmail.com wrote:

 Scott: benchmark the two and you'll see why we have both :-)


 On Thursday, September 12, 2013, Scott Lawrence wrote:

 On Thu, 12 Sep 2013, Tom Ellis wrote:

  On Thu, Sep 12, 2013 at 09:21:20AM -0400, Scott Lawrence wrote:

 Something's always bothered me about map and zipWith for ByteString.
 Why is it

 map :: (Word8 - Word8) - ByteString - ByteString

 but

 zipWith :: (Word8 - Word8 - a) - ByteString - ByteString - [a]


 Well, what if you wanted to zipWith a function of type Word8 - Word8 -
 Foo instead of Word8 - Word8 - Word8?


 Then I would do what I do with map, and call `unpack` first.

 Either of the two options is usable:

  map :: (Word8 - Word8) - ByteString - ByteString
  zipWith :: (Word8 - Word8 - Word8) - ByteString - ByteString -
 ByteString
(or)
  map :: (Word8 - a) - ByteString - [a]
  zipWith :: (Word8 - Word8 - a) - ByteString - ByteString - [a]

 I just don't understand why we have one from each.

 --
 Scott Lawrence
 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-11 Thread John Lato
I didn't see this message and replied privately to Michael earlier, so I'm
replicating my comments here.

1.  Sooner or later I expect you'll want something like this:

class LooseMap c el el' where
  lMap :: (el - el') - c el - c el'

It covers the case of things like hashmaps/unboxed vectors that have class
constraints on elements.  Although maybe LooseFunctor or LFunctor is a
better name.

Probably something similar for Traversable would be good also, as would a
default instance in terms of Functor.

2.  IMHO cMapM_ (and related) should be part of the Foldable class.  This
is entirely for performance reasons, but there's no downside since you can
just provide a default instance.

3.  I'm not entirely sure that the length* functions belong here.  I
understand why, and I think it's sensible reasoning, and I don't have a
good argument against it, but I just don't like it.  With those, and
mapM_-like functions, it seems that the foldable class is halfway to being
another monolithic ListLike.  But I don't have any better ideas either.

As to the bikeshed color, I would prefer to just call the classes
Foldable/Traversable.  People can use qualified imports to disambiguate
when writing instances, and at call sites client code would never need
Data.{Foldable|Traversable} and can just use these versions instead.  I'd
still want a separate name for Functor though, since it's in the Prelude,
so maybe it's better to be consistent.  My $.02.


On Wed, Sep 11, 2013 at 3:25 PM, Michael Snoyman mich...@snoyman.comwrote:

 That's really funny timing. I started work on a very similar project just
 this week:

 https://github.com/snoyberg/mono-traversable

 It's not refined yet, which is why I haven't discussed it too publicly,
 but it's probably at the point where some review would make sense. There's
 been a bit of a discussion on a separate Github issue[1] about it.

 A few caveats:

- The names are completely up for debate, many of them could be
improved.
- The laws aren't documented yet, but they mirror the laws for the
polymorphic classes these classes are based on.
- The Data.MonoTraversable module is the main module to look at. The
other two are far more nascent (though I'd definitely appreciate feedback
people have on them).

 I think this and mono-foldable have a lot of overlap, I'd be interested to
 hear what you think in particular John.

 Michael

 [1] https://github.com/snoyberg/classy-prelude/issues/18


 On Wed, Sep 11, 2013 at 11:05 PM, John Lato jwl...@gmail.com wrote:

 I agree with everything Edward has said already.  I went through a
 similar chain of reasoning a few years ago when I started using ListLike,
 which provides a FoldableLL class (although it uses fundeps as ListLike
 predates type families).  ByteString can't be a Foldable instance, nor do I
 think most people would want it to be.

 Even though I would also like to see mapM_ in bytestring, it's probably
 faster to have a library with a separate monomorphic Foldable class.  So I
 just wrote one:

 https://github.com/JohnLato/mono-foldable
 http://hackage.haskell.org/package/mono-foldable

 Petr Pudlak has done some work in this area.  A big problem is that
 foldM/mapM_ are typically implemented in terms of Foldable.foldr (or
 FoldableLL), but this isn't always optimal for performance.  They really
 need to be part of the type class so that different container types can
 have specialized implementations.  I did that in mono-foldable, using
 Artyom's map implementation (Artyom, please let me know if you object to
 this!)

 pull requests, forks, etc all welcome.

 John L.


 On Wed, Sep 11, 2013 at 1:29 PM, Edward Kmett ekm...@gmail.com wrote:

 mapM_ is actually implemented in terms of Foldable, not Traversable, and
 its implementation in terms of folding a ByteString is actually rather slow
 in my experience doing so inside lens and isn't much faster than the naive
 version that was suggested at the start of this discussion.

 But as we're not monomorphizing Foldable/Traversable, this isn't a think
 that is able to happen anyways.

 -Edward


 On Wed, Sep 11, 2013 at 2:25 PM, Henning Thielemann 
 lemm...@henning-thielemann.de wrote:


 On Wed, 11 Sep 2013, Duncan Coutts wrote:

  For mapM etc, personally I think a better solution would be if
 ByteString and Text and other specialised containers could be an
 instance of Foldable/Traversable. Those classes define mapM etc but
 currently they only work for containers that are polymorphic in their
 elements, so all specialised containers are excluded. I'm sure there
 must be a solution to that (I'd guess with type families) and that
 would
 be much nicer than adding mapM etc to bytestring itself. We would then
 just provide efficient instances for Foldable/Traversable.


 I'd prefer to keep bytestring simple with respect to the number of type
 extensions. Since you must implement ByteString.mapM anyway, you can plug
 this into an instance definition of Traversable

[Haskell-cafe] This is a mail system test, please ignore

2013-09-10 Thread John Wiegley
Testing the new e-mail services at haskell.org.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Please excuse brief service disruption

2013-09-10 Thread John Wiegley
The e-mail services at haskell.org were switched from exim4 to postfix
tonight, please excuse the service disruption.  For about one hour e-mails
were not being accepted to the mailing lists.  All should be resolved now.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: New syntax for Haskell

2013-09-10 Thread John Wiegley
 Niklas Hambüchen m...@nh2.me writes:

 Code written in cucumber syntax is concise and easy to read

concise |kənˈsīs|, adj.

giving a lot of information clearly and in a few words; brief but
comprehensive.

Compare:

Scenario: Defining the function foldl
  Given I want do define foldl
  Which has the type (in brackets) a to b to a (end of brackets),
 to a, to list of b, to a
  And my arguments are called f, acc, and l
  When l is empty
  Then the result better be acc
  Otherwise l is x cons xs
  Then the result should be foldl f (in brackets) f acc x
(end of brackets) xs

To:

foldl :: (a - b - a) - a - [b] - a
foldl f z [] = z
foldl f z (x:xs) = foldl f (f z x) xs

How is that more concise or preferable?

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FLTK GUI Binding in progress. Call for participation.

2013-09-08 Thread John Lask

On 9/09/2013 7:09 AM, aditya siram wrote:

Hi all,
I'm working on a FLTK [1] GUI binding [2]. The attraction of FLTK is that


there is an existing binding on hackage:

hs-fltk library: Binding to GUI library FLTK


which I understand is quite serviceable. Perhaps effort could be 
directed on making improvements (should they be required) to this rather 
than duplicating existing functionality.




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


Re: [Haskell-cafe] Unary functions and infix notation

2013-09-06 Thread John Lato
The observation that this only applies to functions with a polymorphic
return type is key.

  id :: a - a

This can be instantiated at

  id' :: (a-b) - (a-b)
  id' :: (a-b) - a - b-- these are the same

What this means is that id is a function with arity-2 whenever the first
argument is arity-1, and generally id is a function of arity x+1 where x is
the argument arity.  Incidentally, this is exactly the same as the ($)
operator.

John L.


On Fri, Sep 6, 2013 at 10:04 AM, Johannes Emerich johan...@emerich.dewrote:

 As is well known, any binary function f can be turned into an infix
 operator by surrounding it with backticks:

 f a b   -- prefix application
 a `f` b -- infix application

 It is then possible to take left and right sections, i.e. partially
 applying f:

 (a `f`) -- equivalent to \b - a `f` b
 (`f` b) -- equivalent to \a - a `f` b

 This extends relatively naturally to functions of arity greater than two,
 where usage of a function in infix notation produces a binary operator that
 returns a function of arity n-2.

 Weirdly, however, infix notation can also be used for unary functions with
 polymorphic types, as the following ghci session shows:

Prelude :t (`id` 1)
(`id` 1) :: Num a = (a - t) - t
Prelude (`id` 1) (\y - show y ++ .what)
1.what

 Desugaring of an equivalent source file shows that id is applied to the
 anonymous function, which is then applied to 1.

 The following example of a function that is not polymorphic in its return
 type behaves closer to what I would have expected: It does not work.

Prelude let z = (\y - True) :: a - Bool
Prelude :t (`z` True)

interactive:1:2:
The operator `z' takes two arguments,
but its type `a0 - Bool' has only one
In the expression: (`z` True)

 What is the purpose/reason for this behaviour?

 Thank you,
 --Johannes
 ___
 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] On Markdown in Haddock and why it's not going to happen

2013-09-02 Thread John MacFarlane
When the proposal was first being discussed, I suggested that instead of
adding markdown support to haddock, one might enhance the existing
haddock markup, making it more expressive, so that it could encode the same
range of structural features as markdown.  If I'm not mistaken, currently
haddock doesn't allow list items with multiple paragraphs or other block
elements, or nested lists, or images, or blockquotes.  This makes it
impossible to create a pandoc writer for haddock markup (we already have a
haddock reader, soon to be released).

With a pandoc writer for haddock, one could write longer documentation sections
(e.g. tutorials) in markdown and convert them to haddock for inclusion in
source code.  This should help people who don't like haddock markup or don't
want to learn it.  With the reader, haddock comments can already be converted
into other formats.

I haven't been following your work, but do I understand correctly
that you've been making haddock markup more expressive and rational?
Has this gotten to the point where a pandoc writer would be feasible?

John

+++ Mateusz Kowalczyk [Aug 30 13 02:30 ]:
 Greetings café,
 
 Perhaps some saddening news for Markdown fans out there. As you might
 remember, there was a fair amount of push for having Markdown as an
 alternate syntax for Haddock.
 
 Unfortunately, this is probably not going to happen for reasons listed
 on the post I just published at [1].
 
 This thread is meant to be for discussion about the post as many people,
 myself included, felt that Markdown would be a nice thing to have.
 
 I feel like I covered the topic fairly well on the post but feel free to
 give suggestions or ask questions.
 
 I would also like to remind you that if there's something that you'd
 like to see in Haddock or something that you feel is broken, a good way
 express this is to make a ticket on the Haddock Trac[2].
 
 I will close the relevant Markdown ticket on the Trac[3] in about 3
 days, unless someone can come up with a reasonable solution that meets
 the initial intent of this part of the project: a widely known markup
 format that could be used as an alternate syntax for Haddock so that
 it's possible to write the documentation without learning the vanilla
 syntax itself.
 
 [1]:
 http://fuuzetsu.co.uk/blog/posts/2013-08-30-why-Markdown-in-Haddock-can't-happen.html
 
 [2]: http://trac.haskell.org/haddock
 
 [3]: http://trac.haskell.org/haddock/ticket/244
 -- 
 Mateusz K.
 
 ___
 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] Fw: Re: On Markdown in Haddock and why it's not going to happen

2013-09-02 Thread John MacFarlane
+++ Mateusz Kowalczyk [Sep 02 13 21:34 ]:
 On 02/09/13 19:43, John MacFarlane wrote:
  When the proposal was first being discussed, I suggested that instead of
  adding markdown support to haddock, one might enhance the existing
  haddock markup, making it more expressive, so that it could encode the same
  range of structural features as markdown.  If I'm not mistaken, currently
  haddock doesn't allow list items with multiple paragraphs or other block
  elements, or nested lists, or images, or blockquotes.  
 Paragraph level elements are indeed not allowed in lists. The list
 contents are currently (that is, on my working branch) allowed to be:
 monospace (delimited by @), anchors, identifiers, module names,
 pictures, URLs, bold, emphasis, HTML escape codes, regular strings. Note
 that if a monospaced string is the only element of the list content, it
 gets turned into a code block.
 
 I'm not sure what you mean by block elements.

I mean things like paragraphs, blockquotes, code blocks, other lists.

In markdown you can have a list item that contains these things:

1.  This is my first list item.

Second paragraph of first list item. Some code:

foo = bar $ baz * 2.0

2.  This is my second list item.

* Sublist item one
* Sublist item two

3.  This is my third list item.  Someone said:

 We want markdown support in haddock!

In Haddock, last I looked, you couldn't do any of this...

In your original message, you emphasized features of Haddock that
don't exist in standard markdown and would require extensions
(definition lists, automatic links to Haskell identifiers, etc.).

But in many other ways, markdown is much more expressive than
Haddock markup, as the example above illustrates.  The changes that
would be needed to Haddock to allow it to express what can be expressed
in markdown are much bigger, I think, than the changes that would be
needed to markdown to allow it to express what can be expressed in
Haddock.



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


Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-27 Thread John Lato
IMHO it's perfectly reasonable to expect sequence/replicateM/mapM to be
able to handle a list of ~1e6 elements in the Unescapable Monad (i.e. IO).
All the alternate implementations in the world won't be as handy as
Prelude.sequence, and no amount of documentation will prevent people from
running into this headlong*.  So unless there's a downside to upping the
stack size limitation I'm unaware of, +1 to that suggestion from me.

John
[1] Most people are physically incapable of reading documents that explain
why what they want to do won't work.  Even if people did read the
documentation, I suspect that the people most in need of the information
would be the least likely to understand how it applies to their situation.



On Tue, Aug 27, 2013 at 9:19 PM, John Alfred Nathanael Chee 
cheech...@gmail.com wrote:

 This is somewhat related: http://ghc.haskell.org/trac/ghc/ticket/4219

 This also solves the concrete problem you gave in your original post
 (in reverse order):

 import Control.Monad
 import System.Random

 sequencel :: Monad m = [m a] - m [a]
 sequencel = foldM (\tail m - (\x - return $ x : tail) = m) []

 main :: IO ()
 main = print = sequencel (replicate 100 (randomIO :: IO Integer))

 Following on Reid's point, maybe it's worth noting in the
 documentation that replicateM, mapM, and sequence are not tail
 recursive for Monads that define (=) as strict in the first
 argument?

 On Tue, Aug 27, 2013 at 6:07 AM, Niklas Hambüchen m...@nh2.me wrote:
  On 27/08/13 20:37, Patrick Palka wrote:
  You can use ContT to force the function to use heap instead of stack
  space, e.g. runContT (replicateM 100 (lift randomIO)) return
 
  That is interesting, and works.
 
  Unfortunately its pure existence will not fix sequence, mapM etc. in
 base.
 
  ___
  Libraries mailing list
  librar...@haskell.org
  http://www.haskell.org/mailman/listinfo/libraries



 --
 Love in Jesus Christ, John Alfred Nathanael Chee
 http://www.biblegateway.com/
 http://web.cecs.pdx.edu/~chee/

 ___
 Libraries mailing list
 librar...@haskell.org
 http://www.haskell.org/mailman/listinfo/libraries

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


Re: [Haskell-cafe] definition of the term combinator

2013-08-23 Thread John Wiegley
 Jason Dagit dag...@gmail.com writes:

 Where can I find a formal and precise definition of the term
 combinator,

A function that uses nothing but its arguments.

 as a term used by the Haskell community to describe something?

I find that Haskellers often use combinator to mean a function that makes new
functions out of other functions, which it can often do as a pure combinator,
but isn't always a combinator per se.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] Yet Another Forkable Class

2013-08-22 Thread John ExFalso
To be honest I'm not so sure about these effects... Simply the fact that
the Member class needs -XOverlappingInstances means that we cannot have
duplicate or polymorphic effects. It will arbitrarily pick the first match
in the former and fail to compile in the latter case.

Furthermore I don't really understand the way open sums are implemented.
These unions should be disjoint, but the way they're implemented in the
paper they try to be true unions which cannot be done as that would need
type equality (-XOverlappingInstances is a hack around this)

A correct disjoint open sum would behave well with duplicate and
polymorphic types in the type list. For example we should be able to
project the open sum equivalent of Either String String into the second
String but we cannot with the implementation in the paper. This means we
need to ~index~ the type list instead of picking the result type and
trying for equality with each entry. Something like this:
http://lpaste.net/92069

Of course this is very inconvenient and simply replaces the monad
transformers' lifts with a static index into the effect list.
In general I think there is no convenient way of stacking effects that is
also type safe. At some point we have to disambiguate which effect we are
trying to use one way or the other. The implementation in the paper simply
picks a heuristic and chooses the first effect that seems to match and
discards the others.



On 22 August 2013 12:15, Alberto G. Corona agocor...@gmail.com wrote:

 The paper is very interesting:

 http://www.cs.indiana.edu/~sabry/papers/exteff.pdf

 It seems that the approach is mature enough and it is better in every way
 than monad transformers, while at the same time the syntax may become
 almost identical to MTL for many uses.

 I only expect to see the library in Hackage with all the blessings, and
 with all the instances of the MTL classes in order to make the transition
 form monad transformers  to ExtEff as transparent as possible


 2013/8/22 o...@okmij.org


 Perhaps effect libraries (there are several to choose from) could be a
 better answer to Fork effects than monad transformers. One lesson from
 the recent research in effects is that we should start thinking what
 effect we want to achieve rather than which monad transformer to
 use. Using ReaderT or StateT or something else is an implementation
 detail. Once we know what effect to achieve we can write a handler, or
 interpreter, to implement the desired operation on the World, obeying
 the desired equations. And we are done.

 For example, with ExtEff library with which I'm more familiar, the
 Fork effect would take as an argument a computation that cannot throw
 any requests. That means that the parent has to provide interpreters
 for all child effects. It becomes trivially to implement:

  Another example would be a child that should not be able to throw
 errors as
  opposed to the parent thread.
 It is possible to specify which errors will be allowed for the child
 thread (the ones that the parent will be willing to reflect and
 interpret). The rest of errors will be statically prohibited then.

  instance (Protocol p) = Forkable (WebSockets p) (ReaderT (Sink p) IO)
 where
  fork (ReaderT f) = liftIO . forkIO . f = getSink

 This is a good illustration of too much implementation detail. Why do we
 need to know of (Sink p) as a Reader layer? Would it be clearer to
 define an Effect of sending to the socket? Computation's type will
 make it patent the computation is sending to the socket.
 The parent thread, before forking, has to provide a handler for that
 effect (and the handler will probably need a socket).

 Defining a new class for each effect is possible but not needed at
 all. With monad transformers, a class per effect is meant to hide the
 ordering of transformer layers in a monad transformer stack. Effect
 libraries abstract over the implementation details out of the
 box. Crutches -- extra classes -- are unnecessary. We can start by
 writing handlers on a case-by-case basis. Generalization, if any,
 we'll be easier to see. From my experience, generalizing from concrete
 cases is easier than trying to write a (too) general code at the
 outset. Way too often, as I read and saw, code that is meant to be
 reusable ends up hardly usable.




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




 --
 Alberto.

 ___
 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] Yet Another Forkable Class

2013-08-21 Thread John ExFalso
TLDR: New forkable monad/transformer suggestion
http://pastebin.com/QNUVL12v(hpaste is down)

Hi,

There are a dozen packages on hackage defining a class for monads that can
be forked, however none of these are modular enough to be useful in my
opinion.

In particular the following are not addressed:
1. Cases when the child thread's monad is different from the parent's
2. Monad transformers (this is somewhat addressed with
Control.Monad.Trans.Control)

I will try to demonstrate both issues with an example.

1. WebSockets

WebSockets is a monad that cannot itself be forked. This is because at any
given time there should only be a single thread listening on a websocket.
However there is a reasonable monad that can be forked off, namely one that
can send to the websocket - one that has access to the Sink.

So first off a Forkable class should not look like this:

class (MonadIO m, MonadIO n) = Forkable m where
fork :: m () - m ThreadId

But rather like this:

class Forkable m n where
fork :: n () - m ThreadId

For our example the instance would be

instance (Protocol p) = Forkable (WebSockets p) (ReaderT (Sink p) IO) where
fork (ReaderT f) = liftIO . forkIO . f = getSink

Another example would be a child that should not be able to throw errors as
opposed to the parent thread.

2. ReaderT

Continuing from the previous example to demonstrate the need to distinguish
forkable transformers.
Say we have some shared state S that both parent and child should have
access to:

type Parent p = ReaderT (TVar S) (WebSockets p)
type Child p = ReaderT (TVar S) (ReaderT (Sink p) IO)

The forkability of Child from Parent should be implied, however with
Forkable we have to write a separate instance.

So what I suggest is a second class:

class ForkableT t where
forkT :: (Forkable m n) = t n () - t m ThreadId

And then:

instance ForkableT (ReaderT r) where
forkT (ReaderT f) = ReaderT $ fork . f

We can also introduce a default for Forkable that uses a ForkableT instance:

class (MonadIO m, MonadIO n) = Forkable m n where
fork :: n () - m ThreadId
default fork :: ForkableT t = t n () - t m ThreadId
fork = forkT

instance (Forkable m n) = Forkable (ReaderT r m) (ReaderT r n)

This means Child is automatically Forkable from Parent, no need to write a
specific case for our specific monads (and if we newtype it we can use
-XGeneralizedNewtypeDeriving)

Note how MonadTransControl already solves the specific problem of lifting a
forking operation into ReaderT. However consider ResourceT from
Control.Monad.Resource: it is basically a ReaderT, however in order to
safely deallocate resources when sharing reference counting is needed. This
means a simple lift would not suffice.

We can nevertheless provide a default ForkableT based on MonadTransControl:
class ForkableT t where
forkT :: (Forkable m n) = t n () - t m ThreadId
default forkT :: (MonadTransControl t, Forkable m n) = t n () - t m
ThreadId
forkT t = liftWith $ \run - fork $ run t  return ()

Actually resourcet's reference counting resourceForkIO also nicely
demonstrates the first problem:
type Parent p = ResourceT (WebSockets p)
type Child p = ResourceT (ReaderT (Sink p) IO)

Note how we cannot use resourceForkIO without touching the underlying
monads.

What do you think? Is there already an established way of modular forking?
I wouldn't like to litter hackage with another unusable Forkable class:)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] inv f g = f . g . f

2013-08-17 Thread John Wiegley
 Dan Burton danburton.em...@gmail.com writes:

 under reversed (take 10) ['a'.. 'z']
 qrstuvwxyz

Excellent, thanks!

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] ANNOUNCE: tasty, a new testing framework

2013-08-06 Thread John Wiegley
 Roman Cheplyaka r...@ro-che.info writes:

 I am pleased to announce the first release of tasty, a new testing framework
 for Haskell. It is meant to be a successor to test-framework (which is
 unmaintained).

It would be nice to see a comparison of the various test frameworks and why
one might select one over another.  I use hspec currently (which also
integrates with HUnit, QuickCheck, etc.), and couldn't tell at a glance what
tasty might offer.  And I particularly dislike writing tests inside of a
gigantic list; I much prefer the monadic style of hspec.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] ScopedTypeVariables

2013-08-06 Thread John Wiegley
 Evan Laforge qdun...@gmail.com writes:

 Would it make sense to split it into a separate extension like
 TypesOnArguments so I can more accurately express my deviation from
 haskell2010 orthodoxy?  Or is there some deeper tie between scoped
 type variables and annotations on arguments?

I've also wondered why I have to enable ScopedTypeVariables in those cases --
when I'm not turning it on to scope any type variables, but just to make
annotations possible in more places.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-23 Thread John van Groningen

On 22-7-2013 17:09, i c wrote:

On Wed, Jul 10, 2013 at 9:47 AM,o...@okmij.org  wrote:



Jon Fairbairn wrote:

It just changes forgetting to use different variable names because of
recursion (which is currently uniform throughout the language) to
forgetting to use non recursive let instead of let.


Let me bring to the record the message I just wrote on Haskell-cafe

http://www.haskell.org/pipermail/haskell-cafe/2013-July/109116.html

and repeat the example:

In OCaml, I can (and often do) write

 let (x,s) = foo 1 [] in
 let (y,s) = bar x s in
 let (z,s) = baz x y s in ...

In Haskell I'll have to uniquely number the s's:

 let (x,s1)  = foo 1 [] in
 let (y,s2)  = bar x s1 in
 let (z,s3)  = baz x y s2 in ...

and re-number them if I insert a new statement.


Not if you use pattern guards:

{-# LANGUAGE PatternGuards #-}

| ~(x,s) = foo 1 []
, ~(y,s) = bar x s
, ~(z,s) = baz x y s
= ...


Usage of shadowing is generally bad practice. It is error-prone. Hides
obnoxious bugs like file descriptors leaks.
The correct way is to give different variables that appear in different
contexts a different name, although this is arguably less convenient and
more verbose.




___
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] Proposal: Non-recursive let

2013-07-23 Thread John van Groningen


| ~(x,s) = foo 1 []
, ~(y,s) = bar x s
, ~(z,s) = baz x y s
= ...

in my previous message should be:

| ~(x,s) - foo 1 []
, ~(y,s) - bar x s
, ~(z,s) - baz x y s
= ...

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


Re: [Haskell-cafe] catching IO errors in a monad transformer stack

2013-07-22 Thread John Lato
I don't think there's anything necessarily wrong with ekmett's exceptions
package, but you should be aware that it may not do what you expect:

module Foo where

import Control.Monad.IO.Class
import Control.Monad.Catch
import Control.Exception (ArithException)

f :: CatchT IO String
f = catch (liftIO $ (div 1 0) `seq` return unreachable) (\x - let _ = x
:: ArithException in return caught it)

g = do
x - runCatchT f
print x

f' :: IO String
f' = catch ((div 1 0) `seq` return unreachable) (\x - let _ = x ::
ArithException in return caught it)

g' = do
x - f'
print x

*Foo Control.Exception g
*** Exception: divide by zero
*Foo Control.Exception g'
caught it

I expect this is actually working as designed, but you still may want to be
aware of it.



On Mon, Jul 22, 2013 at 3:45 PM, Eric Rasmussen ericrasmus...@gmail.comwrote:

 Thanks John. I'll try it out, along with Kmett's exceptions package I just
 found:


 http://hackage.haskell.org/packages/archive/exceptions/0.1.1/doc/html/Control-Monad-Catch.html

 I noticed on an issue for lens (https://github.com/ekmett/lens/issues/301)
 they switched to this since MonadCatchIO is deprecated, and it has a more
 general version of catch:


   catch :: Exception e = m a - (e - m a) - m a






 On Sun, Jul 21, 2013 at 6:30 PM, John Lato jwl...@gmail.com wrote:

 I think most people use monad-control these days for catching exceptions
 in monad stacks (http://hackage.haskell.org/package/monad-control-0.3.2.1).
  The very convenient lifted-base package (
 http://hackage.haskell.org/package/lifted-base) depends on it and
 exports a function Control.Exception.Lifted.catch:

 Control.Exception.Lifted.catch :: (MonadBaseControl IO m, Exception e)
   = m a - (e - m a) - m a

 I'd recommend you use that instead of MonadCatchIO.


 On Mon, Jul 22, 2013 at 4:13 AM, Eric Rasmussen 
 ericrasmus...@gmail.comwrote:

 Arie,

 Thanks for calling that out. The most useful part for my case is the
 MonadCatchIO implementation of catch:

 catch :: Exception e = m a - (e - m a) - m a

 Hoogle shows a few similar functions for that type signature, but they
 won't work for the case of catching an IOException in an arbitrary monad.
 Do you happen to know of another approach for catching IOExceptions and
 throwing them in ErrorT?

 Thanks,
 Eric






 On Sun, Jul 21, 2013 at 7:00 AM, Arie Peterson ar...@xs4all.nl wrote:

 On Thursday 18 July 2013 23:05:33 Eric Rasmussen wrote:
  […]
  Would there be any interest in cleaning that up and adding it (or
 something
  similar) to Control.Monad.CatchIO?
  […]

 MonadCatchIO-transformers is being deprecated, as recently GHC has
 removed the
 'block' and 'unblock' functions, rendering the api provided by
 Control.Monad.CatchIO obsolete.


 Regards,

 Arie


 ___
 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 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] catching IO errors in a monad transformer stack

2013-07-21 Thread John Lato
I think most people use monad-control these days for catching exceptions in
monad stacks (http://hackage.haskell.org/package/monad-control-0.3.2.1).
 The very convenient lifted-base package (
http://hackage.haskell.org/package/lifted-base) depends on it and exports a
function Control.Exception.Lifted.catch:

Control.Exception.Lifted.catch :: (MonadBaseControl IO m, Exception e)
  = m a - (e - m a) - m a

I'd recommend you use that instead of MonadCatchIO.


On Mon, Jul 22, 2013 at 4:13 AM, Eric Rasmussen ericrasmus...@gmail.comwrote:

 Arie,

 Thanks for calling that out. The most useful part for my case is the
 MonadCatchIO implementation of catch:

 catch :: Exception e = m a - (e - m a) - m a

 Hoogle shows a few similar functions for that type signature, but they
 won't work for the case of catching an IOException in an arbitrary monad.
 Do you happen to know of another approach for catching IOExceptions and
 throwing them in ErrorT?

 Thanks,
 Eric






 On Sun, Jul 21, 2013 at 7:00 AM, Arie Peterson ar...@xs4all.nl wrote:

 On Thursday 18 July 2013 23:05:33 Eric Rasmussen wrote:
  […]
  Would there be any interest in cleaning that up and adding it (or
 something
  similar) to Control.Monad.CatchIO?
  […]

 MonadCatchIO-transformers is being deprecated, as recently GHC has
 removed the
 'block' and 'unblock' functions, rendering the api provided by
 Control.Monad.CatchIO obsolete.


 Regards,

 Arie


 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Generating Haskell Code out of Haskell AST (GHC API)

2013-07-19 Thread John Blackbox
Thank you!
So, if I'm writing a compiler of custom language, which I want to generate
Haskell AST and further compile it with GHC, you prefer something like
haskell-src-exts
over pure GHC API?


2013/7/19 Antoine Latter aslat...@gmail.com

 The package haskell-src-exts is a lot less intimidating if all you are
 trying to do is programmatically generate Haskell source:

 http://hackage.haskell.org/package/haskell-src-exts

 The base types are here:

 http://hackage.haskell.org/packages/archive/haskell-src-exts/1.13.5/doc/html/Language-Haskell-Exts-Syntax.html#t:Module

 This module has some helper function for generating parts of the AST:

 http://hackage.haskell.org/packages/archive/haskell-src-exts/1.13.5/doc/html/Language-Haskell-Exts-Build.html


 On Thu, Jul 18, 2013 at 1:11 PM, John Blackbox
 blackbox.dev...@gmail.com wrote:
  Hi!
  I dont know GHC API very well, but I want to generate AST of a program
 using
  GHC API.
  Is there any standard method to generate Haskell code out of it?
 (something
  like print_this_for_me_please function? :D
 
  ___
  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] Generating Haskell Code out of Haskell AST (GHC API)

2013-07-19 Thread John Blackbox
I accidentally didn't send that email to haskell-cafe, so I'm pasting it
here also:

Alan - I do NOT want to generate Haskell code. I want only to generate AST
and compile it.
The question about generating the code was only to have a debugging tool
- to see if the generated AST is good - I wanted to generate the Haskell
code only to check if its correct, but normally I would not do it, because
it makes no sense to generate AST - code - AST (by GHC) again etc :)
Additional - I want to connect to GHC's type-checking also and translate
the errors to be appropriate to my language syntax - so maybe the pure GHC
API is the best way to go?


2013/7/19 John Blackbox blackbox.dev...@gmail.com

 Additional - I want to connect to GHC's type-checking also and translate
 the errors to be appropriate to my language syntax.


 2013/7/19 John Blackbox blackbox.dev...@gmail.com

 Alan - I do NOT want to generate Haskell code. I want only to generate
 AST and compile it.
 The question about generating the code was only to have a debugging
 tool - to see if the generated AST is good - I wanted to generate the
 Haskell code only to check if its correct, but normally I would not do it,
 because it makes no sense to generate AST - code - AST (by GHC) again etc
 :)


 2013/7/19 AlanKim Zimmerman alan.z...@gmail.com

 I have not used haskell-src-exts so I may be talking out of turn, but it
 seems that if you want to generate an AST which you then turn into source
 code and compile it makes more sense than using than GHC AST, which has a
 number of wrinkles, including fields that are only valid at certain phases
 of the compilation process.

 For my purposes, in the Haskell Refactorer, I need access to the
 renaming and type-checking, which to my knowledge is not currently
 available in haskell-src-exts, although there is work happening to bring it
 in, e.g. https://github.com/haskell-suite/haskell-names.


 On Fri, Jul 19, 2013 at 10:09 AM, John Blackbox 
 blackbox.dev...@gmail.com wrote:

 Thank you!
 So, if I'm writing a compiler of custom language, which I want to
 generate Haskell AST and further compile it with GHC, you prefer
 something like haskell-src-exts over pure GHC API?


 2013/7/19 Antoine Latter aslat...@gmail.com

 The package haskell-src-exts is a lot less intimidating if all you are
 trying to do is programmatically generate Haskell source:

 http://hackage.haskell.org/package/haskell-src-exts

 The base types are here:

 http://hackage.haskell.org/packages/archive/haskell-src-exts/1.13.5/doc/html/Language-Haskell-Exts-Syntax.html#t:Module

 This module has some helper function for generating parts of the AST:

 http://hackage.haskell.org/packages/archive/haskell-src-exts/1.13.5/doc/html/Language-Haskell-Exts-Build.html


 On Thu, Jul 18, 2013 at 1:11 PM, John Blackbox
 blackbox.dev...@gmail.com wrote:
  Hi!
  I dont know GHC API very well, but I want to generate AST of a
 program using
  GHC API.
  Is there any standard method to generate Haskell code out of it?
 (something
  like print_this_for_me_please function? :D
 
  ___
  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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Not working examples in GHC API documentation

2013-07-18 Thread John Blackbox
Hi!
Please take a look here: http://www.haskell.org/haskellwiki/GHC/As_a_library
The examples are not working. Even the simpelst one:

import GHC

import GHC.Paths ( libdir )

import DynFlags ( defaultLogAction )



main =

defaultErrorHandler defaultLogAction $ do

  runGhc (Just libdir) $ do

dflags - getSessionDynFlags

setSessionDynFlags dflags

target - guessTarget test_main.hs Nothing

setTargets [target]

load LoadAllTargets


throws:


$ ghc -package ghc Main.hs

[1 of 1] Compiling Main ( Main.hs, Main.o )

Main.hs:6:25:

Couldn't match type `DynFlags' with `[Char]'

Expected type: DynFlags.FatalMessager

  Actual type: DynFlags.LogAction

In the first argument of `defaultErrorHandler', namely

  `defaultLogAction'

In the expression: defaultErrorHandler defaultLogAction

In the expression:

  defaultErrorHandler defaultLogAction

  $ do { runGhc (Just libdir)

 $ do { dflags - getSessionDynFlags;

setSessionDynFlags dflags;

 } }

Main.hs:7:7:

Couldn't match expected type `DynFlags.FlushOut'

with actual type `IO SuccessFlag'

In a stmt of a 'do' block:

  runGhc (Just libdir)

  $ do { dflags - getSessionDynFlags;

 setSessionDynFlags dflags;

 target - guessTarget test_main.hs Nothing;

 setTargets [target];

  }

In the second argument of `($)', namely

  `do { runGhc (Just libdir)

$ do { dflags - getSessionDynFlags;

   setSessionDynFlags dflags;

    } }'

In the expression:

  defaultErrorHandler defaultLogAction

  $ do { runGhc (Just libdir)

 $ do { dflags - getSessionDynFlags;

setSessionDynFlags dflags;

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


Re: [Haskell-cafe] Not working examples in GHC API documentation

2013-07-18 Thread John Blackbox
Great, but how can we learn the API, when examples are not working? -.-


2013/7/18 Johan Tibell johan.tib...@gmail.com

 I filed a bug a while back:

 http://ghc.haskell.org/trac/ghc/ticket/7752

 Someone that understands the API needs to fix the doc. :)

 On Thu, Jul 18, 2013 at 7:58 PM, John Blackbox
 blackbox.dev...@gmail.com wrote:
  Hi!
  Please take a look here:
 http://www.haskell.org/haskellwiki/GHC/As_a_library
  The examples are not working. Even the simpelst one:
 
  import GHC
 
  import GHC.Paths ( libdir )
 
  import DynFlags ( defaultLogAction )
 
 
 
  main =
 
  defaultErrorHandler defaultLogAction $ do
 
runGhc (Just libdir) $ do
 
  dflags - getSessionDynFlags
 
  setSessionDynFlags dflags
 
  target - guessTarget test_main.hs Nothing
 
  setTargets [target]
 
  load LoadAllTargets
 
 
 
  throws:
 
 
  $ ghc -package ghc Main.hs
 
  [1 of 1] Compiling Main ( Main.hs, Main.o )
 
  Main.hs:6:25:
 
  Couldn't match type `DynFlags' with `[Char]'
 
  Expected type: DynFlags.FatalMessager
 
Actual type: DynFlags.LogAction
 
  In the first argument of `defaultErrorHandler', namely
 
`defaultLogAction'
 
  In the expression: defaultErrorHandler defaultLogAction
 
  In the expression:
 
defaultErrorHandler defaultLogAction
 
$ do { runGhc (Just libdir)
 
   $ do { dflags - getSessionDynFlags;
 
  setSessionDynFlags dflags;
 
   } }
 
  Main.hs:7:7:
 
  Couldn't match expected type `DynFlags.FlushOut'
 
  with actual type `IO SuccessFlag'
 
  In a stmt of a 'do' block:
 
runGhc (Just libdir)
 
$ do { dflags - getSessionDynFlags;
 
   setSessionDynFlags dflags;
 
   target - guessTarget test_main.hs Nothing;
 
   setTargets [target];
 
    }
 
  In the second argument of `($)', namely
 
`do { runGhc (Just libdir)
 
  $ do { dflags - getSessionDynFlags;
 
 setSessionDynFlags dflags;
 
  } }'
 
  In the expression:
 
defaultErrorHandler defaultLogAction
 
$ do { runGhc (Just libdir)
 
   $ do { dflags - getSessionDynFlags;
 
  setSessionDynFlags dflags;
 
   } }
 
 
 
  ___
  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] Generating Haskell Code out of Haskell AST (GHC API)

2013-07-18 Thread John Blackbox
Hi!
I dont know GHC API very well, but I want to generate AST of a program
using GHC API.
Is there any standard method to generate Haskell code out of it? (something
like print_this_for_me_please function? :D
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wrapping all fields of a data type in e.g. Maybe

2013-07-16 Thread John Lato
The suggestion of parameterizing on a functor would be good, however
there's another approach I've often seen (although it's not quite what
you've asked for).  You can leave your config datatype alone, but instead
of making it a monoid have your configuration parsers return functions with
the type (Cfg - Cfg).  You can wrap these functions in Endo to get a
monoid, combine them together, and then apply that function to the default
configuration.


On Wed, Jul 17, 2013 at 4:57 AM, Michael Orlitzky mich...@orlitzky.comwrote:

 I have a common pattern in my command-line programs; I start out with a
 configuration data type, which over-simplified looks like:

   data Cfg = Cfg { verbose :: Bool }

 Now, there's usually a default configuration,

   default :: Cfg
   default = Cfg False

 The user can override the defaults one of two ways, either via a config
 file, or from the command-line. If both are specified, the command-line
 takes precedence. The way I do this is with,

   data OptionalCfg = OptionalCfg { verbose :: Maybe Bool }

 And then I define I Monoid instance for OptionalCfg which lets me merge
 two ofthem. Once the two OptionalCfgs are merged, I merge *that* with
 the default Cfg.

 This all works great, except that when there's 20 or so options, I
 duplicate a ton of code in the definition of OptionalCfg. Is there some
 pre-existing solution that will let me take a Cfg and create a new type
 with Cfg's fields wrapped in Maybe?

 ___
 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] ordNub

2013-07-15 Thread John Lato
In my tests, using unordered-containers was slightly slower than using Ord,
although as the number of repeated elements grows unordered-containers
appears to have an advantage.  I'm sure the relative costs of comparison vs
hashing would affect this also.  But both are dramatically better than the
current nub.

Has anyone looked at Bart's patches to see how difficult it would be to
apply them (or re-write them)?


On Mon, Jul 15, 2013 at 8:43 PM, Clark Gaebel cgae...@uwaterloo.ca wrote:

 Apologies. I was being lazy. Here's a stable version:

   import qualified Data.HashSet as S

   hashNub :: (Ord a) = [a] - [a]
   hashNub l = go S.empty l
 where
   go _ [] = []
   go s (x:xs) = if x `S.member` s then go s xs
 else x : go (S.insert x s) xs

 Which, again, will probably be faster than the one using Ord, and I
 can't think of any cases where I'd want the one using Ord instead. I
 may just not be creative enough, though.


   - Clark

 On Mon, Jul 15, 2013 at 12:46 AM, Brandon Allbery allber...@gmail.com
 wrote:
  On Sun, Jul 14, 2013 at 7:54 AM, Clark Gaebel cgae...@uwaterloo.ca
 wrote:
 
  Oops sorry I guess my point wasn't clear.
 
  Why ord based when hashable is faster? Then there's no reason this has
 to
  be in base, it can just be a
 
  Did the point about stable fly overhead?
 
  --
  brandon s allbery kf8nh   sine nomine
 associates
  allber...@gmail.com
 ballb...@sinenomine.net
  unix, openafs, kerberos, infrastructure, xmonad
 http://sinenomine.net

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

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


Re: [Haskell-cafe] ordNub

2013-07-15 Thread John Lato
On Tue, Jul 16, 2013 at 10:31 AM, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:

 On 16 July 2013 11:46, John Lato jwl...@gmail.com wrote:
  In my tests, using unordered-containers was slightly slower than using
 Ord,
  although as the number of repeated elements grows unordered-containers
  appears to have an advantage.  I'm sure the relative costs of comparison
 vs
  hashing would affect this also.  But both are dramatically better than
 the
  current nub.
 
  Has anyone looked at Bart's patches to see how difficult it would be to
  apply them (or re-write them)?

 If I understand correctly, this function is proposed to be added to
 Data.List which lives in base... but the proposals here are about
 using either Sets from containers or HashSet from
 unordered-containers; I thought base wasn't supposed to depend on any
 other package :/


That was one of the points up for discussion: is it worth including a
subset of Set functionality to enable a much better nub in base?  Is it
even worth having Data.List.nub if it has quadratic complexity?

As an alternative, Bart's proposal was for both including ordNub in
containers and an improved nub (with no dependencies outside base) in
Data.List.  Unfortunately the patches are quite old (darcs format), and I
don't know how they'd apply to the current situation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-11 Thread John Lato
I agree that how the exception was thrown is more interesting than the
type.  I feel like there should be a way to express the necessary
information via the type system, but I'm not convinced it's easy (or even
possible).

Another issue to be aware of is that exceptions can be thrown from pure
code, so if you don't fully evaluate your return value an exception can be
thrown later, outside the catch block.  In practice this usually means an
NFData constraint, or some other constraint for which you can guarantee
evaluation.

In the past I've been pretty vocal about my opposition to exceptions.  It's
still my opinion that they do not make it easy to reason about exceptional
conditions.  Regardless, as Haskell has them and uses them, I'd like to see
improvements if possible.  So if anyone is exploring the design space, I'd
be willing to participate.


On Fri, Jul 12, 2013 at 12:57 AM, Michael Snoyman mich...@snoyman.comwrote:




 On Thu, Jul 11, 2013 at 6:07 PM, Felipe Almeida Lessa 
 felipe.le...@gmail.com wrote:

 On Thu, Jul 11, 2013 at 10:56 AM, Michael Snoyman mich...@snoyman.com
 wrote:
  The only
  approach that handles the situation correctly is John's separate thread
  approach (tryAll3).

 I think you meant tryAll2 here.  Got me confused for some time =).

 Cheers,

 --
 Felipe.


 Doh, yes, I did, thanks for the clarification.

 After playing around with this a bit, I was able to get an implementation
 of try, catch, and handle which work for any non-async exception, in monad
 transformers which are instances of MonadBaseControl (from monad-control).
 I'll try to write up my thoughts in something more coherent, likely a blog
 post.

 Michael

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


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-10 Thread John Lato
I think 'shouldBeCaught' is more often than not the wrong thing.  A
whitelist of exceptions you're prepared to handle makes much more sense
than excluding certain operations.  Some common whitelists, e.g. filesystem
exceptions or network exceptions, might be useful to have.

I like Ertugrul's suggestion a lot, however it seems a bit more invasive.
 If we want to do that work, we could also restructure the wired-in
exceptions so they're more hierarchical.  There are some top-level
exceptions we can get by type, such as ArithException, but sadly many
interesting and useful exceptions are lumped together under IOException.


On Wed, Jul 10, 2013 at 4:29 PM, Ertugrul Söylemez e...@ertes.de wrote:

 Michael Snoyman mich...@snoyman.com wrote:

  shouldBeCaught :: SomeException - Bool
 
  One first stab at such a function would be to return `False` for
  AsyncException and Timeout, and `True` for everything else, but I'm
  not convinced that this is sufficient. Are there any thoughts on the
  right approach to take here?

 I think there is no one right approach.  However, if you add such a
 function to the exception library, it really belongs into the Exception
 type class with the following type:

 shouldBeCaught :: (Exception e) = e - Bool

 However, a better approach is to have exception tags.  In most cases you
 don't want to catch killThread's or timeout's exception, but you do want
 to catch all error exceptions:

 data Tag = Error | Abort | TryAgain | {- ... -} | Other String
 deriving (Data, Eq, Ord, Read, Show, Typeable)

 instance IsString Tag where
 fromString t = Other t

 This could then manifest in the following two functions in the Exception
 type class:

 hasTag :: (Exception e) = Tag - e - Bool
 tagsOf :: (Exception e) = e - [Tag]

 Then exception catchers (functions that risk swallowing important
 exceptions) could filter by type and tag.


 Greets,
 Ertugrul

 --
 Not to be or to be and (not to be or to be and (not to be or to be and
 (not to be or to be and ... that is the list monad.

 ___
 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] Correct way to catch all exceptions

2013-07-10 Thread John Lato
On Wed, Jul 10, 2013 at 5:02 PM, Erik Hesselink hessel...@gmail.com wrote:

 On Wed, Jul 10, 2013 at 10:39 AM, John Lato jwl...@gmail.com wrote:
  I think 'shouldBeCaught' is more often than not the wrong thing.  A
  whitelist of exceptions you're prepared to handle makes much more sense
 than
  excluding certain operations.  Some common whitelists, e.g. filesystem
  exceptions or network exceptions, might be useful to have.

 You'd think that, but there are common use cases. For example, if you
 have a queue of work items, and a thread (or threads) processing them,
 it is useful to catch all exceptions of these threads. You can then
 log the exception, remove the item from the queue and put it in some
 error bucket, and continue on to the next item. The same goes for e.g.
 socket listening threads etc.

 The thing here is that you are *not* actually handling the specific
 exception, but instead failing gracefully. But you still want to be
 able to kill the worker threads, and you don't want to handle
 exceptions that you cannot recover from even by moving on to the next
 work item.


I think that's a particularly niche use case.  We have some similar code,
and our approach is to have the thread re-throw (or terminate) after
logging the exception.  There's a separate thread that monitors the thread
pool, and when threads die new ones are spawned to take their place (unless
the thread pool is shutting down, of course).  Spawning a new thread only
happens on an exception and it's cheap anyway, so there's no performance
issue.

As Haskell currently stands trying to sort out thread-control and
fatal-for-real exceptions from other exceptions seems rather fiddly,
unreliable, and prone to change between versions, so I think it's best
avoided.  If there were a standard library function to do it I might use
it, but I wouldn't want to maintain it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-10 Thread John Lato
Hi Michael,

I don't think those are particularly niche cases, but I still think this is
a bad approach to solving the problem.  My reply to Erik explicitly covers
the worker thread case, and for running arbitrary user code (as in your top
line) it's even simpler: just fork a new thread for the user code.  You can
use the async package or similar to wrap this, so it doesn't even add any
LOCs.

What I think is particularly niche is not being able to afford the cost of
another fork, but I strongly doubt that's the case for Warp.

The reason I think this is a bad design is twofold: first maintaining a
list of exclusions like this (whether it's consolidated in a function or
part of the exception instance) seems rather error-prone and increases the
maintenance burden for very little benefit IMHO.

Besides, it's still not correct.  What if you're running arbitrary user
code that forks its own threads?  Then that code's main thread could get a
BlockedIndefinitelyOnMVar exception that really shouldn't escape the user
code, but with this approach it'll kill your worker thread anyway.  Or even
malicious/brain-damaged code that does myThreadId = killThread?

I like Ertugrul's suggestion though.  It wouldn't fix this issue, but it
would add a lot more flexibility to exceptions.


On Wed, Jul 10, 2013 at 6:44 PM, Michael Snoyman mich...@snoyman.comwrote:




 On Wed, Jul 10, 2013 at 1:01 PM, John Lato jwl...@gmail.com wrote:

 On Wed, Jul 10, 2013 at 5:02 PM, Erik Hesselink hessel...@gmail.comwrote:

 On Wed, Jul 10, 2013 at 10:39 AM, John Lato jwl...@gmail.com wrote:
  I think 'shouldBeCaught' is more often than not the wrong thing.  A
  whitelist of exceptions you're prepared to handle makes much more
 sense than
  excluding certain operations.  Some common whitelists, e.g. filesystem
  exceptions or network exceptions, might be useful to have.

 You'd think that, but there are common use cases. For example, if you
 have a queue of work items, and a thread (or threads) processing them,
 it is useful to catch all exceptions of these threads. You can then
 log the exception, remove the item from the queue and put it in some
 error bucket, and continue on to the next item. The same goes for e.g.
 socket listening threads etc.

 The thing here is that you are *not* actually handling the specific
 exception, but instead failing gracefully. But you still want to be
 able to kill the worker threads, and you don't want to handle
 exceptions that you cannot recover from even by moving on to the next
 work item.


 I think that's a particularly niche use case.  We have some similar code,
 and our approach is to have the thread re-throw (or terminate) after
 logging the exception.  There's a separate thread that monitors the thread
 pool, and when threads die new ones are spawned to take their place (unless
 the thread pool is shutting down, of course).  Spawning a new thread only
 happens on an exception and it's cheap anyway, so there's no performance
 issue.

 As Haskell currently stands trying to sort out thread-control and
 fatal-for-real exceptions from other exceptions seems rather fiddly,
 unreliable, and prone to change between versions, so I think it's best
 avoided.  If there were a standard library function to do it I might use
 it, but I wouldn't want to maintain it.


 Maybe I'm just always working on niche cases then, because I run into this
 problem fairly regularly. Almost any time you want to write a library that
 will run code it doesn't entirely trust, this situation arises. Examples
 include:

- Writing a web server (like Warp) which can run arbitrary user code.
Warp must fail gracefully if the user code throws an exception, without
bringing down the entire server thread.
- Writing some kind of batch processing job which uses any library
which may throw an exception. A white list approach would not be sufficient
here, since we want to be certain that any custom exception types have been
caught.
- A system which uses worker threads to do much of its work. You want
to make certain the worker threads don't unexpectedly die because some
exception was thrown that you were not aware could be thrown. I use this
technique extensively in Keter, and in fact some work I'm doing on that
code base now is what triggered this email.

 I think that, overall, Ertugrul's suggestion is probably the right one: we
 should be including richer information in the `Exception` typeclass so that
 there's no guessing involved, and any custom exception types can explicitly
 state what their recovery preference is. In the meanwhile, I think we could
 get pretty far by hard-coding some rules about standard exception types,
 and making an assumption about all custom exception types (e.g., they *
 should* be caught by a catch all exceptions call).

 If we combine these two ideas, we could have a new package on Hackage
 which defines the right set of tags and provides a `tagsOf` function

[Haskell-cafe] bug in Data.ByteString.Lazy or in me?

2013-07-03 Thread John MacFarlane
On a 64-bit Windows 8 server EC2 instance, with Haskell Platform
freshly installed from the package installer,

GHCI :m + Data.ByteString.Lazy
GHCI Data.ByteString.Lazy.hGetContents stdin

gives me an immediate error hGetBufSome: resource exhausted (Not enough
space), while

GHCI :m + Data.ByteString
GHCI Data.ByteString.hGetContents stdin

waits for user input, as expected.

On 32-bit Windows, both work as expected.

Can anyone explain this?  Is this a bug in bytestring?

John


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


Re: [Haskell-cafe] some questions about Template Haskell

2013-07-02 Thread John Lato
lift and [| |] give similar results for that very stripped-down example,
but it would be incorrect to extrapolate their behaviors from that case.
 They're executed at different times, by different mechanisms, and have
vastly different behavior.  It's also best to think of [| |] as having the
type String - ExpQ, even though the input isn't syntactically quoted.

Suppose you have a slightly different example:

  let x = 1 :: Int
  runQ $ lift $ show x
 ListE [LitE (CharL '1')]
  runQ [| show x |]
 AppE (VarE GHC.Show.show) (VarE x_1627398832)

With lift, the expression is evaluated, then the result '1' is lifted into
an AST.  But TH quotes do something entirely different: they lift *the
expression* into an AST.  In order to do so, the quoting mechanism needs to
parse its input string, then determine what each identifier is referring to.

When you're defining a function:

  let p :: (Show a, Lift a) = a - ExpQ; p n = [| show n |]

The quote has two terms: show and n.  'n' is a lambda-bound value, and show
is free. Free variables are looked up in the environment.  That's why we
see 'VarE GHC.Show.show' in the AST above; the fully-qualified Name is
generated and the AST references that name.  (numeric and string literals
are represented directly)

This is the key difference between this function definition and running the
splice above: in the function 'n' is lambda-bound, whereas in the above
splice 'x' is a free variable.

Lambda bindings can't be referenced by name because that name may not be in
scope when the generated splice is run.  Instead, lambda-bound values must
be lifted directly into the AST, which is exactly what 'lift' does.  If we
apply the function to a value, we can see the generated AST:

  runQ (p 2)
AppE (VarE GHC.Show.show) (LitE (IntegerL 2))

The generated AST has the number 2, and applies the function  GHC.Show.show
to it.

If we want to show something that doesn't have a Lift instance, we can't do
it directly.  However, we can do this:

  let q :: Show a = a - ExpQ; q n = [| $(lift $ show n) |]
  runQ (q 2)
 ListE [LitE (CharL '2')]

Note the differences.  We no longer require that 'n' has a Lift instance.
 However, the actual value of 'n' never appears in the AST!  Instead, we
first show 'n', then lift in the resulting string.  The order of operations
is changed too.  In the first case, the literal 2 is lifted into the AST
via lift, and the generated splice will apply show to that number whenever
the splice is run.  In the second case, (show 2) is evaluated first, then
the result is lifted into the AST (again via lift), causing that string to
be referenced within the splice.

HTH,
John




On Wed, Jul 3, 2013 at 5:44 AM, TP paratribulati...@free.fr wrote:

 John Lato wrote:

  Now, I have found another behavior difficult to understand for me:
 
   runQ $ lift u
  ListE [LitE (CharL 'u')
   runQ $ [| u |]
  LitE (StringL u)
 
  So we have similar behaviors for lift and [||]. We can check it in a
  splice:
 
   $( [| u |] )
  u
   $( lift u )
  u
 
  But if I replace a working version:
 
  pr n = [| putStrLn ( $(lift( nameBase n ++  =  )) ++ show $(varE n) )
  |]   - case (i) -
 
  by
 
  pr n = [| putStrLn ( $([| (nameBase n) ++  =  |]) ++ show $(varE n) )
  |]   - case (ii) -
 
  I again get the error
 
 
  In the working version, 'n' appears inside a splice, whereas in the other
  n
  is in a quote.  AFAIK any value can be used in a splice (provided it
 meets
  the staging restrictions), whereas only Lift-able values can be used in a
  quote.

 If I take this as a granted axiom, then I can admit the behavior above
 (error in case (ii), whereas it is working in case (i)) because n is a
 (Name), and so is not instance of Lift. Thus we are compelled to use lift
 instead of [||] (although the behavior is about the same for both in simple
 examples, as shown in my example above for u).

 I do not understand the exact reason for that, but I can do without; and
 maybe it is better, because I am very probably not enough experienced to
 understand the details (and the reason is perhaps not trivial when I read
 Oleg who writes that what gives an error above in Haskell works in
 MetaOCaml).

 What is strange is that:
 * in the version using lift, the definition of lift asks for the output
 of
 (nameBase n) to be an instance of Lift, what is the case because it is a
 string (cf my previous post in this thread).
 * whereas in the second version, we ask for n, not (nameBase n), to be an
 instance of Lift.

 Anyway, if we admit your axiom as granted, then we can also admit that the
 following version does not work (version of my initial post):

   pr :: Name - ExpQ
   pr n = [| putStrLn $ (nameBase n) ++  =  ++ show $(varE n) |]

 Thanks,

 TP


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

___
Haskell-Cafe mailing list
Haskell

Re: [Haskell-cafe] some questions about Template Haskell

2013-06-30 Thread John Lato
On Mon, Jul 1, 2013 at 6:01 AM, TP paratribulati...@free.fr wrote:

 o...@okmij.org wrote:

  pr :: Name - ExpQ
  pr n = [| putStrLn $ (nameBase n) ++  =  ++ show $(varE n) |]
 
  The example is indeed problematic. Let's consider a simpler one:
 
  foo :: Int - ExpQ
  foo n = [|n + 1|]
 
  The function f, when applied to an Int (some bit pattern in a machine
  register), produces _code_. It helps to think of the code
  as a text string with the
  source code. That text string cannot include the binary value that is
  n. That binary value has to be converted to the numeric text string, and
  inserted in the code. That conversion is called `lifting' (or
  quoting). The function foo is accepted because Int is a liftable type,
  the instance of Lift. And Name isn't.

 Thanks Oleg,
 Probably the following question will be stupid, but I ask it anyway: in my
 initial example, (nameBase n) returns a String, so we are not in the case
 where it is not liftable? In fact I am not sure to have understood your
 answer.


The problem isn't the output of nameBase, it's the input parameter 'n'.  In
your example, you've created a function that takes input (a Name) and
generates code based upon that input.  In order to lift a value (n) from an
ordinary context into a quote, it needs a Lift instance.



 Now, I have found another behavior difficult to understand for me:

  runQ $ lift u
 ListE [LitE (CharL 'u')
  runQ $ [| u |]
 LitE (StringL u)

 So we have similar behaviors for lift and [||]. We can check it in a
 splice:

  $( [| u |] )
 u
  $( lift u )
 u

 But if I replace a working version:

 pr n = [| putStrLn ( $(lift( nameBase n ++  =  )) ++ show $(varE n) ) |]

 by

 pr n = [| putStrLn ( $([| (nameBase n) ++  =  |]) ++ show $(varE n) ) |]

 I again get the error


In the working version, 'n' appears inside a splice, whereas in the other n
is in a quote.  AFAIK any value can be used in a splice (provided it meets
the staging restrictions), whereas only Lift-able values can be used in a
quote.

Perhaps it helps if you think about what a quote does: it allows you to
write essentially a string of Haskell code that is converted into an AST.
 For this to work, the quote parser needs to know how to generate the AST
for an identifier.  Like much of Haskell, it's type-driven.  For
identifiers in scope from imports, TH simply generates a variable with the
correct name.  But for data, the parser needs a way to generate an AST
representation, which is what Lift is for.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: module-management-0.9.3 - clean import lists, split and merge modules

2013-06-28 Thread John Wiegley
 David Fox d...@seereason.com writes:

 Cliff Beshers wrote a CLI for this, I will add it as a cabal
 executable in the next version.

Oh, also, I was unable to build the library using GHC 7.4.2.  It looks like it
still depends on the old Exception stuff that used to be Prelude?

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] ANNOUNCE: module-management-0.9.3 - clean import lists, split and merge modules

2013-06-27 Thread John Wiegley
 David Fox d...@seereason.com writes:

 I am pleased to announce the first release of module-management, a package
 for cleaning import lists, and splitting and merging modules.  You can see a
 description at the top of the documentation for Language.Haskell.Modules
 (once it appears) here:

How about building an executable along with the library called cleanImports,
so that I can use it from the command-line.  Otherwise, every who wants to use
your library in this way will be writing pretty much the exact same code.

cleanImports is something I've been wanting, just hadn't gotten around to
writing it yet.  Thanks!

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] Nightly builds of GHC HEAD for OS X 10.8

2013-06-21 Thread John Wiegley
 John Wiegley jo...@fpcomplete.com writes:

 Since mid-January, I’ve been running nightly builds of GHC on my Mac Pro for
 10.8.x, 64-bit. I’ve decided to make these results publically downloadable
 here:
 
 http://ghc.newartisans.com.

Just a note: I'm now including builds and logs for Ubuntu 12.04.x LTS 64-bit
as well, in addition to OS X 10.8.x.

If anyone has another platform they'd like to add, and can give me SSH access
to an account on their machine, the build needs about 10G of disk space and
eight hours a day of full CPU access (on average).  It can run in whatever
time range works best for you.  Let me know by e-mail if you're interested in
contributing to these nightlies.

As a next step, I plan to build source tarballs as well, so that the binaries
can be used forensically to allow bisecting among the builds for a breakage.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


[Haskell-cafe] Nightly builds of GHC HEAD for OS X 10.8

2013-06-12 Thread John Wiegley
Since mid-January, I’ve been running nightly builds of GHC on my Mac Pro for
10.8.x, 64-bit. I’ve decided to make these results publically downloadable
here:

http://ghc.newartisans.com.

The installer tarballs are in dist, while the fulltest and nofib logs are in
logs. According to Jenkins this build takes 8h15m minutes, so I figured this
might save others some CPU heat.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] Why isn't hsc2hs functionality provided by ghc?

2013-06-05 Thread John Lato
On Wed, Jun 5, 2013 at 3:56 PM, Roman Cheplyaka r...@ro-che.info wrote:

 * Ivan Lazar Miljenovic ivan.miljeno...@gmail.com [2013-06-05
 17:47:40+1000]
  On 5 June 2013 17:34, Roman Cheplyaka r...@ro-che.info wrote:
   * Jason Dagit dag...@gmail.com [2013-06-04 21:00:25-0700]
My preferred solution would be to have ghc/ghci automatically run
 hsc2hs
(support c2hs also?) when necessary.  But so long as it's handled
automatically, I wouldn't be particularly bothered by the
 implementation.
  
   How about having a `ghci` command for cabal? Or does the automatic
   requirement really need to be part of ghc to work the way you want?
  
   (BTW, cabal-dev does have a `ghci` command, but I haven't tested to
   see if it does the hsc - hs conversion.)
  
   I don't think cabal can provide that. Let's say you're inside a 'cabal
   ghci' session. If you modify the hsc file and reload it in ghci, you'd
   expect to load the updated version — yet cabal hasn't even been called
   since 'cabal ghci', and have had no chance to re-generate the hs file.
  
   To answer the subject question — hsc2hs is not a single preprocessor
   available. There are also c2hs and greencard, and maybe something else.
   It is (or, at least, was) not clear which one should be generally
   preferred. Perhaps by now hsc2hs is a clear winner — I don't know.
  
   Another option is to add a generic preprocessor option to GHC,
 something
   like -pgmX cmd. Then, for hsc2hs one would write something like
  
 {-# OPTIONS_GHC -pgmX hsc2hs #-}
 
  Isn't this what -pgmF is
  for?
 http://www.haskell.org/ghc/docs/7.6.1/html/users_guide/options-phases.html#replacing-phases
 
  {-# OPTIONS_GHC -F -pgmF hsc2hs #-}

 Indeed! I should've read the whole section.

 Problem solved, then?


Pretty close.  For anyone who wants to use hsc2hs in this way, the first
step is to create a wrapper script to handle the arguments appropriately
(otherwise the output doesn't go to the proper location)

 file ghc_hsc2hs.sh
   #!/bin/sh
   hsc2hs $2 -o $3

Put the wrapper in your path, and add
{-# OPTIONS_GHC -F -pgmF ghc_hsc2hs.sh #-}

to the top of the source file.  The source file must have a .hs extension
for ghci to load it, but hsc2hs will ignore that and process it anyway.

With this you can load the file in ghci, and if you modify the file
reloading in ghci will pick up the changes, so it works pretty nicely.

There are a couple drawbacks though.  First, this isn't good for
distribution because other people won't have your wrapper script.  Second,
this preprocessor stage comes after CPP, which might impose some
difficulties in certain cases.

I can see this working well for internal projects etc.  If hsc2hs (and
other preprocessors) were distributed in a fashion suitable for use with
-F, either directly or by providing a wrapper, I think this could become
the preferred workflow.  I'm not entirely pleased that a non-Haskell file
gets a .hs extension, but c'est la vie.

I think it would generally be useful if ghc's -F phase were to support
non-Haskell files, but that's probably a bit more work than just
distributing a pgmF-friendly hsc2hs.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FRP memory leaks

2013-06-05 Thread John Lato
Which FRP frameworks have you been looking at?

In my experience, the most publicized leaks have been time leaks, which are
a particular type of memory leak related to switching.  However, the
presence of time leaks mostly arises in terms of the FRP implementation.
 Arrowized FRP (e.g. Yampa, netwire) do not typically suffer from this for
example.  Some libraries that implement the semantics of Conal Elliott's
Push-pull functional reactive programming (or similar semantics) have
been susceptible to this, however recent implementations are not.  Sodium,
elerea, and reactive-banana for example have generally overcome the worst
issues present in earlier systems.  Leaks can still be present in current
systems of course, but now they're generally due to the programmer
unintentionally retaining data in a case that's much simpler to reason
about.  That is, the situation today is more similar to forgetting to use
deepseq or similar, rather than the prior leaks that were very difficult to
reason about.

I think the most common current issue is that a very natural way of
accumulating reactive events across time can leak.  Suppose you have a
library of reactive widgets, where each widget has an associated stream of
IO actions that you want to run.  E.g. clicking a button prints it, sliding
a scale prints the value, etc.

 class Actionable a where
   actions :: a - Event (IO ())

suppose you have a collection that allows you to add/remove Actionable
things to it (e.g. a button panel).  This panel has an action stream that's
simply the concatenation of those of its components.  One possible
implementation looks like this:

 data ButtonPanel = ButtonPanel (Event (IO ())

 emptyPanel = ButtonPanel mempty

 addActionable :: Actionable a = ButtonPanel - a - ButtonPanel
 addActionable (ButtonPanel e) a = ButtonPanel (e  actions a)

I've omitted all the parts for wiring up the gui, but suppose they're
handled also, and removing a button from the panel just removes it from the
gui and destroys the widget.  After that, the button's event stream is
empty, so you can just leave the ButtonPanel's event stream unchanged,
because the destroyed button will never fire.

This is a memory leak.  The destroyed Button's event stream is still
referenced in the ButtonPanel event stream, so data related to it never
gets freed.  Over time your FRP network will grow, and eventually you'll
hit scaling problems.

The proper solution in this instance is to keep a list of each button's
event stream within the button panel.  It's ok to keep a cached aggregate
stream, but that cache needs to be re-built when a button is removed.  This
is usually fairly natural to do with FRP, but your ButtonPanel may look
like this instead:

 data ButtonPanel = ButtonPanel  (Map Key (Event (IO ()))

 addActionable :: Actionable a = ButtonPanel- Key - a - ButtonPanel
 removeActionable :: ButtonPanel - Key - ButtonPanel

and now you need to manage some sort of Key for collection elements.

This style isn't entirely idiomatic FRP.  Instead of these functions, you
could have all your modifications handled via the FRP framework.  For
example,

 data ButtonPanel = ButtonPanel (Behavior (Map Key (Event (IO ()
 buttonPanel :: Actionable a = Event (Key,a) - Event Key - ButtonPanel

but you still need to be aware that objects can reference older objects.
 Behaviors are frequently created via accumulators over events (e.g.
accumB), and if the accumulation is doing something like 'mappend', a
memory leak is likely.

Basically, the issue is that when you're accumulating reactive stuff over
time, you need to be sure that your accumulator doesn't reference data that
is otherwise expired.  This example uses a push-pull style pseudocode
because that's what I'm most familiar with.  I'm not entirely show how (or
if) this translates to arrowized FRP, although it wouldn't surprise me if
there's a similar pattern.


On Thu, Jun 6, 2013 at 2:50 AM, Łukasz Dąbek sznu...@gmail.com wrote:

 Hello, Cafe!

 I've heard that one of the problems of FRP (Functional Reactive
 Programming) is that it's easy to create memory leaks. However I cannot
 find any natural examples of such leaks. Could anybody post some
 (pseudo)code demonstrating this phenomenon? Preferably something that
 arises when one is writing bigger applications in FRP style.

 Thanks in advance!

 --
 Łukasz Dąbek

 ___
 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] Why isn't hsc2hs functionality provided by ghc?

2013-06-05 Thread John Lato
I agree that preprocessing code shouldn't be hsc2hs specific.  I prefer
c2hs myself.  But hsc2hs is distributed with ghc, which makes it as
official as a good many other parts of modern Haskell.

I also agree that making cabal-ghci work nicely would be ideal, but I don't
think it can be done without either adding hooks into ghci or wrapping
stdin.  As Roman points out, if you use :r in ghci, cabal-ghci wouldn't
pick up changes in the source file.  Using ghc's support for custom
preprocessors seems like a very straightforward solution: it already
exists, can be used today, and isn't tied to hsc2hs.

Not that this should stop anyone from working on cabal-ghci of course.


On Thu, Jun 6, 2013 at 11:43 AM, Jeremy Shaw jer...@n-heptane.com wrote:

 While hsc2hs is a popular FFI preprocessor, it is not the only one.
 There is also greencard and a few others.

 While hsc2hs can usually get the job done -- it's not clear that it is
 really the best choice. I think the Haskell FFI got to the point that
 it was 'just good enough' and then people lost interest in doing
 anything more. Let's face it -- working on the FFI is just not that
 exciting :)

 So, basically, we are stuck with stuff that is 'good enough' but no so
 great that we want to make it official.

 We can bind to C fairly easily, but for C++, Python, Ruby, Javascript,
 Java, etc, we have never really made much headway.

 I think the efforts to make cabal-ghci work nicely could really be the
 best solution for now. That is more extensible, and makes it easy to
 solve the problem you actually care about (being able to easily
 load/compile .hs files) with out giving priority to any particular FFI
 system.

 - jeremy

 On Tue, Jun 4, 2013 at 9:02 PM, silly silly8...@gmail.com wrote:
  I was wondering today, why hasn't hsc2hs been merged with ghc so that
  it would be possible to add a
 
  {-# LANGUAGE ForeignFunctionInterface #-}
 
  at the top of a source file and then load it with ghci or compile it,
  without the intermediate step of calling hsc2hs? This would be exactly
  like the CPP extension. I don't have to call cpp manually. All I have
  to do is to add {-# LANGUAGE CPP #-} and then ghc will take care of
  the rest. This would also mean that there would be no need to have a
  separate file extension. Surely I must not be the first person to have
  that thought, so there must be a good reason why this hasn't happen
  yet, but what is it?
 
  ___
  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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why isn't hsc2hs functionality provided by ghc?

2013-06-04 Thread John Lato
On Wed, Jun 5, 2013 at 10:15 AM, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:

 On 5 June 2013 12:02, silly silly8...@gmail.com wrote:
  I was wondering today, why hasn't hsc2hs been merged with ghc so that
  it would be possible to add a
 
  {-# LANGUAGE ForeignFunctionInterface #-}
 
  at the top of a source file and then load it with ghci or compile it,
  without the intermediate step of calling hsc2hs? This would be exactly
  like the CPP extension. I don't have to call cpp manually. All I have
  to do is to add {-# LANGUAGE CPP #-} and then ghc will take care of
  the rest. This would also mean that there would be no need to have a
  separate file extension. Surely I must not be the first person to have
  that thought, so there must be a good reason why this hasn't happen
  yet, but what is it?

 Isn't this done automatically when you have files with the .hsc extension?


cabal handles this transparently, but not ghc.  It's frustrating when you
want to develop a project with ghci.

I don't think it's a good idea to merge hsc2hs syntax into Haskell files.
 In particular, it's often useful to inspect the intermediate .hs file
produced by hsc2hs during development or debugging.  Also it would
complicate ghc's parser, etc...

My preferred solution would be to have ghc/ghci automatically run hsc2hs
(support c2hs also?) when necessary.  But so long as it's handled
automatically, I wouldn't be particularly bothered by the implementation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why isn't hsc2hs functionality provided by ghc?

2013-06-04 Thread John Lato
cabal-dev ghci does work with hsc2hs, but only because it doesn't interpret
your source.  Rather, cabal-dev ghci loads ghci using the sandbox install
of your package, which is less useful for a variety of reasons.

Aside from that detail, I wouldn't gain any benefit from having this
feature built in to ghci instead of accessing ghci via cabal (or
cabal-dev).  cabal seems like a better location, and it's aware of several
preprocessors already.



On Wed, Jun 5, 2013 at 12:00 PM, Jason Dagit dag...@gmail.com wrote:

 On Tue, Jun 4, 2013 at 8:45 PM, John Lato jwl...@gmail.com wrote:
  On Wed, Jun 5, 2013 at 10:15 AM, Ivan Lazar Miljenovic
  ivan.miljeno...@gmail.com wrote:
 
  On 5 June 2013 12:02, silly silly8...@gmail.com wrote:
   I was wondering today, why hasn't hsc2hs been merged with ghc so that
   it would be possible to add a
  
   {-# LANGUAGE ForeignFunctionInterface #-}
  
   at the top of a source file and then load it with ghci or compile it,
   without the intermediate step of calling hsc2hs? This would be exactly
   like the CPP extension. I don't have to call cpp manually. All I have
   to do is to add {-# LANGUAGE CPP #-} and then ghc will take care of
   the rest. This would also mean that there would be no need to have a
   separate file extension. Surely I must not be the first person to have
   that thought, so there must be a good reason why this hasn't happen
   yet, but what is it?
 
  Isn't this done automatically when you have files with the .hsc
 extension?
 
 
  cabal handles this transparently, but not ghc.  It's frustrating when you
  want to develop a project with ghci.
 
  I don't think it's a good idea to merge hsc2hs syntax into Haskell files.
  In particular, it's often useful to inspect the intermediate .hs file
  produced by hsc2hs during development or debugging.  Also it would
  complicate ghc's parser, etc...
 
  My preferred solution would be to have ghc/ghci automatically run hsc2hs
  (support c2hs also?) when necessary.  But so long as it's handled
  automatically, I wouldn't be particularly bothered by the implementation.

 How about having a `ghci` command for cabal? Or does the automatic
 requirement really need to be part of ghc to work the way you want?

 (BTW, cabal-dev does have a `ghci` command, but I haven't tested to
 see if it does the hsc - hs conversion.)

 Jason

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


Re: [Haskell-cafe] Design of extremely usable programming language libraries

2013-05-28 Thread John Lato
  Not sure what you mean here — attoparsec does support unlimited
  lookahead, in the sense that a parser may fail arbitrarily late in the
  input stream, and backtrack to any previous state. Although attoparsec
  is a poor choice for programming language parsing, primarily because
  of the error messages.
 I guess I have an outdated notion of attoparsec. But yes, error messages
 seem to be the weak point of attoparsec. Also, the fact that it only
 accepts bytestrings makes it harder (but no impossible, since we can
 convert Strings to ByteStrings) to reuse the parser as a QuasiQuoter.
 So, I'll rephrase my question. What's the best choice for a library for
 parsing programming languages nowadays?


Parsec is still widely popular since it's part of the HP, but I use
uu-parsinglib as my first-choice parser.  It comes with a lot of examples,
good documentation, and many features I like (good error messages and auto
error correction).  I don't know how performance compares with parsec or
attoparsec, but it's always been good enough for me.

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


[Haskell-cafe] list comprehension doesn't work

2013-05-14 Thread John
Hi,

I have to write a function which returns a list of all pairs (x,y) where x,
y ∈ N AND:
–  x is the product of two natural numbers (x = a · b, where a, b ∈ N) AND
–  x is really bigger than 5 but really smaller than 500, AND
–  y is a squer number (y = c² where c ∈ N) NOT greater than 1000, AND
–  x is a divisor of y.

My attempt is as follows:

listPairs :: [(Int, Int)]
listPairs = [(x,y) | x-[0..], y-[0..], x-[0..]*[0..], x  5, x  500,
(y*y)  1001, mod y x == 0]

However it doesn't work unfortunatly 

Could anyone tell me where my mistake is?

Thanks.



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/list-comprehension-doesn-t-work-tp5730158.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] list comprehension doesn't work

2013-05-14 Thread John
thanks to both!

listPairs = [(a*b, y) | a - [0..], b - [0..], (a*b)  5, (a*b)  500,
(y*y)  1001, mod y x == 0]

Now I have it as you said, however the compiler complains about all y and x
and says they are NOT in scope.

Why is it so? I can't see any problem with that...




--
View this message in context: 
http://haskell.1045720.n5.nabble.com/list-comprehension-doesn-t-work-tp5730158p5730161.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] list comprehension doesn't work

2013-05-14 Thread John
Danny Gratzer wrote
 Well you've deleted the portion of the code referring to x and y.
 
 listPairs = [(a*b, y) | y - [0..], a - [0..], b - [0..], (a*b)  5,
 (a*b)  500, (y*y)  1001, mod y (a*b) == 0]
 
 This will still never terminate however.

oh I see, but as you say it doesn't terminate and I get nothing. Does it
mean, that the function is wrong in this place?

Some questions:
1. Does the order of conditions affect the result at all?
2. The , means AND or , right? So how do you write OR || instead? E.g
z-[1..10] OR z-[100..110].
Ofcourse it doesn't relate to this topic, but I wanted to know it.

Since I'm a very beginner I think the approach of Daniel is slightly complex
for me to comprehend, right?
Allthough I tried it, but it says isProduct and isSquer are not in Scope, so
I should define them first in WHERE-Clause right?

Thanks again to all




--
View this message in context: 
http://haskell.1045720.n5.nabble.com/list-comprehension-doesn-t-work-tp5730158p5730167.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] list comprehension doesn't work

2013-05-14 Thread John
Danny Gratzer wrote
 Isn't the product check actually redundant? re-reading the requirements we
 could just define a = 1 and b = x. Maybe I'm misunderstanding though.

I'm not sure. As I understand the requirement, the squer of y should not be
greater than 1000.

But anyway, without this condition it doesn't work yet 

Do you have any idea, what is wrong with it now?



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/list-comprehension-doesn-t-work-tp5730158p5730168.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] list comprehension doesn't work

2013-05-14 Thread John
is'nt it possible, to write it in one line without any nested functions in
WHERE?
If it's possible I'd prefer that...

any idea?

Thanks



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/list-comprehension-doesn-t-work-tp5730158p5730170.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] list comprehension doesn't work

2013-05-14 Thread John
thanks for your tips.

As I said, I'm at the very beginning of Haskell. I try it to understand as
much as I can, however the topic is very new to me. Sorry about my silly
questions...

You said, their is a mailing list for beginner? Could you please tell me I
get to that?

Thanks



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/list-comprehension-doesn-t-work-tp5730158p5730172.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] Incrementation fails

2013-05-07 Thread John
Hello All,

I'm in a big trouble with incrementation of a counter in this code. It
doesn't increment.

Could you please tell me where the problem ist and how can I solve it?

replaceBasedIdx::  String  -  [String]  -  String  -  String
replaceBasedIdxfindStr replaceStrList myText = replaceBasedIdxSub
findStr replaceStrList myText 0

replaceBasedIdxSub  ::  String  -  [String]  -  String  - Int - String
replaceBasedIdxSub findStr replaceStrList myText counter = loop myText
  where
loop [] = []
loop myText =
  let (prefix, rest) = splitAt n myText
  in
if findStr == prefix-- found an
occurrence?
then (replaceStrList !! (counter+1)) ++ loop rest   -- yes: replace
it

else head myText : loop (tail myText)   -- no: keep
looking
n = length findStr

Thank you very mutch!

Greetings!




--
View this message in context: 
http://haskell.1045720.n5.nabble.com/Incrementation-fails-tp5729905.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Backward compatibility

2013-05-02 Thread John Lato
On Thu, May 2, 2013 at 5:30 PM, Ertugrul Söylemez e...@ertes.de wrote:


 To express this question in a broader context:  Are you leaving a broken
 tool and replacing it with a new shiny one?


So I read the original post, and it really wasn't clear to me what exact
changes were causing the issues; I don't think I'm alone in thinking the OP
could have been a bit more explicit about the nature of the problem.  Also,
at least Flippa is explicitly unmaintained (according to the first hit
googling Flippa Haskell), and I hadn't seen mention of WASH for a year or
more.  And of course, ghc-7.0 was released 2.5 years ago, ghc-7.6 is the
current version, and there's been ample time for incompatibilities to
accumulate.

Despite those issues I'm rather sympathetic to the OP, in part because most
of these breaking changes aren't replacing a broken tool.  If the
Functor/Applicative/Monad hierarchy were fixed it would cause a lot of
breakage, and I (like many of us I'm sure) would have to update a lot of
packages, but I wouldn't mind because that would be a clear improvement.
But replacing import List with import Data.List?  That's not even a
problem.  Consider another breaking change, requiring newtype constructors
be in scope for foreign imports.  This required a lot of code churn,
especially as IIRC the CDouble constructor wasn't exported previously (for
reasons of abstraction, which I can also rant about), so of course it
wouldn't have been in explicit import lists.  At least this has some
marginal utility if you care about Safe Haskell.

I did a lot of work to get packages compilable with ghc-7.6 and submitted
patches to probably a dozen different repos.  Aside from one exception
(related to the FFI), every breaking change was either related to
namespacing/import issues, or bumping versions in .cabal files (I consider
the whole try/catch mess to be an import issue, although at least in that
case the benefit is more obvious).  Two pragmas existed that duplicate
functionality, one was deprecated in the last release and now the other one
is deprecated while the first has been un-deprecated.  It's just
rearranging deck chairs.  It doesn't feel like a significant improvement,
and it's even harder to bill as one.

I don't think there's anything wrong with moving at a fast pace, nor do I
think backwards compatibility should be maintained in perpetuity.
Unfortunately this leaves a lot of scope for migrations to be handled
poorly, and for unintended consequences of shiny new systems.  IMHO both
have caused issues for Haskell developers and users in the recent and more
distant past.  This is an issue where I think the community should
continually try to improve, and if a user calls out a difficulty we should
at least try to learn from it and not repeat the same mistake.

(Unfortunately I'm not really sure what we can learn from this particular
case, but maybe somebody wiser than me could point the way)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] text-icu on Windows

2013-04-27 Thread John MacFarlane
Hello café:

I'd very much like to get text-icu working on Windows, as then I could ship
pandoc binaries that do proper unicode collation in bibliographies.  But I'm
having a devil of a time.  This may be due to my very limited Windows
knowledge.  Any help would be appreciated, especially from someone who actually
has text-icu working on Windows.

I was able to cabal install text-icu without errors. I used --extra-lib-dirs
and --extra-include-dirs to point to the lib and include directories in the
32-bit binary distribution of icu4c.  I'm using the latest Haskell Platform,
2012.4.0.0 with ghc 7.4.2.

I was also able to build the following simple program that uses text-icu, by
doing ghc --make icu.hs:

~~~
-- icu.hs
import Data.Text.ICU
main = print $ Locale tr-TR
~~~

No errors or warnings in either of these steps. But when I try to run the
compiled program, icu.exe, I get no output at all. I expected to get a line
with 'Locale tr-TR', but instead I get nothing -- not even an error or 
warning.
This remains the case if I try

~~~
main = do
  print Start
  print $ Locale tr-TR
  print Done
~~~

'echo $?' yields False.

Any ideas?

John

(I've posted a similar question to StackOverflow [1], but it hasn't gotten
an answer yet there, so I thought I'd try here.)

[1]: 
http://stackoverflow.com/questions/16127710/how-do-i-get-text-icu-working-on-windows)


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


Re: [Haskell-cafe] Markdown extension for Haddock as a GSoC project

2013-04-27 Thread John MacFarlane
I agree with Chris that it would be better to have a standard syntax for
Haskell documentation.  Especially if the alternative is ten different
markup languages. (Remember, all of these need to be supported in
haddock, which is a basic piece of infrastructure.)

Here's a thought.  Instead of adding support for markdown, why not
enhance the existing haddock markup, making it more expressive, so that
it could encode the same range of structural features as markdown?

If this were done, we could add a haddock writer to pandoc.  There is
already a haddock reader in the development version, but a writer is
difficult because haddock is so much less expressive than other formats.
For example, unless I'm mistaken, it doesn't allow list items with
multiple paragraphs or other block elements, or nested lists, or images,
or blockquotes.

With a pandoc reader and writer for haddock, it would be easy to write
your documentation in any format you choose (several variants of
markdown, reST, textile, LaTeX, HTML, mediawiki) and produce equivalent
haddock markup to paste into the source file.

It would also be easy to convert the documentation in your source file
to any of the formats supported by pandoc.  So, you could generate a man
page from your haddock markup, or a web page or blog entry, or a LaTeX
document.

It seems to me that this would provide most of the advantages people
who want a markdown extension for haddock are looking for.  But it would
not require taking sides in markdown/reST/asciidoc/creole wars,
and it would not lead to the fragmentation of documentation formats
in Haskell source code.  If the extensions to haddock markup were done
carefully, it wouldn't even require a special PRAGMA, since all existing
markup would have the same interpretation in the extended markup.

John

+++ Chris Smith [Apr 27 13 12:05 ]:
I don't agree with this at all. Far more important than which
convention gets chosen is that Haskell code can be read and written
without learning many dialects of Haddock syntax. I see an API for
pluggable haddock syntax as more of a liability than a benefit. Better
to just stick to what we have than fragment into more islands.
 
I do think that changing Haddock syntax to include common core pieces
of Markdown could be a positive change... but not if it spawns a battle
of fragmented documentation syntax that lasts a decade.
On Apr 27, 2013 11:08 AM, Bryan O'Sullivan [3]b...@serpentine.com
wrote:
 
On Sat, Apr 27, 2013 at 2:23 AM, Alistair Bayley
[4]alist...@abayley.org wrote:
 
How's about Creole?
[5]http://wikicreole.org/
Found it via this:
[6]http://www.wilfred.me.uk/blog/2012/07/30/why-markdown-is-not-my-favo
urite-language/
If you go with Markdown, I vote for one of the Pandoc implementations,
probably Pandoc (strict):
[7]http://johnmacfarlane.net/babelmark2/
(at least then we're not creating yet another standard...)
 
Probably the best way to deal with this is by sidestepping it: make the
support for alternative syntaxes as modular as possible, and choose two
to start out with in order to get a reasonable shot at constructing a
suitable API.
I think it would be a shame to bikeshed on which specific syntaxes to
support, when a lot of productive energy could more usefully go into
actually getting the work done. Better to say prefer a different
markup language? code to this API, then submit a patch!
 
  ___
  Haskell-Cafe mailing list
  [8]Haskell-Cafe@haskell.org
  [9]http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 References
 
1. mailto:cdsm...@gmail.com
2. mailto:b...@serpentine.com
3. mailto:b...@serpentine.com
4. mailto:alist...@abayley.org
5. http://wikicreole.org/
6. 
 http://www.wilfred.me.uk/blog/2012/07/30/why-markdown-is-not-my-favourite-language/
7. http://johnmacfarlane.net/babelmark2/
8. mailto:Haskell-Cafe@haskell.org
9. 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] text-icu on Windows

2013-04-27 Thread John MacFarlane
Ryan,

Many thanks for your reply.  I was assuming ghc would statically link
against the library files instead of relying on the dll's.  I will see
if I can build the library from source under mingw.  An alternative
would be to distribute the needed dlls with the binary.

John

+++ Ryan Yates [Apr 27 13 19:53 ]:
Hi John,
 
I just tried this out and if I copied all of the .dll files from the
icu4c bin folder into the same folder as the test icu.exe it works as
expected. You can see what dlls are missing with the dependency walker
program[1]http://www.dependencywalker.com/. Perhaps with a mingw based
build of icu4c (the one I used said it was built with Visual Studio 10)
you could avoid this.
 
Ryan Yates
On Sat, Apr 27, 2013 at 4:56 PM, John MacFarlane [2]j...@berkeley.edu
wrote:
 
  Hello caf:
  I'd very much like to get text-icu working on Windows, as then I
  could ship
  pandoc binaries that do proper unicode collation in bibliographies.
  But I'm
  having a devil of a time. This may be due to my very limited Windows
  knowledge. Any help would be appreciated, especially from someone
  who actually
  has text-icu working on Windows.
  I was able to cabal install text-icu without errors. I used
  --extra-lib-dirs
  and --extra-include-dirs to point to the lib and include directories
  in the
  32-bit binary distribution of icu4c. I'm using the latest Haskell
  Platform,
  2012.4.0.0 with ghc 7.4.2.
  I was also able to build the following simple program that uses
  text-icu, by
  doing ghc --make icu.hs:
  ~~~
  -- icu.hs
  import Data.Text.ICU
  main = print $ Locale tr-TR
  ~~~
  No errors or warnings in either of these steps. But when I try to
  run the
  compiled program, icu.exe, I get no output at all. I expected to get
  a line
  with 'Locale tr-TR', but instead I get nothing -- not even an
  error or warning.
  This remains the case if I try
  ~~~
  main = do
  print Start
  print $ Locale tr-TR
  print Done
  ~~~
  'echo $?' yields False.
  Any ideas?
  John
  (I've posted a similar question to StackOverflow [1], but it hasn't
  gotten
  an answer yet there, so I thought I'd try here.)
  [1]:
  [3]http://stackoverflow.com/questions/16127710/how-do-i-get-text-icu
  -working-on-windows)
  ___
  Haskell-Cafe mailing list
  [4]Haskell-Cafe@haskell.org
  [5]http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 References
 
1. http://www.dependencywalker.com/
2. mailto:j...@berkeley.edu
3. 
 http://stackoverflow.com/questions/16127710/how-do-i-get-text-icu-working-on-windows
4. mailto:Haskell-Cafe@haskell.org
5. 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Map Reduce spec in Haskell

2013-04-18 Thread John D. Ramsdell
I'm learning about the Map Reduce computation frequently used with big
data.  For the fun of it, I decided to write a very high-level spec of Map
Reduce.  Here is what I came up with.  Enjoy.

John

 module MapReduce where
 import Data.List (nub)

A high-level specification of Map Reduce as a Haskell program.  The
program uses lists to represent multisets.  As multisets have no
implied ordering, the ordering implied by lists in this specification
should be ignored.

The database is a multiset of key-value pairs.

 type Key = String
 type Value = String
 type Datum = (Key, Value)
 type Data = [Datum]

A mapper maps a datum to a finite multiset of key-value pairs.

 type Mapper = Datum - Data

A reducer takes a key and a multiset of values and produces a finite
multiset of values.

 type Reducer = (Key, [Value]) - [Value]

A step is a mapper followed by a reducer

 type Step = (Mapper, Reducer)

A program is a finite sequence of steps

 type Program = [Step]

The semantics of a program is provided by the run function.

 run :: Program - Data - Data
 run [] d = d
 run (s : p) d =
   run p (step s d)

The three parts of a step are mapping, shuffling, and reducing.

 step :: Step - Data - Data
 step (m, r) d =
   let mapped = transform m d
   shuffled = shuffle mapped in
   reduce r shuffled

The first part of a step is to transform the data by applying the
mapper to each datum and collecting the results.

 transform :: Mapper - Data - Data
 transform m d =
   [p | u - d, p - m u]

Next, values with common keys are collected.  Keys are unique after
shuffling.

 shuffle :: Data - [(Key, [Value])]
 shuffle d =
   [(k, vs) | k - nub (map fst d), -- nub eliminates duplicate keys
  let vs = [v | (k', v) - d, k' == k]]

A reducer is applied to the data associated with one key, and always
produces data with that key.

 reduce :: Reducer - [(Key, [Value])] - Data
 reduce r rs =
   [(k, v) | (k, vs) - rs, v - r (k, vs)]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Numerics and Warnings

2013-04-10 Thread John Lato
The issue with this example is that you have

genericTake :: Integral a = a - [b] - [b]

where the 'a' is converted to an Int without being checked for overflow.

IMHO type defaulting is irrelevant for this one problem; evaluating

 take 44 foobar

has exactly the same result without any defaulting taking place.  Arguably
fromIntegral could have other behavior (error/exception/Maybe) when a
conversion would overflow, but that seems like a very significant change.

Aside from this example, I'm quite sympathetic to the issue.  I've more
than once defined values as

let two = 2 :: Int
 three = 3 :: Int

solely to suppress warnings about type defaulting for (^n).

Really, I'd prefer to see the Prelude export
(^) :: Num a = a - Int - a

I think that's the most common case, and it's probably never useful to
raise to a power greater than (maxBound :: Int).

John L.


On Thu, Apr 11, 2013 at 8:10 AM, Tom Ellis 
tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:

 On Thu, Apr 11, 2013 at 12:56:05AM +0100, Barak A. Pearlmutter wrote:
   ... in most of the cases I do want this warnings. It's possible to get
   something default to Integer when it should be Int. There are only few
   cases when it's not appropriate. Only ^ and ^^ with literals I think
 
  There are a few other cases, albeit less annoying.  Like this:
 
  c = fromIntegral 2 :: Int
 
  Granted this is silly code, but the same case arises inside pretty much
  any code that is generic over Integral, in which case the warning you
  get is not the *right* warning.  Example:
 
  genericTake n xs = take (fromIntegral n) xs
  genericTake 44 foobar

 Hi Barak,

 I don't write a lot of numeric code so I am under-educated in this area.
 Could you write a more substantial example so I get a clearer idea of
 what's
 going on?

 Thanks,

 Tom

 ___
 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] GSoC Project Proposal: Markdown support for Haddock

2013-04-08 Thread John MacFarlane
+++ John MacFarlane [Apr 05 13 16:04 ]:
 I like markdown and use it all the time.  While I acknowledge the
 problems that have been pointed out, markdown has the advantage of being
 easily readable as it is in the source document, and not looking like
 markup.
 
 But I do want to point out one problem with markdown as a format for
 documentation in Haskell files.  Consider:
 
 
 module MyModule
 {-
 # Introduction
 
 This is my module
 -}
 where
 import System.Environment
 
 main = getArgs = print
 
 
 Now try to compile with -cpp, and you'll get an error because of the '#'
 in column 1.  '#' in column 1 is common in markdown (and even
 indispensible for level 3+ headers).
 
 One could work around this by disallowing level 3+ headers, by allowing
 the headers to be indented, or by introducing new setext-like syntax for
 level 3+ headers, but it is a problem for the idea of using a markdown
 SUPERset.
 
 John

Let me amplify my original comment with one more observation about
problems using markdown to comment Haskell code.

Markdown blockquotes start with '' (usually in the leftmost column).
But this causes problems when your source document is bird-style
literate Haskell:

--
This is my literate Haskell module.  As
someone said:

 literate Haskell is great!

Oops, that will be interpreted by GHC
as code, not comment.

 main = print $ reverse [1,2]
--

You can work around this by indenting the first '' one space, which is
still valid Markdown, but it's a bit awkward.  Obviously, we'd want any
Haddock markup successor to work in literate Haskell too.

reStructuredText has fewer potential conflicts and might be a more
sensible choice.  But one would need to write a correct parser for
it.  The pandoc parser doesn't cover 100% of rST, and differs in other
ways from the docutils parser (e.g. it allows markup inside links).
For full compatibility you'd probably want to copy the python module's
parsing algorithm exactly.

John


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


[Haskell-cafe] My first Haskell program

2013-04-06 Thread John Wood
Hello, Cafe
I'm new to Haskell and the mailing list, and am wondering if I could get some 
feedback on my first program -- a Markov text generator. The code is posted 
here:http://codereview.stackexchange.com/questions/24791/haskell-markov-text-generator
Thanks,
John; ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GSoC Project Proposal: Markdown support for Haddock

2013-04-05 Thread John Wiegley
 Johan Tibell johan.tib...@gmail.com writes:

 I suggest that we implement an alternative haddock syntax that's a superset
 of Markdown.

Definite +1 from me too.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] GSoC Project Proposal: Markdown support for Haddock

2013-04-05 Thread John MacFarlane
I like markdown and use it all the time.  While I acknowledge the
problems that have been pointed out, markdown has the advantage of being
easily readable as it is in the source document, and not looking like
markup.

But I do want to point out one problem with markdown as a format for
documentation in Haskell files.  Consider:


module MyModule
{-
# Introduction

This is my module
-}
where
import System.Environment

main = getArgs = print


Now try to compile with -cpp, and you'll get an error because of the '#'
in column 1.  '#' in column 1 is common in markdown (and even
indispensible for level 3+ headers).

One could work around this by disallowing level 3+ headers, by allowing
the headers to be indented, or by introducing new setext-like syntax for
level 3+ headers, but it is a problem for the idea of using a markdown
SUPERset.

John

+++ dag.odenh...@gmail.com [Apr 05 13 21:59 ]:
I forgot the mention the craziness with the *significant trailing
whitespace*.
 
On Fri, Apr 5, 2013 at 9:49 PM, [1]dag.odenh...@gmail.com
[2]dag.odenh...@gmail.com wrote:
 
Personally I think Markdown sucks, although perhaps less than Haddock
markup.
Still:
* No document meta data
* No code block meta data like language for syntax highlighting
* No tables
* No footnotes
* HTML fallback is insecure
* Confusing syntax (is it []() or ()[] for links?)
* Syntax that gets in the way (maybe I don't want *stars* emphasized)
* Above point leads to non-standard dialects like GitHub Markdown
(no, GitHub doesn't use markdown)
* Not extensible, leading to even more non-standard hacks and
work-arounds (GitHub Markdown, Pandoc Markdown, other Markdown
libraries have their own incompatible extensions)
* Not well suited for web input (e.g. four-space indentation for code
blocks), although not that important for Haddock
An important thing to note here is that no, Markdown has *not* won
because no one is actually using *Markdown*. They're using their own,
custom and incompatible dialects.
Only two of the above points apply to reStructuredText (web input and
syntax getting in the way), and those particular points don't apply to
Creole. Therefore I tend to advocate Creole for web applications and
reStructuredText for documents.
On Thu, Apr 4, 2013 at 6:49 PM, Johan Tibell
[3]johan.tib...@gmail.com wrote:
 
  Hi all,
  Haddock's current markup language leaves something to be desired
  once
  you want to write more serious documentation (e.g. several
  paragraphs
  of introductory text at the top of the module doc). Several features
  are lacking (bold text, links that render as text instead of URLs,
  inline HTML).
  I suggest that we implement an alternative haddock syntax that's a
  superset of Markdown. It's a superset in the sense that we still
  want
  to support linkifying Haskell identifiers, etc. Modules that want to
  use the new syntax (which will probably be incompatible with the
  current syntax) can set:
  {-# HADDOCK Markdown #-}
  on top of the source file.
  Ticket: [4]http://trac.haskell.org/haddock/ticket/244
  -- Johan
  ___
  Haskell-Cafe mailing list
  [5]Haskell-Cafe@haskell.org
  [6]http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 References
 
1. mailto:dag.odenh...@gmail.com
2. mailto:dag.odenh...@gmail.com
3. mailto:johan.tib...@gmail.com
4. http://trac.haskell.org/haddock/ticket/244
5. mailto:Haskell-Cafe@haskell.org
6. 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GSoC Project Proposal: Markdown support for Haddock

2013-04-04 Thread John MacFarlane
+++ Simon Heath [Apr 04 13 13:04 ]:
 I humbly suggest reStructuredText rather than Markdown, which is what
 is used by the Python community for documentation.  Since it's specifically
 made for documentation it may be nicer.  But, I don't want to spark
 a format argument.
 
 There is also the Pandoc program, which is a universal-ish markup-
 language-converter, conveniently written in Haskell.  Might be a place
 to start for this, regardless of the language chosen:
 http://www.johnmacfarlane.net/pandoc/
 
 Simon

(Pandoc author here.) It probably wouldn't make sense for a key
infrastructure component like Haddock to depend on a behemoth like
pandoc.  But I could help out with a markdown-superset parser if needed.
I have an experimental thing here that could be used as a basis (it's 7x
faster than pandoc and uses 1/5 the memory, BSD licensed):
https://github.com/jgm/Markdown

Another idea: If someone contributed a Haddock markup writer to pandoc,
then documentation could be written in markdown (or RST or whatever) and
converted automatically to standard Haddock markup.  David Lazar has
recently contributed a Haddock markup reader, but there is no writer.

Note: Creating a writer would be a bit tricky, because Haddock markup
isn't expressive enough for many of the constructions pandoc allows --
for example, if I'm not mistaken, you can't have multiple paragraphs
inside list items.  Decisions would have to be made about how to deal
with such cases.  There are also a few Haddock constructions that don't
correspond to anything in pandoc.

John


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


Re: [Haskell-cafe] Threadscope 0.2.2 goes in segmentation fault on Mac Os X 10.8.3

2013-03-30 Thread John Wiegley
 Alfredo Di Napoli alfredo.dinap...@gmail.com writes:

 I know it's a bit difficult to debug this way, I can try debugging with gdb
 if it can help.

Yes, can you show us a backtrace from gdb, and also look in your CrashReports
log folder to see if it gives a bit more information on the state of the
process at the time it died?

Thanks,
-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] introducing Maybe at managing level

2013-03-28 Thread John Lato
In FP, I think this sort of problem is generally handled via algebraic data
types rather than exceptions.  In particular this directly addresses the
issue of exceptions don't necessarily shout themselves out, since the
compiler warns you if you've missed a case.

They sound mathy, but algebraic data types are actually a pretty simple
concept.  I think the Learn You a Haskell explanation is decent:
http://learnyouahaskell.com/making-our-own-types-and-typeclasses

Provided I understand the context properly, actually using exceptions for
this sort of issue would be extremely rare practice.


On Fri, Mar 29, 2013 at 12:21 AM, luc taesch luc.tae...@gmail.com wrote:

 I was looking for some link introducing the way FP/ Haskell handles errors
 and Exceptions.

 This is for a non FP Guy, and ideally withought scaring them with Monads
 and category theory :-).

 for the background :

 the guy said : As I mentioned in another thread in banking (in particular)
 it is the exception processing that often dominates the functionality of a
 system - as the core concept is generally very straightforward. Developing
 for exception handling (not in a Java/C++ sense) is a tricky thing - as
 the exception don't necessarily shout themselves out - and are often why we
 have large misunderstood legacy systems which are hard to replace.



 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] Does GHC 7.8 make targeting bare metal ARM any easier?

2013-03-20 Thread John Meacham
kiwamu has been targeting an arm cortex-m3 succesfully with jhc. this
is a CPU with 40k of RAM running Haskell code very much on bare metal.
:)

John

On Tue, Mar 19, 2013 at 6:07 PM, Jeremy Shaw jer...@n-heptane.com wrote:
 There have been at least a couple projects, such as hOp and HaLVM
 which attempt to run GHC on the bare metal or something similar.

 Both these projects required a substantial set of patches against GHC
 to remove dependencies things like POSIX/libc. Due to the highly
 invasive nature, they are also highly prone to bitrot.

 With GHC 7.8, I believe we will be able to cross-compile to the
 Raspberry Pi platform. But, what really appeals to me is going that
 extra step and avoiding the OS entirely and running on the bare metal.
 Obviously, you give up a lot -- such as drivers, network stacks, etc.
 But, there is also a lot of potential to do neat things, and not have
 to worry about properly shutting down an embedded linux box.

 Also, since the raspberry pi is a very limited, uniform platform,
 (compared to general purpose PCs) it is feasible to create network
 drivers, etc, because only one chipset needs to be supported.
 (Ignoring issues regarding binary blobs, undocumented chipsets, usb
 WIFI, etc).

 I'm wondering if things are any easier with cross-compilation support
 improving. My thought is that less of GHC needs to be tweaked?

 - jeremy

 ___
 Glasgow-haskell-users mailing list
 glasgow-haskell-us...@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

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


Re: [Haskell-cafe] Compiled program using OpenGL fails to trigger GPU switch on Mac, but works in GHCi

2013-03-17 Thread John Lato
Hello,

Unfortunately I don't have much to add.

On Wed, Mar 13, 2013 at 9:51 PM, Jesper Särnesjö sarne...@gmail.com wrote:

 Hi everybody,

 This started out on haskell-beginners, as a question about poor
 performance for a Haskell program using OpenGL. Thanks to a few good
 suggestions there, I've managed to figure out more or less what the
 underlying problem is, but not its cause.

 In short, I have two programs, one written in Haskell [1] and one
 written in C [2], that consist of calls to the same functions, in the
 same order, to the same C library, but which do not exhibit the same
 behavior. Further, the Haskell program behaves differently when
 compiled using GHC, and when run in GHCi. I would like to know why
 this is, and how to fix it.


There are two major differences between compiled code and code run from
ghci.  First, ghci always uses the threaded runtime (compiled with
-threaded).  Second, optimization levels.

If you compile your program with -threaded, do you get the desired behavior
(e.g. does it work the same as with ghci)?

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


Re: [Haskell-cafe] [jhc] ANNOUNCE: Ajhc 0.8.0.2 Release

2013-03-16 Thread John Meacham
I have merged your changes back into the main jhc tree. Thanks!
John

On Sat, Mar 16, 2013 at 5:28 AM, Kiwamu Okabe kiw...@debian.or.jp wrote:
 We are happy to announce Ajhc 0.8.0.2.

 It's first release announce for Ajhc.
 Major change on this release is ability to compile Haskell code for tiny CPU.
 There is demo on tiny CPU at https://github.com/ajhc/demo-cortex-m3.
 And you can watch demo movie at http://www.youtube.com/watch?v=bKp-FC0aeFE.
 Perhaps changes on the announce will be merged to jhc.

 Ajhc's project web site is found at http://ajhc.masterq.net/.
 You can get Ajhc 0.8.0.2 source code from https://github.com/ajhc/ajhc/tags.

 ## Changes

 * Fix warning messages on compiling.
 * Ready to compile with GHC 7.6.2.
 * New RTS for tiny CPU. How to use:
   https://github.com/ajhc/demo-cortex-m3#porting-the-demo-to-a-new-platform

 - - -
 Metasepi team

 ___
 jhc mailing list
 j...@haskell.org
 http://www.haskell.org/mailman/listinfo/jhc

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


Re: [Haskell-cafe] Open-source projects for beginning Haskell students?

2013-03-12 Thread John Lato
There's the doctest package: http://hackage.haskell.org/package/doctest,
which looks pretty good and has a number of users (35 direct reverse deps).

It has support for cabal test integration, although I would like to see
better integration with other test tools.  But that can be added in the
test executable I suppose.

My only quibble with this suggestion is that asking beginners to do this
sort of work may do more harm than good.  It would certainly be helpful,
but I don't think most people would find it interesting.



On Tue, Mar 12, 2013 at 3:19 PM, Edward Z. Yang ezy...@mit.edu wrote:

 I also support this suggestion.  Although, do we have the build
 infrastructure
 for this?!

 Edward

 Excerpts from Michael Orlitzky's message of Mon Mar 11 19:52:12 -0700 2013:
  On 03/11/2013 11:48 AM, Brent Yorgey wrote:
  
   So I'd like to do it again this time around, and am looking for
   particular projects I can suggest to them.  Do you have an open-source
   project with a few well-specified tasks that a relative beginner (see
   below) could reasonably make a contribution towards in the space of
   about four weeks? I'm aware that most tasks don't fit that profile,
   but even complex projects usually have a few simple-ish tasks that
   haven't yet been done just because no one has gotten around to it
   yet.
 
  It's not exciting, but adding doctest suites with examples to existing
  packages would be a great help.
 
* Good return on investment.
 
* Not too hard.
 
* The project is complete when you stop typing.
 

 ___
 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] File I/O benchmark help (conduit, io-streams and Handle)

2013-03-09 Thread John Lato
On Fri, Mar 8, 2013 at 6:36 PM, Simon Marlow marlo...@gmail.com wrote:

 1GB/s for copying a file is reasonable - it's around half the memory
 bandwidth, so copying the data twice would give that result (assuming no
 actual I/O is taking place, which is what you want because actual I/O will
 swamp any differences at the software level).

 The Handle overhead should be negligible if you're only using hGetBufSome
 and hPutBuf, because those functions basically just call read() and write()
 when the amount of data is larger than the buffer size.

 There's clearly something suspicious going on here, unfortunately I don't
 have time right now to investigate, but I'll keep an eye on the thread.


Possibly disk caching/syncing issues?  If some of the tests are able to
either read entirely from cache (on the 1MB test), or don't completely sync
after the write, they could happen much faster than others that have to
actually hit the disk.  For the 60MB test, it's almost guaranteed that
actual IO would take place and dominate the timings.

John L.


 Cheers,
 Simon


 On 08/03/13 08:36, Gregory Collins wrote:

 +Simon Marlow
 A couple of comments:

   * maybe we shouldn't back the file by a Handle. io-streams does this

 by default out of the box; I had a posix file interface for unix
 (guarded by CPP) for a while but decided to ditch it for simplicity.
 If your results are correct, given how slow going by Handle seems to
 be I may revisit this, I figured it would be good enough.
   * io-streams turns Handle buffering off in withFileAsOutput. So the

 difference shouldn't be as a result of buffering. Simon: is this an
 expected result? I presume you did some Handle debugging?
   * the IO manager should not have any bearing here because file code

 doesn't actually ever use it (epoll() doesn't work for files)
   * does the difference persist when the file size gets bigger?
   * your file descriptor code doesn't handle EINTR properly, although

 you said you checked that the file copy is being done?
   * Copying a 1MB file in 1ms gives a throughput of ~1GB/s. The other

 methods have a more believable ~70MB/s throughput.

 G


 On Fri, Mar 8, 2013 at 7:30 AM, Michael Snoyman mich...@snoyman.com
 mailto:mich...@snoyman.com wrote:

 Hi all,

 I'm turning to the community for some help understanding some
 benchmark results[1]. I was curious to see how the new io-streams
 would work with conduit, as it looks like a far saner low-level
 approach than Handles. In fact, the API is so simple that the entire
 wrapper is just a few lines of code[2].

 I then added in some basic file copy benchmarks, comparing
 conduit+Handle (with ResourceT or bracket), conduit+io-streams,
 straight io-streams, and lazy I/O. All approaches fell into the same
 ballpark, with conduit+bracket and conduit+io-streams taking a
 slight lead. (I haven't analyzed that enough to know if it means
 anything, however.)

 Then I decided to pull up the NoHandle code I wrote a while ago for
 conduit. This code was written initially for Windows only, to work
 around the fact that System.IO.openFile does some file locking. To
 avoid using Handles, I wrote a simple FFI wrapper exposing open,
 read, and close system calls, ported it to POSIX, and hid it behind
 a Cabal flag. Out of curiosity, I decided to expose it and include
 it in the benchmark.

 The results are extreme. I've confirmed multiple times that the copy
 algorithm is in fact copying the file, so I don't think the test
 itself is cheating somehow. But I don't know how to explain the
 massive gap. I've run this on two different systems. The results you
 see linked are from my local machine. On an EC2 instance, the gap
 was a bit smaller, but the NoHandle code was still 75% faster than
 the others.

 My initial guess is that I'm not properly tying into the IO manager,
 but I wanted to see if the community had any thoughts. The relevant
 pieces of code are [3][4][5].

 Michael

 [1] 
 http://static.snoyman.com/**streams.htmlhttp://static.snoyman.com/streams.html
 [2]
 https://github.com/snoyberg/**conduit/blob/streams/io-**
 streams-conduit/Data/Conduit/**Streams.hshttps://github.com/snoyberg/conduit/blob/streams/io-streams-conduit/Data/Conduit/Streams.hs
 [3]
 https://github.com/snoyberg/**conduit/blob/streams/conduit/**
 System/PosixFile.hschttps://github.com/snoyberg/conduit/blob/streams/conduit/System/PosixFile.hsc
 [4]
 https://github.com/snoyberg/**conduit/blob/streams/conduit/**
 Data/Conduit/Binary.hs#L54https://github.com/snoyberg/conduit/blob/streams/conduit/Data/Conduit/Binary.hs#L54
 [5]
 https://github.com/snoyberg/**conduit/blob/streams/conduit/**
 Data/Conduit/Binary.hs#L167https://github.com/snoyberg/conduit/blob/streams/conduit/Data/Conduit/Binary.hs#L167

Re: [Haskell-cafe] File I/O benchmark help (conduit, io-streams and Handle)

2013-03-08 Thread John Lato
I'd like to point out that it's entirely possible to get good performance
out of a handle. The iteratee package has had both FD and Handle-based
IO for a while, and I've never observed any serious performance differences
between the two.  Also, if I may be so bold, Michael's supercharged copy
speeds are on par with iteratee's performance using Handles:
http://www.tiresiaspress.us/io-benchmarks.html

So while there's definitely something interesting going on here, I think it
needs a bit more investigation before suggesting that Handles should be
avoided.

For comparison, on my system I get
$ time cp input.dat output.dat

real 0m0.004s
user 0m0.000s
sys 0m0.000s

so the throughput observed on the faster times is entirely reasonable.

John L.


On Fri, Mar 8, 2013 at 4:36 PM, Gregory Collins g...@gregorycollins.netwrote:

 +Simon Marlow
 A couple of comments:

- maybe we shouldn't back the file by a Handle. io-streams does this
by default out of the box; I had a posix file interface for unix (guarded
by CPP) for a while but decided to ditch it for simplicity. If your results
are correct, given how slow going by Handle seems to be I may revisit this,
I figured it would be good enough.
- io-streams turns Handle buffering off in withFileAsOutput. So the
difference shouldn't be as a result of buffering. Simon: is this an
expected result? I presume you did some Handle debugging?
- the IO manager should not have any bearing here because file code
doesn't actually ever use it (epoll() doesn't work for files)
- does the difference persist when the file size gets bigger?
- your file descriptor code doesn't handle EINTR properly, although
you said you checked that the file copy is being done?
- Copying a 1MB file in 1ms gives a throughput of ~1GB/s. The other
methods have a more believable ~70MB/s throughput.

 G


 On Fri, Mar 8, 2013 at 7:30 AM, Michael Snoyman mich...@snoyman.comwrote:

 Hi all,

 I'm turning to the community for some help understanding some benchmark
 results[1]. I was curious to see how the new io-streams would work with
 conduit, as it looks like a far saner low-level approach than Handles. In
 fact, the API is so simple that the entire wrapper is just a few lines of
 code[2].

 I then added in some basic file copy benchmarks, comparing conduit+Handle
 (with ResourceT or bracket), conduit+io-streams, straight io-streams, and
 lazy I/O. All approaches fell into the same ballpark, with conduit+bracket
 and conduit+io-streams taking a slight lead. (I haven't analyzed that
 enough to know if it means anything, however.)

 Then I decided to pull up the NoHandle code I wrote a while ago for
 conduit. This code was written initially for Windows only, to work around
 the fact that System.IO.openFile does some file locking. To avoid using
 Handles, I wrote a simple FFI wrapper exposing open, read, and close system
 calls, ported it to POSIX, and hid it behind a Cabal flag. Out of
 curiosity, I decided to expose it and include it in the benchmark.

 The results are extreme. I've confirmed multiple times that the copy
 algorithm is in fact copying the file, so I don't think the test itself is
 cheating somehow. But I don't know how to explain the massive gap. I've run
 this on two different systems. The results you see linked are from my local
 machine. On an EC2 instance, the gap was a bit smaller, but the NoHandle
 code was still 75% faster than the others.

 My initial guess is that I'm not properly tying into the IO manager, but
 I wanted to see if the community had any thoughts. The relevant pieces of
 code are [3][4][5].

 Michael

 [1] http://static.snoyman.com/streams.html
 [2]
 https://github.com/snoyberg/conduit/blob/streams/io-streams-conduit/Data/Conduit/Streams.hs
 [3]
 https://github.com/snoyberg/conduit/blob/streams/conduit/System/PosixFile.hsc
 [4]
 https://github.com/snoyberg/conduit/blob/streams/conduit/Data/Conduit/Binary.hs#L54
 [5]
 https://github.com/snoyberg/conduit/blob/streams/conduit/Data/Conduit/Binary.hs#L167

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




 --
 Gregory Collins g...@gregorycollins.net

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


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


Re: [Haskell-cafe] File I/O benchmark help (conduit, io-streams and Handle)

2013-03-07 Thread John Lato
I would have expected sourceFileNoHandle to make the most difference, since
that's one location (write) where you've obviously removed a copy. Does
sourceFileNoHandle allocate less?

Incidentally, I've recently been making similar changes to IO code
(removing buffer copies) and getting similar speedups.  Although the
results tend to be less pronounced in code that isn't strictly IO-bound.


On Fri, Mar 8, 2013 at 2:50 PM, Michael Snoyman mich...@snoyman.com wrote:

 One clarification: it seems that sourceFile and sourceFileNoHandle have
 virtually no difference in speed. The gap comes exclusively from sinkFile
 vs sinkFileNoHandle. This makes me think that it might be a buffer copy
 that's causing the slowdown, in which case the benchmark may in fact be
 accurate.
 On Mar 8, 2013 8:30 AM, Michael Snoyman mich...@snoyman.com wrote:

 Hi all,

 I'm turning to the community for some help understanding some benchmark
 results[1]. I was curious to see how the new io-streams would work with
 conduit, as it looks like a far saner low-level approach than Handles. In
 fact, the API is so simple that the entire wrapper is just a few lines of
 code[2].

 I then added in some basic file copy benchmarks, comparing conduit+Handle
 (with ResourceT or bracket), conduit+io-streams, straight io-streams, and
 lazy I/O. All approaches fell into the same ballpark, with conduit+bracket
 and conduit+io-streams taking a slight lead. (I haven't analyzed that
 enough to know if it means anything, however.)

 Then I decided to pull up the NoHandle code I wrote a while ago for
 conduit. This code was written initially for Windows only, to work around
 the fact that System.IO.openFile does some file locking. To avoid using
 Handles, I wrote a simple FFI wrapper exposing open, read, and close system
 calls, ported it to POSIX, and hid it behind a Cabal flag. Out of
 curiosity, I decided to expose it and include it in the benchmark.

 The results are extreme. I've confirmed multiple times that the copy
 algorithm is in fact copying the file, so I don't think the test itself is
 cheating somehow. But I don't know how to explain the massive gap. I've run
 this on two different systems. The results you see linked are from my local
 machine. On an EC2 instance, the gap was a bit smaller, but the NoHandle
 code was still 75% faster than the others.

 My initial guess is that I'm not properly tying into the IO manager, but
 I wanted to see if the community had any thoughts. The relevant pieces of
 code are [3][4][5].

 Michael

 [1] http://static.snoyman.com/streams.html
 [2]
 https://github.com/snoyberg/conduit/blob/streams/io-streams-conduit/Data/Conduit/Streams.hs
 [3]
 https://github.com/snoyberg/conduit/blob/streams/conduit/System/PosixFile.hsc
 [4]
 https://github.com/snoyberg/conduit/blob/streams/conduit/Data/Conduit/Binary.hs#L54
 [5]
 https://github.com/snoyberg/conduit/blob/streams/conduit/Data/Conduit/Binary.hs#L167


 ___
 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] ANNOUNCE: Start Ajhc project with forking jhc.

2013-03-06 Thread John Meacham
What is the cortex m3 board you are experimenting with? looks like it
could be a Maple Mini https://www.sparkfun.com/products/11280 ?

if so, getting it in 20k of ram is quite impressive :) I only tested
against larger ARM processors such as tablets/cell phones.

John

On Wed, Mar 6, 2013 at 4:51 AM, Kiwamu Okabe kiw...@debian.or.jp wrote:
 Hi all.

 I am a user of jhc Haskell compiler.
 Jhc can compile Haskell code to micro arch such as Cortex-M3.
 I have written LED blinking demo for Cortex-M3 with jhc.
 Very fun!

   https://github.com/ajhc/demo-cortex-m3
   http://www.youtube.com/watch?v=3R9sogReVHg

 And I created many patches for jhc.
 But...I think that the upstream author of jhc, John Meacham,
 can't pull the contribution speedy, because he is too busy.
 It's difficult that maintain many patches without any repositories,
 for me.

 Then, I have decided to fork jhc, named Ajhc.
 # pain full...

   http://ajhc.github.com/

 I will feedback Ajhc's big changes to jhc mailing list.
 Or I am so happy if John joins Ajhc project.

 Regards,
 --
 Kiwamu Okabe

 ___
 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] Future of MonadCatchIO

2013-03-03 Thread John Lato
On Mon, Mar 4, 2013 at 12:07 AM, Ertugrul Söylemez e...@ertes.de wrote:

 Arie Peterson ar...@xs4all.nl wrote:

  Would anyone have a problem with a deprecation of
  MonadCatchIO-transformers, and a failure to update it to work with a
  base without 'block' and 'unblock'?

 Yes.  This is a simplified variant of a monad I use:

 newtype Continue f m a = Continue (m (Maybe a, f (Continue f a)))

 It's related to Cofree and has a valid and very straightforward
 MonadCatchIO instance.  However, it's probably impossible to write a
 valid MonadTransControl/MonadBaseControl instance for it.

 So I kindly ask you not to deprecate MonadCatchIO.  The reason I'm
 hesitant about moving to monad-control is that it's hard to understand
 and also very difficult to define for CPS monads.  It is commonly
 believed to be impossible.


You can always cast the continuation to a dynamic type and cast it back
later.
Doing so would typically require additional constraints, however if you're
trying to make an instance for MonadTransControl that's unfortunately not
possible (you'd need a Typeable constraint on the monad parameter, but it's
not in scope).  Lacking an appropriate MonadTransControlWithTypeable class,
it's certainly possible to fall back to various low-level, highly-dubious
constructs.  Which I of course implemented without hesitation :grin


 Also I've seen at least one article about the incorrectness of
 monad-control.  That's one further reason I like to avoid it.


I'd appreciate a link if anyone could manage to find it.  I haven't seen
any criticisms of monad-control.

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


Re: [Haskell-cafe] Future of MonadCatchIO

2013-03-03 Thread John Lato

 Also I've seen at least one article about the incorrectness of
 monad-control.  That's one further reason I like to avoid it.


 I'd appreciate a link if anyone could manage to find it.  I haven't seen
 any criticisms of monad-control.


Oddly, I just stumbled across
http://blog.ezyang.com/2012/01/monadbasecontrol-is-unsound/ from a
mostly-unrelated search.  Was this the article to which you're referring?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How does one create an input handle bound to a string instead of a file?

2013-02-28 Thread John D. Ramsdell
I think I wasn't clear about my question.  I want something that
creates a value of type System.IO.Handle.  You see, I have a high
performance S-expression parser that I'd like to use in GHCi reading
strings while at the command loop.

Here is more details on my module SExpr that exports the SExpr data
type and the load function.  The desired function is called
stringHandle.

-- An S-expression
data SExpr
= S String -- A symbol
| Q String -- A quoted string
| N Int-- An integer
| L [SExpr a]  -- A proper list

-- Read one S-expression or return Nothing on EOF
load :: Handle - IO (Maybe (SExpr Pos))

In GHCi, I want to type something like:

SExpr let h = stringHandle ()
SExpr load h
Just (L [])
SExpr load h
Nothing
SExpr

It seems to me right now that I have to implement a duplicate parser
that implements Read.  At least S-expression parsing is easy.

John

On Thu, Feb 28, 2013 at 3:02 AM, Ganesh Sittampalam gan...@earth.li wrote:
 Hi,

 On 27/02/2013 20:38, John D. Ramsdell wrote:
 How does one create a value of type System.IO.Handle for reading that
 takes its input from a string instead of a file?  I'm looking for the
 equivalent of java.io.StringReader in Java.  Thanks in advance.

 http://hackage.haskell.org/package/bytestring-handle can make handles
 that read and write to ByteStrings.

 Cheers,

 Ganesh



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


Re: [Haskell-cafe] How does one create an input handle bound to a string instead of a file?

2013-02-28 Thread John D. Ramsdell
I couldn't find the mkHandle function in the source linked to the
specified Haddock generated documentation page.

If there is a consensus that others besides myself would like a
function with the signature

stringHandle :: String - IO (Handle)

I'd be happy to contribute code.  I'd need help as I haven't ever
contributed this kind of code.

John

On Wed, Feb 27, 2013 at 10:05 PM, Bob Ippolito b...@redivi.com wrote:
 I haven't had time to make an example yet but it looks like if you go down
 to GHC.IO.Handle.Internals there's a mkHandle function that takes a
 BufferedIO and some other stuff and gives you an IO Handle.


 On Wed, Feb 27, 2013 at 3:23 PM, Gregory Collins g...@gregorycollins.net
 wrote:

 Hm, perhaps I stand corrected. Then how exactly do you make the bytestring
 Handle?


 On Thu, Feb 28, 2013 at 12:15 AM, Don Stewart don...@gmail.com wrote:

 I don't think that's right - Simon's buffer class rewrite should have
 made this possible, I think.


 http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/GHC-IO-BufferedIO.html

 On Feb 27, 2013 10:52 PM, Gregory Collins g...@gregorycollins.net
 wrote:

 On Wed, Feb 27, 2013 at 9:38 PM, John D. Ramsdell ramsde...@gmail.com
 wrote:

 How does one create a value of type System.IO.Handle for reading that
 takes its input from a string instead of a file?  I'm looking for the
 equivalent of java.io.StringReader in Java.  Thanks in advance.


 You can't. There are several libraries that purport to provide better
 interfaces for doing IO in Haskell, like conduit, pipes, enumerator, and my
 own io-streams library (http://github.com/snapframework/io-streams, soon to
 be released). You could try one of those.

 G
 --
 Gregory Collins g...@gregorycollins.net

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




 --
 Gregory Collins g...@gregorycollins.net

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



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


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


Re: [Haskell-cafe] How does one create an input handle bound to a string instead of a file?

2013-02-28 Thread John D. Ramsdell
I see now.  I read the source code incorrectly.  Now I know what to do.

John

On Thu, Feb 28, 2013 at 8:40 AM, Ganesh Sittampalam gan...@earth.li wrote:
 Hi John,

 Using bytestring-handle, you can get this with something like

 stringHandle :: String - Handle
 stringHandle s = readHandle False (Data.ByteString.Char8.pack s)

 [note the complete disregard of encoding issues in the use of
 Data.ByteString.Char8]

 Cheers,

 Ganesh

 On 28/02/2013 13:32, John D. Ramsdell wrote:
 I think I wasn't clear about my question.  I want something that
 creates a value of type System.IO.Handle.  You see, I have a high
 performance S-expression parser that I'd like to use in GHCi reading
 strings while at the command loop.

 Here is more details on my module SExpr that exports the SExpr data
 type and the load function.  The desired function is called
 stringHandle.

 -- An S-expression
 data SExpr
 = S String -- A symbol
 | Q String -- A quoted string
 | N Int-- An integer
 | L [SExpr a]  -- A proper list

 -- Read one S-expression or return Nothing on EOF
 load :: Handle - IO (Maybe (SExpr Pos))

 In GHCi, I want to type something like:

 SExpr let h = stringHandle ()
 SExpr load h
 Just (L [])
 SExpr load h
 Nothing
 SExpr

 It seems to me right now that I have to implement a duplicate parser
 that implements Read.  At least S-expression parsing is easy.

 John

 On Thu, Feb 28, 2013 at 3:02 AM, Ganesh Sittampalam gan...@earth.li wrote:
 Hi,

 On 27/02/2013 20:38, John D. Ramsdell wrote:
 How does one create a value of type System.IO.Handle for reading that
 takes its input from a string instead of a file?  I'm looking for the
 equivalent of java.io.StringReader in Java.  Thanks in advance.

 http://hackage.haskell.org/package/bytestring-handle can make handles
 that read and write to ByteStrings.

 Cheers,

 Ganesh





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


Re: [Haskell-cafe] How does one create an input handle bound to a string instead of a file?

2013-02-28 Thread John D. Ramsdell
The actual parser is a bit more complicated than I let on.  First,
it's important that not all of a file be read at the same time as the
files can be huge.  Second, it keeps track of column row position
information as an IORef, which makes sense because the ref is bundled
in a structure with the handle and manipulated only in the IO Monad in
conjunction with operations on the handle.

John

On Thu, Feb 28, 2013 at 9:00 AM, Erik Hesselink hessel...@gmail.com wrote:
 Is your parser impure? I would expect a function from
 String/Text/ByteString to Maybe (SExpr Pos).
  Then you have no need for a Handle.

 Regards,

 Erik

 On Thu, Feb 28, 2013 at 2:32 PM, John D. Ramsdell ramsde...@gmail.com wrote:
 I think I wasn't clear about my question.  I want something that
 creates a value of type System.IO.Handle.  You see, I have a high
 performance S-expression parser that I'd like to use in GHCi reading
 strings while at the command loop.

 Here is more details on my module SExpr that exports the SExpr data
 type and the load function.  The desired function is called
 stringHandle.

 -- An S-expression
 data SExpr
 = S String -- A symbol
 | Q String -- A quoted string
 | N Int-- An integer
 | L [SExpr a]  -- A proper list

 -- Read one S-expression or return Nothing on EOF
 load :: Handle - IO (Maybe (SExpr Pos))

 In GHCi, I want to type something like:

 SExpr let h = stringHandle ()
 SExpr load h
 Just (L [])
 SExpr load h
 Nothing
 SExpr

 It seems to me right now that I have to implement a duplicate parser
 that implements Read.  At least S-expression parsing is easy.

 John

 On Thu, Feb 28, 2013 at 3:02 AM, Ganesh Sittampalam gan...@earth.li wrote:
 Hi,

 On 27/02/2013 20:38, John D. Ramsdell wrote:
 How does one create a value of type System.IO.Handle for reading that
 takes its input from a string instead of a file?  I'm looking for the
 equivalent of java.io.StringReader in Java.  Thanks in advance.

 http://hackage.haskell.org/package/bytestring-handle can make handles
 that read and write to ByteStrings.

 Cheers,

 Ganesh



 ___
 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] How does one create an input handle bound to a string instead of a file?

2013-02-27 Thread John D. Ramsdell
How does one create a value of type System.IO.Handle for reading that
takes its input from a string instead of a file?  I'm looking for the
equivalent of java.io.StringReader in Java.  Thanks in advance.

John

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


Re: [Haskell-cafe] ANN: lazy-csv - the fastest and most space-efficient parser for CSV

2013-02-25 Thread John Wiegley
 Malcolm Wallace malcolm.wall...@me.com writes:

 Simple answer - I have never heard of cassava, and suspect it did not exist
 when I first did the benchmarking. I'd be happy to re-do my performance
 comparison, including cassava and any other recent-ish CSV libraries, if I
 can find them.

I would be very interested in those results, Malcolm.

Thanks,
-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


[Haskell-cafe] searching the attic for lambada

2013-02-13 Thread John Lask


I'm interested in resurrecting the idl generator from lambada:

http://www.dcs.gla.ac.uk/mail-www/haskell/msg02391.html

is the code out there in anyone's attic?


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


[Haskell-cafe] Structured Graphs

2013-02-12 Thread John Sharley
What are the prospects for Haskell supporting Structured Graphs as defined here?
http://www.cs.utexas.edu/~wcook/Drafts/2012/graphs.pdf

Is there an interest by developers of GHC in doing this?

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


Re: [Haskell-cafe] Use forM_ with Maybe, it's Foldable!

2013-01-26 Thread John Wiegley
 Felipe Almeida Lessa felipe.le...@gmail.com writes:

 A few days ago I decided to hoogle the type of whenJust [2] and what I
 discovered is that

   import Data.Foldable (forM_)
   whenJust = forM_

You can also use for_, if you want to use Applicative instead of Monad.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] ANN: monad-bool 0.1

2013-01-23 Thread John Wiegley
 Petr P petr@gmail.com writes:

 Don't take it so hard. Trying to reinvent something is always a great
 exercise and makes you really understand the problem. And it can have
 interesting results too. One of my university professors once heard about
 some concept, but didn't know the details. He tried to derive the concept
 himself, and he actually invented something different, new and very useful.

Thank you very much to everyone for the encouragement, and especially to
Edward and Shachaf for the education on #haskell.  It will be hard to unlearn
a lesson like this one. :)  And I will certainly endeavor to make the most
valuable mistakes I can from here on, with the help of such a gracious
community. :)

Yours,
-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


[Haskell-cafe] ANN: monad-bool 0.1

2013-01-22 Thread John Wiegley
monad-bool implements a pair of Boolean monoids and monads, to support
short-circuiting, value-returning computations similar to what Python and Ruby
offer with their native  and || operators.

For example, in Python you might see this:

x = [1,2,3,0]
print x[1] || x[3]   -- prints 2

With this library, you can now mirror such code in Haskell:

let x = [1,2,3,0]
print $ (x !! 1) ||? (x !! 3)   -- prints Success 2

Booleanness is based on each type having an instance of the
'Control.Conditional.ToBool' type, for which only the basic types are covered
(Bool, Int, Integer, Maybe a, Either a b, [a], Attempt a).  If you wish to
define a truth value for your own types, simply provide an instance for
ToBool:

instance ToBool MyType where
toBool = ...

The And/Or monoids use the Attempt library so that the actual type of the
successful results depends on case analysis.  It could be a list, a Maybe, an
Either, or an exception in the IO Monad.

The monad variants, AndM, AndMT, OrM and OrMT provide short-circuiting
behavior in a Monad, which returns the last value returned before truth was
determined.  Here are two examples:

Use 'onlyIf' with AndM and AndMT to guard later statements, which are only
evaluated if every preceding 'onlyIf' evaluates to True.  For example:

foo :: AndM Int
foo = do onlyIf (True == True)
 return 100
 onlyIf (True == True)
 return 150
 onlyIf (True == False)
 return 200

When run with `evalAndM foo (-1)` (where (-1) provides a default value), 'foo'
returns 150.

Use 'endIf' with OrM and OrMT to chain statements, which are only executed if
every preceding 'endIf' evaluated to False.  For example:

bar :: OrM Int
bar = do endIf (True == False)
 return 100
 endIf (True == False)
 return 150
 endIf (True == True)
 return 200

When run with `evalOrM bar (-1)` (where (-1) again provides a default value),
'bar' returns 150.

And please, somebody let me know if this has already been done.  A search for
likely candidates did not turn up anything obvious in Hoogle, but as my
knowledge of the whole of Hackage is minimal, I would appreciate any wiser
minds that can inform me.

Thank you,
-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] [Haskell] ANN: monad-bool 0.1

2013-01-22 Thread John Wiegley
 Henning Thielemann lemm...@henning-thielemann.de writes:

 Does the And monad fulfill the monad laws? In a proper monad an interim
 (return x) (without a '-') is a no-op.

You are very right.  I will make the necessary changes.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


  1   2   3   4   5   6   7   8   9   10   >