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

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

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


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


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] 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] 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] 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] 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] edge: compile testing

2012-12-16 Thread John Lato

 From: Christopher Howard christopher.how...@frigidcode.com

 On 12/14/2012 07:05 PM, Clark Gaebel wrote:
  Unacceptable argument type in foreign declaration

 Thanks for giving it a try. Could you send off a bug report to the
 OpenAL Haskell module maintainer? sven.pa...@aedion.de

 (I might offer to do it, but I tried to e-mail him once about a
 different issue and never heard back. Probably didn't make it through
 his spam filter.)


I think Sven's been incommunicado for a few years now.  Most likely
somebody else will need to step forward as the OpenAL maintainer, if
there's interest in keeping that package current.

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


Re: [Haskell-cafe] Motion to unify all the string data types

2012-11-11 Thread John Lato

 From: Francesco Mazzoli f...@mazzo.li

 At Sat, 10 Nov 2012 15:16:30 +0100,
 Alberto G. Corona  wrote:
  There is a ListLike package, which does this nice abstraction. but I
 don't
  know if it is ready for and/or enough complete for serious usage.  I?m
  thinking into using it for the same reasons.
 
  Anyone has some experiences to share about it?

 I've used it in the past and it's solid, it's been around for a while and
 the
 original author knows his Haskell.

 Things I don't like:

 * The classes are huge:
   
 http://hackage.haskell.org/packages/archive/ListLike/3.1.6/doc/html/Data-ListLike.html#t:ListLike
 .
   I'd much rater prefer to have all those utilities functions outside the
 type
   class, for no particular reason other then the ugliness of the type
 class.


Speaking as the ListLike maintainer, I'd like this too.  But it's difficult
to do so without sacrificing performance.  In some cases, sacrificing *a
lot* of performance.  So they have to be class members.

However, there's no reason ListLike has to remain a single monolithic
class.  I'd prefer an API that's split up into several classes, as was done
in Edison.  Then 'ListLike' itself would just be a type synonym, or
possibly a small type class with the appropriate superclasses.

However this seems like a lot of work for relatively little payoff, which
makes it a low priority for me.

* It defines its own wrappers for `ByteString':
   
 http://hackage.haskell.org/packages/archive/ListLike/3.1.6/doc/html/Data-ListLike.html#t:CharString
 .


The community's view on newtypes is funny.  On the one hand, I see all the
time the claim Just use a newtype wrapper to write instances for ...
(e.g. the recent suggestion of 'instance Num a = Num (a,a)'.  On the
other, nobody actually seems to want to use these newtype wrappers.  Maybe
it clutters the code?  I don't know.

I couldn't think of a better way to implement this functionality, patches
would be gratefully accepted.  Anyway, you really shouldn't use these
wrappers unless you're using a ByteString to represent ASCII text.  Which
you shouldn't be doing anyway.  If you're using a ByteString to represent a
sequence of bytes, you needn't ever encounter CharString.


 * It doesn't have instances for `Text', you have to resort to the
   `listlike-instances' package.


Given that text and vector are both in the Haskell Platform, I wouldn't
object to these instances being rolled into the main ListLike package.  Any
comments on this?

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


Re: [Haskell-cafe] A clarification about what happens under the hood with foldMap

2012-10-23 Thread John Lato
 From: Alfredo Di Napoli alfredo.dinap...@gmail.com
 Subject: [Haskell-cafe] A clarification about what happens under the
 hoodwith foldMap

 I'm sure I'm missing a point, but the minimum definition for a Foldable
 instance is given in terms of foldMap, so I get the cake for free, foldr
 included, right?
 In the example I have defined my treeSum as:

 treeSum = Data.Foldable.foldr (+) 0

 So the only thing Haskell knows it that I want to fold over a Foldable for
 which foldMap (and therefore foldr) is defined, and specifically I want to
 fold using (+) as function.
 But foldMap is defined in terms of f, which in this case is Sum, because I
 want to sum things. It it were (*) f would have been Product, right?

 So what I'm missing is the relation between foldMap and foldr, aka How
 Haskell infer from (+) that I want f = Sum and not something different?

What you're missing is that this isn't how foldr is defined.  As you
probably suspect, it isn't possible for Haskell to deduce f = Sum
from just the function.  And in general the function parameter to
foldr isn't even equivalent to mappend for any monoid, because it
operates on two values with different types.  Rather, foldr is defined
using the Endo monoid, which is

 newtype Endo a = Endo (a - a)

instance Monoid (Endo a) where
mempty = id
mappend = (.)

Here's the default instance of Data.Foldable.foldr

 foldr :: (a - b - b) - b - t a - b
 foldr f z t = appEndo (foldMap (Endo . f) t) z

What happens is that, as the tree is traversed, Leaf constructors are
replaced with 'id' (mempty :: Endo b), and branch values are replaced
with 'Endo . f', where f = (+) in this example.  Look at Endo . f:

-- Endo :: (b - b) - Endo b
-- f :: a - (b - b)
-- Endo . f :: a - Endo b

so at each branch (Endo . f) is applied to the value, resulting in the
type 'Endo b'

foldMap just composes everything together with mappend, which, after
the Endo constructor is removed, is a giant function pipeline :: b -
b, which is then applied to the provided base value (0 here).

John L.

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


Re: [Haskell-cafe] Either Monad and Laziness

2012-09-17 Thread John Lato
 Subject: Re: [Haskell-cafe] Either Monad and Laziness

 On 9/14/12 5:16 PM, Eric Velten de Melo wrote:
 But now I'm kinda lost. Is there an easy way to explain the difference 
 between:
 -iteratee
 -conduit
 -enumerator

I tend to group them into three families.  'iteratee' and 'enumerator'
are fairly directly drawn from Oleg's code, with mostly implementation
differences (at least when compared to the other families).  They've
tended to keep Oleg's original names (iteratee, enumerator,
enumeratee).

The biggest user-visible difference between iteratee and enumerator is
the level of datastream abstraction.  iteratee abstracts over the
stream, and enumerator abstracts over elements of the stream.  The
stream is explicitly a list of elements.  This exposes some of the
details of data chunking to the user, which has both advantages and
disadvantages (iteratee exposes this also, but it's not necessary as
is the case for enumerator).

The second family (chronologically) includes conduit and (maybe)
iterIO.  I've written a little about this group at
http://johnlato.blogspot.sg/2012/06/understandings-of-iteratees.html
Although they serve the same goals in spirit, the implementation may
or may not necessarily be an iteratee/enumerator arrangement (e.g.
conduit).  This is a technical observation, not a criticism, depending
on exactly what you consider to define the style in the first place.
This group has usually renamed functions.  I discuss some of the other
differences on my blog.

The third familiy is all the pipes-* stuff.  This group tends towards
emphasizing the relationship between iteratee/enumerator pairs and
coroutines, and also emphasizing (to use Oleg terminology) composition
of enumeratees.  I've been meaning to write more about this group, but
thus far have been unable to do so.

I'd rather not hijack by evangelizing, but obviously I think iteratee
provides several important advantages over the other options.

John L.

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


Re: [Haskell-cafe] Haskell-Cafe Digest, Vol 106, Issue 38

2012-06-26 Thread John Lato
 Message: 12
 Date: Wed, 27 Jun 2012 00:19:30 +0200
 From: Tillmann Rendel ren...@informatik.uni-marburg.de
 Subject: Re: [Haskell-cafe] Martin Odersky on What's wrong with
        Monads
 Cc: haskell-cafe@haskell.org
 Message-ID: 4fea3572.5060...@informatik.uni-marburg.de
 Content-Type: text/plain; charset=ISO-8859-1; format=flowed

 Hi,

 MightyByte wrote:
 Of course every line of your program that uses a Foo will change if you 
 switch
 to IO Foo instead.

 But we often have to also change lines that don't use Foo at all. For
 example, here is the type of binary trees of integers:

   data Tree = Leaf Integer | Branch (Tree Integer) (Tree Integer)

 A function to add up all integers in a tree:

   amount:: Tree - Integer
   amount (Leaf x) = x
   amount (Branch t1 t2) = amountt1 + amountt2

 All fine so far. Now, consider the following additional requirement: If
 the command-line flag --multiply is set, the function amount computes
 the product instead of the sum.

 In a language with implicit side effects, it is easy to implement this.
 We just change the third line of the amount function to check whether to
 call (+) or (*). In particular, we would not touch the other two lines.

 How would you implement this requirement in Haskell without changing the
 line amount (Leaf x) = x?

Why would you do that even in an imperative language?  The program
logic turns into a spaghetti mess, and it's much harder to test.

I would write Tree like this:

data Tree a = Leaf a | Branch (Tree a) ( Tree a)
  deriving (Foldable, Show)

and instead of an amount function I would use a fold.  If you like,
you can use ala from Control.Newtype

*Main Data.Foldable Data.Monoid let t1 = Branch (Leaf 1) (Branch
(Leaf 4) (Leaf 5)) :: Tree Int
*Main Data.Foldable Data.Monoid ala Sum foldMap t1
10
*Main Data.Foldable Data.Monoid ala Product foldMap t1
20

Now the amount calculation can be something like

amount :: Num a = Tree a - IO a
amount tree = multFlag = \b - if b then ala Product foldMap tree
else ala Sum foldMap tree


although I probably wouldn't actually write it unless it was called in
more than one place.  There are other ways to write it too; the
important part is that checking the configuration is completely
separate from the tree traversal.

Plus, if it changes again (now there's another flag that says to
ignore values == n or something, you can use the same fold, just
change the function that's passed to it (or the monoid instance if
you're using that).

Plus, this type of code is much simpler to debug, test, and maintain
than imperative-style magic functions.

Cheers,
John

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


Re: [Haskell-cafe] Haskell-Cafe Digest, Vol 106, Issue 38

2012-06-26 Thread John Lato
On Wed, Jun 27, 2012 at 9:15 AM, Richard O'Keefe o...@cs.otago.ac.nz wrote:

 On 27/06/2012, at 12:51 PM, John Lato wrote:

 data Tree a = Leaf a | Branch (Tree a) ( Tree a)
  deriving (Foldable, Show)

 While I am familiar with deriving (Show),
 I am not familiar with deriving (Foldable),
 which looks rather useful.

 http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/deriving.html
 just says With -XDeriveFoldable, you can derive instances of the
 class Foldable, defined in Data.Foldable. but it provides no details.

 Would you care to explain more about deriving (Foldable)?

There's not much to explain, DeriveFoldable basically does just that;
automatically provide an instance of the Foldable class for a data
type.  I think the original proposal for DeriveFoldable was from Twan
van Laarhoven, 
http://www.mail-archive.com/haskell-prime@haskell.org/msg02116.html,
and there's a little bit of history on GHC's trac,
http://hackage.haskell.org/trac/ghc/ticket/2953.  The current
implementation probably hasn't changed much since Simon PJ's original
patch, although there's probably substantial overlap with ghc's
generics these days.

As for the Foldable class itself, the docs at
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Foldable.html
are pretty good.  It lets you perform a number of folds (left, right,
monoidal) over arbitrary datatypes, not just lists.

I think that's about it.  Although I'm not the best person to explain
either the DeriveFoldable algorithm or the different uses of folds;
maybe someone else would be able to fill in anything I've missed.

John L.

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


Re: [Haskell-cafe] Google Summer of Code - Lock-free data

2012-03-29 Thread John Lato
Slightly related: I think it would be interesting to compare a
Disruptor-based concurrency communications mechanism and compare it to
e.g. TChans

1.  Disruptor - http://code.google.com/p/disruptor/

 From: Ryan Newton rrnew...@gmail.com

 I think so. Atomically reading and writing a single memory location
 (which CAS does) is just a very simple transaction. But using a CAS
 instruction should be more efficient, since STM has to maintain a
 transaction log and commit transactions, which creates some overhead.


 Ah, I see. In that case, it may be worthwhile to implement the CAS
 instruction in terms of STM as well and measure the performance difference
 this makes for the final data structure. After all, STM is a lot more
 compositional than CAS, so I'd like to know whether the loss of
 expressiveness is worth the gain in performance.


 There's one annoying hitch with doing apples-to-apples comparisons here.

 The problem is that CAS falls short of being a hardware-accelerated version
 of a simple transaction (read TVar, (==) against expected value,
 conditionally update TVar), because CAS is based on pointer equality rather
 than true equality.  (eq? rather than equal? for any Schemers out there.)

 For this reason our Fake version of CAS -- for older GHCs and for
 performance comparison -- has to use reallyUnsafePointerEquality#:


 http://hackage.haskell.org/packages/archive/IORefCAS/0.2/doc/html/Data-CAS-Internal-Fake.html

 But we do provide a CASable type class in that package which is precisely
 for comparing the performance of:

   - Hardware CAS
   - Fake CAS -- atomicModifyIORef + ptrEquality
   - Foreign CAS -- gcc intrinsic + function call

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


[Haskell-cafe] difficulty building (some) TH packages with ghc-7.4.1

2012-03-26 Thread John Lato
Hello,

I've run into an odd problem when building certain packages that use
Template Haskell with GHC-7.4.1.  For example, RepLib:

$ cabal --version
cabal-install version 0.13.3
using version 1.14.0 of the Cabal library

$ cabal install -O2 -w ~/.ghc-7.4.1/bin/ghc RepLib --reinstall
Resolving dependencies...
Configuring RepLib-0.5.2...
Building RepLib-0.5.2...
Preprocessing library RepLib-0.5.2...
[ 1 of 12] Compiling Generics.RepLib.R ( Generics/RepLib/R.hs,
dist/build/Generics/RepLib/R.o )
[ 2 of 12] Compiling Generics.RepLib.R1 ( Generics/RepLib/R1.hs,
dist/build/Generics/RepLib/R1.o )
[ 3 of 12] Compiling Generics.RepLib.Derive (
Generics/RepLib/Derive.hs, dist/build/Generics/RepLib/Derive.o )
[ 4 of 12] Compiling Generics.RepLib.PreludeReps (
Generics/RepLib/PreludeReps.hs,
dist/build/Generics/RepLib/PreludeReps.o )
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package type-equality-0.1.0.2 ... linking ... done.
Loading package array-0.4.0.0 ... linking ... done.
Loading package deepseq-1.3.0.0 ... linking ... done.
Loading package containers-0.4.2.1 ... linking ... done.
Loading package pretty-1.1.1.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
Loading package transformers-0.2.2.0 ... linking ... done.
Loading package mtl-2.0.1.0 ... linking ... done.
cabal: Error: some packages failed to install:
RepLib-0.5.2 failed during the building phase. The exception was:
ExitFailure 11

This is without library profiling enabled.  If I enable library
profiling, the unprofiled build is fine but the profiled build exits
with the same error, at the same location.

If I pass the -v argument to cabal-install, the package builds fine
with profiling disabled.  The -v flag makes no difference with
profiling enabled, although some packages (but not RepLib) work with
-v2

I haven't seen this with ghc-7.2.*, but I'm guessing this is some sort
of cabal-install bug.  Has anyone else witnessed anything like this?

Thanks,
John L.

___
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?

2012-03-23 Thread John Lato
 From: Heinrich Apfelmus apfel...@quantentunnel.de

 Tom Murphy wrote:
      If you want to do Haskell audio synthesis, you could also use
 hsc3 (good start here: http://slavepianos.org/rd/ut/hsc3-texts/). With
 hsc3 you can start on serious audio synthesis with only a few lines of
 Haskell. In my opinion it could use a much larger community.

 While Rohan's bindings to SuperCollider are great, I have found that
 SuperCollider itself is quite difficult to understand for a new user.
 (My tomata-rubato project aims to be much easier to learn.)

 Also, as far as I am aware, you can't do low-level audio programming in
 SuperCollider, i.e. play a list of samples that you've calculated
 yourself. That's cool if you're only interested in sound design, but bad
 for learning how audio programming works.

I think this charge is a bit unfair.  If you really want to do
low-level stuff, it's possible within SC.  You just have to work in
SuperCollider, not Haskell (AFAIK).

However, it is possible to transfer audio data between Haskell and
Csound, in several ways.  The hCsound package comes with some examples
of transferring the audio input and output streams between csound and
haskell.  Named channels provide for even more complicated routing if
you like.

John L.

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


Re: [Haskell-cafe] Clarifying a mis-understanding about regions (and iteratees)

2012-02-23 Thread John Lato
ResourceT really addresses a different problem.  Specifically, the
issue of how to guarantee that finalizers will run in the context of
short-circuiting monadic effects.  It does this by providing a single
region (not nested regions as Oleg describes) as the base of the monad
stack, ensuring that any short-circuiting effects still need to go
through the ResourceT layer's finalization steps.

Same implementation strategy, different goal.

It doesn't provide nested regions, although you may be able to stack
multiple ResourceT's on top of each other (I have no idea if this
works or not) to do so.

The regions package (http://hackage.haskell.org/package/regions) is
another implementation predating ResourceT.  I don't know why it never
caught on, except perhaps that at announcement time it was a solution
without a problem.

John L.

 From: Yves Par?s yves.pa...@gmail.com

 Hi, so there are different regions libraries?
 Is there a shootout comparing them, possibly also with ResourceT from
 conduit (which has also been implemented in a stand-alone package
 http://hackage.haskell.org/package/resource-simple-0.1 by Robin Banks), for
 I take it it tries to respond to the same problem?

 2012/2/23 o...@okmij.org


 I have just come across the reddit discussion about regions and
 iteratees.

 http://www.reddit.com/r/haskell/comments/orh4f/combining_regions_and_iteratees/

 There is an unfortunate misunderstanding about regions which I'd like to
 correct. I'm posting in Cafe in hope that some of the participants of
 that discussion read Haskell-Cafe (I'm not a redditor).

 The user Faucelme wrote:
  Would it be possible to implement a region-based iteratee which opened
 some
  file A and wrote to it, then opened some file B and wrote to it,
 while
  ensuring that file A is closed before file B is opened?

 To which the user tibbe replied
  You can typically explicitly close the files as well.

 and the user dobryak commented

  Regions that Oleg refers to started out with region-based memory
 allocation,
  which is effectively a stack allocation strategy, in which resource
  deallocation is in LIFO order. So I think your assumption is correct.

 Regretfully, these comments are incorrect. First of all, memory
 regions were invented to get around the stack allocation, LIFO
 strategy. If the stack allocation sufficed, why do we need heap?  We
 have heap specifically because the memory allocation patterns are
 complex: a function may allocate memory that outlives it.  Regions
 let the programmer create arbitrarily many nested regions; everything
 in a parent region is available to a child. Crucially, a child may
 request any of its ancestors to allocate memory in their
 regions. Therefore, although regions are nested, memory does not have
 to be allocated and freed in LIFO order.

 The Lightweight monadic regions implement all these patterns for files
 or other resources (plus the dynamic bequest).
        http://okmij.org/ftp/Computation/resource-aware-prog/region-io.pdf

 The running example of the Haskell Symposium 08 paper was the
 following (see sec 1.1)

 1. open two files for reading, one of them a configuration file;
 2. read the name of an output file (such as the log file) from the
   configuration file;
 3. open the output file and zip the contents of both input files into
   the output file;
 4. close the configuration file;
 5. copy the rest, if any, of the other input file to the output file.

 As you can see, the pattern of opening and closing is non-LIFO: the
 output file has to be opened after the configuration file and is
 closed also after the configuration file. Therefore, the user Faucelme
 can find the solution to his question in the code accompanying the
 Monadic Regions paper.

 Section 5 of the paper describes even more complex example:

 1. open a configuration file;
 2. read the names of two log files from the configuration file;
 3. open the two log files and read a dated entry from each;
 4. close the configuration file and the newer log file;
 5. continue processing the older log file;
 6. close the older log file.

 where the pattern of opening and closing is not statically known:
 it is decided on values read from the files.

 So, Faucelme's question can be answered in affirmative using the
 existing RegionIO library (which, as has been shown, well integrates
 with Iteratees). There is already a region library with the desired
 functionality.



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

 -- next part --
 An HTML attachment was scrubbed...
 URL: 
 http://www.haskell.org/pipermail/haskell-cafe/attachments/20120223/b14ad2b2/attachment.htm

 --

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


 End of Haskell-Cafe Digest, 

[Haskell-cafe] How to increase performance using concurrency for sequential producer-consumer problem

2012-02-14 Thread John Lato
I would use bounded STM channels (from the stm-chans package) for
communication; this would keep the producer from getting too far ahead
of the converters.  You'd need to tag items as they're produced (an
Integer should be fine) also, and keep track of the tags.  A TVar
should suffice for that.  The basic outline is that the producer
writes to a channel.  Each converter thread reads from that channel,
and when it's finished, checks the output index TVar.  If the
converter's item index is equal to the current output index,the
converter puts its value into an output channel and increments the
output index.  A final consumer reads from the output channel and
processes each item in turn.

Or instead of a bounded input channel, the producer could write to a
TMVar.  Which is better probably depends on the details of your
production pattern.

You certainly could use something like iteratee-stm or the conduits
variant, but they wouldn't directly help with concurrency of
converters, nor with synchronization.  What they would give you is
concurrency between the producer, converter, and consumer.  Of course
you could build your own converter step to work within that framework.

John L.

 Date: Mon, 13 Feb 2012 16:12:22 +0100
 From: Roel van Dijk vandijk.r...@gmail.com
 Subject: [Haskell-cafe] How to increase performance using concurrency
        for sequential producer-consumer problem
 To: Haskell Caf? haskell-cafe@haskell.org
 Message-ID:
        cabw4ky7pu_rjsj5hq_7gs_vtqv-da4iyv0vhey_j1yxxybl...@mail.gmail.com
 Content-Type: text/plain; charset=UTF-8

 Hello,

 I have a program which I believe can benefit from concurrency. But I
 am wondering if the mechanisms I need already exist somewhere on
 Hackage.

 Here is a sketch of my program, in literate Haskell:

 module Problem where
 import Control.Monad ( forM_ )

 The producer produces values. It blocks until there are now more
 values to produce. Each value is given to a callback function.

 type Producer a = (a - IO ()) - IO ()

 The converter does some work with a value. This work is purely CPU and
 it is the bottleneck of the program. The amount of work it has to do
 is variable.

 type Converter a b = a - b

 The consumer does something with the value calculated by the
 converter. It is very important that the consumer consumes the values
 in the same order as they are produced.

 type Consumer b = b - IO ()

 Dummy producer, converter and consumer:

 producer :: Producer Int
 producer callback = forM_ [1..10] callback

 converter :: Converter Int Int
 converter = (*10)

 consumer :: Consumer Int
 consumer = print

 A simple driver. Does not exploit concurrency.

 simpleDriver :: Producer a - Converter a b - Consumer b - IO ()
 simpleDriver producer converter consumer = producer (consumer . converter)

 current_situation :: IO ()
 current_situation = simpleDriver producer converter consumer

 Ideally I would like a driver that spawns a worker thread for each
 core in my system. But the trick is in ensuring that the consumer is
 offered results in the same order as they are generated by the
 producer.

 I can envision that some kind of storage is necessary to keep track of
 results which can not yet be offered to the consumer because it is
 still waiting for an earlier result.

 Is there any package on Haskell that can help me with this problem? Or
 do I have to implement it using lower level concurrency primitives?

 Regards,
 Roel



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


Re: [Haskell-cafe] ANN: stm-conduit-0.2.1

2012-02-13 Thread John Lato
 Message: 6
 Date: Sun, 12 Feb 2012 01:47:40 -0500
 From: wren ng thornton w...@freegeek.org
 Subject: Re: [Haskell-cafe] ANN: stm-conduit-0.2.1
 To: Haskell Cafe haskell-cafe@haskell.org
 Message-ID: 4f37608c.3090...@freegeek.org
 Content-Type: text/plain; charset=ISO-8859-1; format=flowed

 On 2/9/12 2:29 PM, Felipe Almeida Lessa wrote:
 Your package uses TMChans which AFAIK are unbounded.  That means that
 if the writer is faster than the reader, then everything will be kept
 into memory.  This means that using TMChans you may no longer say that
 your program uses a constant amount of memory.  Actually, you lose a
 lot of your space reasoning since, being concurrent processes, you
 can't guarantee almost anything wrt. progress of the reader.

 Of course, you're free to use TBMChans instead, which are bounded :)

This is what I did in iteratee-stm.  The stm-chans package is very nice.

(and the results with iteratee-stm were very good as well)

John L.

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


[Haskell-cafe] interest in Irish Haskell User's Group?

2012-01-24 Thread John Lato
Hello,

Some other Haskellers and I have been discussing starting an Irish
Haskell User's Group.  I think we're close to critical mass, and need
just a few more interested people to give it a run.  To that end, I'd
appreciate hearing from anyone who would be interested in attending or
participating.

Our initial meeting would likely be in Maynooth as that's where we're
based, however we'd like to see involvement across at least the
greater Dublin area, and possibly further afield.

So, please let me know if you're interested in participating.  I'll
post further details when we've established an initial meeting.

Thanks,
John L.

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


Re: [Haskell-cafe] How to terminate the process group of a process created with createProcess?

2012-01-12 Thread John Lato
 From: Brandon Allbery allber...@gmail.com

 On Wed, Jan 11, 2012 at 16:26, Andr? Scholz andre.sch...@uni-bremen.dewrote:

 (on unix) creating a process A which spawns itself a subprocess B and
 terminating process A before it finishes leaves process B as a process on
 its
 own. This is because terminateProcess sends the sigterm signal to the
 process only and not to its process group.


 terminateProcess passes on the semantics of kill(2); on SVID-compliant (and
 I think POSIX.1-compliant) systems, the negative of the process group
 leader's process ID is used to signal the process group.  Note that you may
 need to arrange for your initial child process to invoke setpgrp() to
 insure that the parent program is not part of the process group.

System.Process.terminateProcess takes a ProcessHandle as input, which
is an opaque type which essentially can only be created via
System.Process.createProcess or similar; it's not possible to pass
arbitrary pid's to it.

However, on Posix systems it is currently possible (ghc-7.2.1) to
import System.Process.Internals, which would allow you to either
create a new ProcessHandle from an arbitrary pid or retrieve the pid
from a ProcessHandle.  My answer on SO now shows how to do so.  Of
course this approach won't be portable, and it may change depending on
your compiler version.

(link to SO: 
http://stackoverflow.com/questions/8820903/haskell-how-to-timeout-a-function-that-runs-an-external-command/
)

John L.

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


Re: [Haskell-cafe] GHC exceeding command line length limit with split-objs - and a possible fix

2012-01-11 Thread John Lato
I used https://github.com/kennethreitz/osx-gcc-installer/downloads to
get a real gcc on Lion.  Biggish download, but it worked.  I've also
seen reports of success by self-compiling gcc, or by installing XCode
4 on top of an existing XCode 3 installation.

John L.

 From: Eugene Kirpichov ekirpic...@gmail.com

 Oh well... looks like building ghc won't be easy, as it doesn't build with
 llvm-gcc and it's not easy to get a real gcc on Lion. But I don't stop
 trying :)

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


Re: [Haskell-cafe] typeclass and functional dependency problem

2012-01-10 Thread John Lato
 From: Martin DeMello martindeme...@gmail.com
 Subject: [Haskell-cafe] typeclass and functional dependency problem

 I'm writing a Gtk2hs app, and I have several custom widgets that are
 composite objects represented by records, one field of which is a
 container widget. I am trying to write a replacement for gtk2hs's
 boxPackStart

 boxPackStart :: (BoxClass self, WidgetClass child) = self - child -
 Packing - Int - IO ()

 that will accept either a gtk widget or one of my custom widgets to
 place in the box, and do the right thing. Here's my attempt at it;
 what I want to know is why the commented out bit didn't work and I had
 to individually add instances of widgets instead:

 -
 -- packable objects
 class WidgetClass w = Packable a w | a - w where
    widgetOf :: a - w

 --instance WidgetClass w = Packable w w where
 --    widgetOf = id

 instance Packable Button Button where
    widgetOf = id

 instance Packable Entry Entry where
    widgetOf = id

 instance Packable Label Label where
    widgetOf = id

 instance Packable Notebook Notebook where
    widgetOf = id

 instance Packable HBox HBox where
    widgetOf = id

 -- add widget to box
 boxPackS :: (BoxClass b, WidgetClass w, Packable a w) = b - a -
 Packing - Int - IO ()
 boxPackS box child p i = boxPackStart box (widgetOf child) p i

 -

 If I try to use

 instance WidgetClass w = Packable w w where
    widgetOf = id

 instead, I get the compilation error

 Editor.hs:23:10:
    Functional dependencies conflict between instance declarations:
      instance Packable PairBox VBox -- Defined at Editor.hs:23:10-30
      instance WidgetClass w = Packable w w
        -- Defined at GuiUtils.hs:13:10-38

 even though PairBox does not belong to WidgetClass.

This is a very common problem.  The line

 instance WidgetClass w = Packable w w where

means Every type is an instance of Packable by this declaration, not
Every type that has a WidgetClass instance is a Packable by this
declaration, which is what you wanted.  So you end up with two
Packable instances for PairBox, Packable PairBox PairBox and
Packable PairBox Container (or whatever type you used), which causes
this conflict.

This is a consequence of Haskell type classes being open.  Even if you
don't have a WidgetClass instance for a type (PairBox) in scope where
you define this instance, one could be defined elsewhere and be in
scope at a call site.

Unfortunately Haskell doesn't provide a way to write what you want.  I
can think of a few solutions, none of which are ideal:

1.  Create separate instances for each type.  Writing some generating
code to do this is probably the best available option.
2.  Convert everything to a Container.
3.  Make boxPackS a TH splice, and use a naming convention to
differentiate your objects from the built-in widgets.

I don't like 3) because it's fragile.  Pretty much everything else is
a variant of either 1 (lots of instance decls) or 2 (another function
call/separate functions).

John L.

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


[Haskell-cafe] Haskell meta-programming

2011-12-21 Thread John Lato
 From: Heinrich Apfelmus apfel...@quantentunnel.de

 * Meta-programming / partial evaluation. When designing a DSL, it is
 often the case that you know how to write an optimizing compiler for
 your DSL because it's usually a first-order language. However, trying to
 squeeze that into GHC rules is hopeless. Having some way of compiling
 code at run-time would solve that. Examples:
 ** Conal Elliott's image description language Pan
 ** Henning Thielemann's synthesizer-llvm

I've been thinking about this, and I suspect that meta-programming in
Haskell may not be that far off.  Suppose you have a Meta monad

data Meta a = Meta { runMeta :: a}

with the magical property that the compiler will optimize/recompile
expressions of type `Meta a` when they are run via `runMeta`.  That
would provide usable metaprogramming, and I think it would have all
the desired type properties etc.

Of course no compiler currently has that facility, but we could use a
different monad, perhaps something like this:

data ThMeta a = ThMeta { runThMeta :: Language.Haskell.TH.ExpQ }

now we just need to get the compiler to run an arbitrary TH splice and
check that the types match after `runThMeta` is called.  I think this
is already possible via the GHC api.  It would have the undesirable
property that some expressions could be ill-typed, and this wouldn't
be known until run-time, but it's a start.

That's about as far as I got before I discovered a much more
worked-out version on Oleg's site (with Chung-chieh Shan and Yukiyoshi
Kameyama).  Of course they've tackled a lot of the awkward typing
issues that my simple construct rudely pushes onto the user.

I'm probably showing my naivety here, and I haven't fully digested
their papers yet, but I wouldn't be surprised to see applications
using Haskell metaprogramming within a relatively short time.

John L.

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


Re: [Haskell-cafe] Module name space question

2011-12-12 Thread John Lato
 From: Christoph Breitkopf chbreitk...@googlemail.com

 Hi,

 I recently asked about what interfaces to implement for a new data type.
 Following the rule that the last 10% of work take the second 90% of time,
 some other questions have come up.

 If anyone wants to look at the code in question:
 http://www.chr-breitkopf.de/comp/IntervalMap

 Some time ago, I was looking for a data structure to search in sets of
 possibly
 overlapping intervals, and found only Data.SegmentTree, which did not fit
 my needs
 (nice term for I did not understand the type signatures).

I can't answer any of your specific questions, although I've published
a related structure in the splaytree package
(http://hackage.haskell.org/package/splaytree).  The interface is
minimal, although it suits my needs and I'd be happy to extend it if
someone else found it worthwhile.

The difference between my data structure (which I've called a
RangeSet) and a standard IntervalSet is that overlapping ranges are
combined, and if part of a range is deleted, the affected range is
modified and possibly split e.g.

 let set1 = singleton $ range 0 5
  set2 = insert (range 2 5) set1

after this, set2 has one node representing the range 0-7.

Staying on topic, my package puts everything under
`Data.SplayTree.xxx`, which is different from the fingertree package
organization.  AFAICT the selection of one convention over the other
is fairly arbitrary, although more packages seem to use the one
second-level hierarchy structure (e.g. bytestring, text, containers).

John L.

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


Re: [Haskell-cafe] containers-deepseq?

2011-11-29 Thread John Lato
 Message: 22
 Date: Tue, 29 Nov 2011 12:18:41 +0200
 From: Michael Snoyman mich...@snoyman.com
 Subject: Re: [Haskell-cafe] containers-deepseq?

 By the way, this is the part of situation that cabal-src is coming to
 solve, and it *is* solved... except that the result is a lot of
 re-compiling.

How is cabal-src different from cabal-dev?

John

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


Re: [Haskell-cafe] A Mascot

2011-11-23 Thread John Lato
 From: Michael Orlitzky mich...@orlitzky.com

 On 11/22/11 16:52, heathmatlock wrote:
 Wasn't planning on it, but I saw some emails on the topic, so I worked
 on what I presented earlier:

 Anyway, creative design-by-committee is doomed, so my advice is to
 ignore this and all other advice =)

+1

(The knight is my favorite, but Da for Mascot regardless)

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


Re: [Haskell-cafe] German names for kinds and sorts

2011-11-14 Thread John Lato
 From: Jerzy Karczmarczuk jerzy.karczmarc...@unicaen.fr

 So, even more seriously, I propose to use more often Latin and Greek.

Jerzy's arguments make a lot of sense to me, but why not use an
index-based notation?

T0 = Type
T1 = Kind
T2 = Sort
etc.

this seems easier to me than an arbitrary hierarchy, particularly as
you go higher up the structure.

John Lato

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


[Haskell-cafe] what happens to ()'s from Core?

2011-10-05 Thread John Lato
Hello,

I'm working on a small EDSL, and I think I've finally managed to get
GHC to compile it to good core.  Basically, it allows for the creation
of expressions like:

 g = 0.5*x + 0.1*y

which is then compiled to a tuple (related work: CCA, stream fusion)

 exists s. (s, s - Double - (s,Double))

I also have a function 'mapAccumL :: (V.Unbox a, V.Unbox b) = (s - a
- (s,b)) - s - V.Vector a - V.Vector b'.  Basic usage would be
similar to:

 import qualified Data.Vector.Unboxed as V

 main = do
   let (gs, gf) = $(compile [] g)
   ys = mapAccumL gf gs $ V.enumFromTo (1::Double) 5
  print ys

For 'g' as above, I currently get 's :: (((), ()), Double)', which is
expected.  GHC produces the following core for the inner loop, which
looks pretty good to me:

letrec {
  $s$wa_s2OL [Occ=LoopBreaker]
:: ()
   - ()
   - GHC.Prim.Double#
   - GHC.Prim.Int#
   - GHC.Prim.State# (Control.Monad.Primitive.R:PrimStateST s_a1Y9)
   - (# GHC.Prim.State# s_a1Y9, () #)
  [LclId, Arity=5, Str=DmdType L]
  $s$wa_s2OL =
\ _
  _
  (sc2_s2Oq :: GHC.Prim.Double#)
  (sc3_s2Or :: GHC.Prim.Int#)
  (sc4_s2Os
 :: GHC.Prim.State#
  (Control.Monad.Primitive.R:PrimStateST s_a1Y9)) -
  case GHC.Prim.# sc3_s2Or rb1_a2EV of _ {
GHC.Types.False - (# sc4_s2Os, GHC.Unit.() #);
GHC.Types.True -
  let {
x#_a2aI [Dmd=Just L] :: GHC.Prim.Double#
[LclId, Str=DmdType]
x#_a2aI =
  GHC.Prim.+##
(GHC.Prim.*##
   (GHC.Prim.indexDoubleArray#
  rb2_a2EW (GHC.Prim.+# rb_a2EU sc3_s2Or))
   0.5)
(GHC.Prim.*## sc2_s2Oq 0.1) } in
  $s$wa_s2OL
GHC.Unit.()
GHC.Unit.()
x#_a2aI
(GHC.Prim.+# sc3_s2Or 1)
((GHC.Prim.writeDoubleArray#
@ (Control.Monad.Primitive.PrimState (GHC.ST.ST s_a1Y9))
arr#_a29n
sc3_s2Or
x#_a2aI
(sc4_s2Os
 `cast` (GHC.Prim.State#
   (Sym
(Control.Monad.Primitive.TFCo:R:PrimStateST s_a1Y9))
 :: GHC.Prim.State#
(Control.Monad.Primitive.R:PrimStateST s_a1Y9)
  ~
GHC.Prim.State#
  (Control.Monad.Primitive.PrimState
(GHC.ST.ST s_a1Y9)
 `cast` (GHC.Prim.State#
   (Control.Monad.Primitive.TFCo:R:PrimStateST s_a1Y9)
 :: GHC.Prim.State#
  (Control.Monad.Primitive.PrimState
(GHC.ST.ST s_a1Y9))
  ~
GHC.Prim.State#
(Control.Monad.Primitive.R:PrimStateST s_a1Y9)))
  }; } in

So my question is, what happens to the ()'s after this stage?  Since
they're not used, and also expressed as literals in core (both in the
recursive case and the original call site of $s$wa_s2OL, is the
backend smart enough to get rid of them completely?

Thanks for any advice,
John L.

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


Re: [Haskell-cafe] instance Enum Double considered not entirely great?

2011-09-21 Thread John Lato
 From: Casey McCann c...@uptoisomorphism.net

        CAJ5riwLLu=wAFXm8VPnqRG2Daxxgf=upgxzchydmebgngix...@mail.gmail.com
 Content-Type: text/plain; charset=ISO-8859-1

 On Tue, Sep 20, 2011 at 8:20 PM, Daniel Fischer
 daniel.is.fisc...@googlemail.com wrote:

 However, nowadays I tend to think that making the Eq and Ord instances
 well-behaved (wrt the class contract) and having separate IEEE comparisons
 would overall be preferable.
 There is still the question whether all NaNs should be considered equal or
 not [and where Ord should place NaNs].

 IEEE semantics are incompatible with Ord regardless. The problem can
 be fixed by changing Ord, removing the instance completely, or
 changing the instance to ignore the IEEE spec. I think the latter is
 the least bad option in the big picture.

 I still don't see why it makes sense to add separate IEEE comparisons
 instead of just adding a standard partial order class, though. Surely
 posets are common enough to justify the abstraction, and it surprises
 me that one isn't already included. No doubt there are at least three
 or four different partial ordering classes on Hackage already.

I agree with this already, and will agree more strongly if
ConstraintKinds become widely available.


 Google suggests Exception for NaN from May.

 Ah, yes, wherein someone suggested that comparing to NaN should be a
 runtime error rather than give incorrect results. A strictly more
 correct approach, but not one I find satisfactory...

I would consider this better than the current situation.  At least
your sets wouldn't be silently corrupted.

John L.

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


Re: [Haskell-cafe] mapM is supralinear?

2011-09-21 Thread John Lato
On Wed, Sep 21, 2011 at 1:57 PM, Tim Docker t...@dockerz.net wrote:

 On 09/09/2011, at 8:19 PM, John Lato wrote:

 Agreed.  Whenever I'd like to use mapM (or any other function for
 which a *M_ is available), I've found the following rules helpful:

 1.  If I can guarantee the list is short (~ n=20), go ahead and use mapM
 2.  Otherwise use mapM_, foldM_, or foldM if a real reduction is
 possible (i.e. not foldM snocM []).

 Step 2 sometimes requires changing my design, but it's always been for
 the better.  `mapM_` tends to require more pipeline composition, so
 it's leveraging the language's strengths.

 This thread is really interesting - it relates directly to problems I am
 currently
 having with mapM over large lists (see the thread stack overflow pain).

 Can you explain what you mean by mapM_ tends to require more pipeline
 composition?
 In what way is it leveraging the language strengths?

Hmm, that is suitably cryptic.  One way to think of it is an inversion
of control.  Instead of operating on whole collections of things in a
monad, you specify monadic actions (pipelines) which are applied
sequentially to each input.

Here's a simple example.  Suppose you have a bunch of data serialized
to files, and you want to read each file into a data structure, apply
some process based upon the last file's data, and write out the output
to new files.  One way to do that would look like:

do
dats - mapM readMyData files
let pairs = zip (mempty:dats) dats
zipWithM_ (\(last, this) fname - writeMyData (update last this)
fname) pairs newFiles

However, you could also put everything into a single monadic
operation, like this

do
foldM_ (\last (infile, outfile) - do
this - readMyData infile
writeMyData
(update last this) outfile
return this
   )
   mempty
   (zip files newFiles)

The first interleaves control (mapM, zipWIthM_) with monadic actions
(file IO), whereas the second only has one control function (foldM_)
which completely processes one input.  I say this is more pipeline
composition because you have to create an entire pipeline from input
to output, which is then sequentially fed inputs by the control
function.

I say this leverages Haskell's strengths because it's quite easy to
compose functions and monadic actions in Haskell.  It also tends to be
garbage-collector friendly.  I also find it much easier to reason
about space usage.  You don't need to worry if part of a list is being
retained, because the full list of data doesn't appear anywhere.  If
you need to access prior elements they're specified explicitly so you
know exactly how much data you're holding on to.

My perspective might be warped by my work on iteratees, but I find
this a very natural approach.

John L.

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


Re: [Haskell-cafe] mapM is supralinear?

2011-09-09 Thread John Lato
 From: Daniel Fischer daniel.is.fisc...@googlemail.com

 On Friday 09 September 2011, 00:41:11, Roman Cheplyaka wrote:
 * Ertugrul Soeylemez e...@ertes.de [2011-09-07 16:20:03+0200]

  In general it's a bad idea to use mapM over IO.

 Could you explain why?

 Take it with a grain of salt, there's nothing necessarily wrong with using
 mapM over IO on short lists.

Agreed.  Whenever I'd like to use mapM (or any other function for
which a *M_ is available), I've found the following rules helpful:

1.  If I can guarantee the list is short (~ n=20), go ahead and use mapM
2.  Otherwise use mapM_, foldM_, or foldM if a real reduction is
possible (i.e. not foldM snocM []).

Step 2 sometimes requires changing my design, but it's always been for
the better.  `mapM_` tends to require more pipeline composition, so
it's leveraging the language's strengths.

This has served me well, especially in IO, but in other monads as well.

John L.

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


Re: [Haskell-cafe] a minor bug (memory leak) in ListLike package

2011-08-24 Thread John Lato
Thanks for reporting this.  I understand the problem, however I don't
want to bloat the interface even more with a bunch of strict versions
of functions.  Even so, the current implementation is definitely the
worst possible option as it has the slow performance of building
thunks without the actual benefits of laziness.

`Data.List` currently uses a fully lazy implementation, with RULEs to
specialize to a strict variant for Int and Integer accumulators.  The
same solution should work for ListLike, with the following additions:

1.  `length` be made fully strict in the accumulator
2.  `genericLength'` (strict variant) be exposed via the interface

Currently I know of no way to automatically derive listlike-instances,
however the `listlike-instances` package has instances for a few other
useful types (vectors and Text mainly).  Adding instances is
definitely a pain, so I may well try to create a Derive extension for
the next time I want to do so.

Cheers,
John

On Wed, Aug 24, 2011 at 5:17 AM, bob zhang bobzhang1...@gmail.com wrote:
 于 11-8-23 下午11:37, Ivan Lazar Miljenovic 写道:

 It might not be what_you_  want, but it might be what others want.  If
 you're concerned with efficiency, then wouldn't you use length rather
 than genericLength?

 length is identical to genericLength in ListLike except type signature.
 but still,
 import Data.Number
 import Data.List
 import qualified Data.ListLike as L
 (3 :: Natural)  genericLength [1..] (work)
 (3 :: Natural)  L.genericLength [1..] (non-terminating)

 If you want laziness, L.genericLength should be defined like this
 L.genericLength [] = 0
 L.genericLength (_:l) = 1 + L.genericLength l
 the genericLength used in ListLike package used tail recursion while
 non-strict.
 and also, a strict length is still needed (currently, length is identical to
 genericLength)

 Thank you
 bob


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


Re: [Haskell-cafe] a minor bug (memory leak) in ListLike package

2011-08-24 Thread John Lato
On Wed, Aug 24, 2011 at 7:47 AM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:

 I was just trying to remember some of the tricks Daniel Peebles (aka
 {co}pumpkin) used to do in #haskell with Data.List.genericLength.
 I've never really used ListLike, but was just trying to guess why the
 default implementation was as it is.

Unfortunately I can't answer this either (although I can make a good
guess); it's from John Goerzen's original code.  And really, any
thanks for ListLike should go to him; he did all the work.

John L.

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


Re: [Haskell-cafe] Lifting an enumerator

2011-08-24 Thread John Lato
 Message: 17
 Date: Wed, 24 Aug 2011 17:02:49 +0300
 From: Michael Snoyman mich...@snoyman.com
 Subject: [Haskell-cafe] Lifting an enumerator
 To: Haskell Cafe haskell-cafe@haskell.org
 Cc: John Millikin jmilli...@gmail.com
 Message-ID:
        caka2jgkf0dn4n8ge1_q-zemlzm93bwg_fjmtbazgzrc2gqn...@mail.gmail.com
 Content-Type: text/plain; charset=ISO-8859-1

 Hi all,

 Max asked earlier[1] how to create a new instance of a class in
 Persistent using a monad transformer. Without getting into the
 specific details of persistent, I wanted to pose a question based on a
 much more general question: how can we lift the inner monad of an
 enumerator? We can easily do so for an Iteratee[2], but there is
 nothing to allow it for an Enumerator.

 At first glance, this problem looks very similar to the shortcomings
 of MonadIO when dealing with callbacks. In that case, you cannot use
 liftIO on a function that takes an `IO a` as a parameter. A solution
 to this issue is monad-control[3], which can be used to allow
 exception catching, memory allocation, etc.

 So I'm wondering: can we come up with a similar solution to this issue
 with enumerators? I have a working solution for the specific case of
 the ErrorT monad[4], but it would be great to be able to generalize
 it. Bonus points if we could express this in terms of the typeclasses
 already provided by monad-control.

Based upon a similar problem I worked on in the past, I suspect this
isn't possible in the general case, at least not safely.  That is, any
implementation (presuming it's possible at all) would violate the
resource guarantees enumerators typically provide (an inner MonadCont
is able to do this).

Unfortunately I don't have a proof, so I'm open to counter-examples ;-)

John L.

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


Re: [Haskell-cafe] Problems building lambdabot on osx

2011-08-09 Thread John Lato
 From: Brandon Allbery allber...@gmail.com

 On Mon, Aug 8, 2011 at 21:38, Adam Turoff adam.tur...@gmail.com wrote:

 First, there's the issue with linking against libiconv, which is solved
 this
 way:

        cabal install --extra-lib-dirs=/usr/lib

 That leaves a whole mess of link errors against libHSreadline:


 Yes, because now it's finding the system readline, which isn't actually
 readline (Apple ships a readline which is actually BSD editline, so you
 get missing symbols for things editline doesn't support such as completion).
  I think you'll need to temporarily deactivate MacPorts' iconv instead of
 using --extra-lib-dirs.

 This can't really be fixed by either GHC or MacPorts; there doesn't seem to
 be a good solution as yet, although the MacPorts folks may end up
 implementing a hacky solution because Apple has introduced *another*
 MacPorts-breaking library conflict in Lion (libnotify).

Yep, this is Apple's problem and everyone else just has to put up with it.

If you want to mix macports and a non-macports ghc, I think the best
solution is to self-compile ghc against the macports libiconv.  This
is easy, just configure ghc with

./configure --with-iconv-includes=/opt/local/include
--with-iconv-libraries=/opt/local/lib

I haven't had a problem since I started building ghc this way (10.5 and 10.6).

John L.

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


Re: [Haskell-cafe] [iteratee] empty chunk as special case of input

2011-07-13 Thread John Lato
Hi Sergey,

iteratee (the package) uses a null chunk to signify that no further
stream data is available within the iteratee, that is, at some point
the stream has been entirely consumed.  Therefore, if any of the
composed iteratees haven't run to completion, they need to get more
data from an enumerator.  Thus 'bindIteratee' has the nullC guard in
the definition as an optimization; there's no need to send the null
chunk to bound iteratees because in most cases they won't be able to
do anything with it.

I've recently considered removing this, but at present when I take it
out some unit tests fail and I haven't had time to explore further.
Since this would have other benefits I would like to do so provided it
doesn't strongly impact performance.  Rather than simply removing the
case I could add a null case to the Stream type, but that could cause
some extra work for users.

Also, one rule for writing iteratees is that they shouldn't put
elements into the stream.  Doing so may cause various transformers to
behave incorrectly.  If you want to modify a stream rather than simply
consuming elements, the correct approach is to create an enumeratee
(stream transformer).

John L.

On Wed, Jul 13, 2011 at 11:00 PM, Sergey Mironov ier...@gmail.com wrote:
 Hi community, hi John. I find myself reading bindIteratee[1] function
 for a several days.. there is something that keeps me away from
 completely understanding of the concept. The most noticeble thing is
 \nullC\ guard in the definition. To demonstate the consequences of
 this solution, let me define an iterator like

 myI = Iteratee $ \onDone _ - onDone 'a' (Chunk xyz)

 It is a bit unusial, since myI substitutes real stream with a fake one
 (xyz). Now lets define two actions producing different results in
 unusual manner:

 printI i = enumPure1Chunk ['a'..'g'] i = run = print

 i1 = (return 'b'  myI  I.head)  -- myI substitutes the stream,
 last /I.head/ produces 'x', OK
 i2 = (I.head  myI  I.head) -- produces 'b'!  I expected another
 'x' here but myI's stream was ignored by =

 Well, I understand that this is probably an expected behaviour, but
 what is it for? Why we can't handle null input like non-null? Iterator
 may just stay in it's current state in that case.

 Thanks in advance
 Sergey

 --
 [1] - bindIteratee (basically, =) code from Data.Iteratee.Base.hs

 bindIteratee :: (Monad m, Nullable s)
    = Iteratee s m a
    - (a - Iteratee s m b)
    - Iteratee s m b
 bindIteratee = self
    where
        self m f = Iteratee $ \onDone onCont -
             let m_done a (Chunk s)
                   | nullC s      = runIter (f a) onDone onCont
                 m_done a stream = runIter (f a) (const . flip onDone
 stream) f_cont
                   where f_cont k Nothing = runIter (k stream) onDone onCont
                         f_cont k e       = onCont k e
             in runIter m m_done (onCont . (flip self f .))


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


Re: [Haskell-cafe] [iteratee] empty chunk as special case of input

2011-07-13 Thread John Lato
Sorry for the followup, but I forgot about one other important reason
(probably the real reason) for the nullC case in bindIteratee.  Note
what happens in the regular case: the iteratee is run, and if it's in
a completed state, the result is passed to the bound function (in the
m_done line), which is then also run.  Examine what happens if the
inner iteratee is also complete:

 const . flip onDone stream

which would be more clearly written as

 \b _str - onDone b stream

so in this case the leftover stream result from the first iteratee
(stream) is used as the result of the second iteratee, and the
leftover stream from the second iteratee (_str) is discarded.

This doesn't seem right; what should happen is that the two streams
should be appended somehow.  It works because at this stage an
iteratee won't have been enumerated over (by the current stream at
least), so it can't have any leftover data, just a null chunk.  But
bindIteratee explicitly checks for the null chunk case also so that's
not a problem.  If the iteratee was enumerated over by another stream
and therefore does have leftover data, then since that data isn't part
of the current stream it's rightfully discarded anyway.

This is why your function produced an unexpected result; it's in a
completed state without having been enumerated over, but also has
leftover data, which bindIteratee ignores.

Now that I've thought about it, I'm not convinced this is always
correct; in particular I suspect it for being responsible for a
slightly convoluted implementation of enumFromCallbackCatch.  I'll
have to expend more brain cells on it, I think.

John L.

On Thu, Jul 14, 2011 at 1:15 AM, John Lato jwl...@gmail.com wrote:
 Hi Sergey,

 iteratee (the package) uses a null chunk to signify that no further
 stream data is available within the iteratee, that is, at some point
 the stream has been entirely consumed.  Therefore, if any of the
 composed iteratees haven't run to completion, they need to get more
 data from an enumerator.  Thus 'bindIteratee' has the nullC guard in
 the definition as an optimization; there's no need to send the null
 chunk to bound iteratees because in most cases they won't be able to
 do anything with it.

 I've recently considered removing this, but at present when I take it
 out some unit tests fail and I haven't had time to explore further.
 Since this would have other benefits I would like to do so provided it
 doesn't strongly impact performance.  Rather than simply removing the
 case I could add a null case to the Stream type, but that could cause
 some extra work for users.

 Also, one rule for writing iteratees is that they shouldn't put
 elements into the stream.  Doing so may cause various transformers to
 behave incorrectly.  If you want to modify a stream rather than simply
 consuming elements, the correct approach is to create an enumeratee
 (stream transformer).

 John L.

 On Wed, Jul 13, 2011 at 11:00 PM, Sergey Mironov ier...@gmail.com wrote:
 Hi community, hi John. I find myself reading bindIteratee[1] function
 for a several days.. there is something that keeps me away from
 completely understanding of the concept. The most noticeble thing is
 \nullC\ guard in the definition. To demonstate the consequences of
 this solution, let me define an iterator like

 myI = Iteratee $ \onDone _ - onDone 'a' (Chunk xyz)

 It is a bit unusial, since myI substitutes real stream with a fake one
 (xyz). Now lets define two actions producing different results in
 unusual manner:

 printI i = enumPure1Chunk ['a'..'g'] i = run = print

 i1 = (return 'b'  myI  I.head)  -- myI substitutes the stream,
 last /I.head/ produces 'x', OK
 i2 = (I.head  myI  I.head) -- produces 'b'!  I expected another
 'x' here but myI's stream was ignored by =

 Well, I understand that this is probably an expected behaviour, but
 what is it for? Why we can't handle null input like non-null? Iterator
 may just stay in it's current state in that case.

 Thanks in advance
 Sergey

 --
 [1] - bindIteratee (basically, =) code from Data.Iteratee.Base.hs

 bindIteratee :: (Monad m, Nullable s)
    = Iteratee s m a
    - (a - Iteratee s m b)
    - Iteratee s m b
 bindIteratee = self
    where
        self m f = Iteratee $ \onDone onCont -
             let m_done a (Chunk s)
                   | nullC s      = runIter (f a) onDone onCont
                 m_done a stream = runIter (f a) (const . flip onDone
 stream) f_cont
                   where f_cont k Nothing = runIter (k stream) onDone onCont
                         f_cont k e       = onCont k e
             in runIter m m_done (onCont . (flip self f .))



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


Re: [Haskell-cafe] Call for GUI examples - Functional Reactive Programming

2011-07-09 Thread John Lato
From: Chris Smith cdsm...@gmail.com

 On Fri, 2011-07-08 at 08:08 +0200, Heinrich Apfelmus wrote:
  Do you know any *small GUI programs* that you would *like* to see
  *implemented with Functional Reactive Programming?*

 This isn't really a specific application, but what I'd like to see most
 from FRP is an example of something that involves moving between windows
 and dialog boxes.  All of the GUI-based FRP examples I've seen so far
 involve interactions in a specific GUI layout.  It's unclear to me how
 FRP extends into a situation like:

 - There's a starting window showing several options for what to do
 - When the user chooses an option, that window closes, and a new one
 opens with that activity.
 - In response to some actions, dialog boxes appear with their own
 interactions.

 It's not clear to me if anyone in FRP has an idea of how stuff like this
 fits in.  Is there some FRP trick to handle this declaratively?  Or
 would you just say each move to a new window ends or pauses one network
 of events and behaviors, and starts a new one?

I can show you how I've been handling this with reactive-banana and
gtk2hs.  As a small example, the File-Open command is meant to open
a new project.  The codez:

 maybeEvent0 :: Typeable a = Action - IO (Maybe a) - NetworkDescription 
 (Event a)
 maybeEvent0 act ops = do
(addHandler, runHandlers) - liftIO newAddHandler
liftIO $ on act actionActivated $ ops = maybe (return ()) runHandlers
fromAddHandler addHandler

 -- | Load a saved project file
 openHandler :: ActionGroup - Window - NetworkDescription (Event (String, 
 HTree))
 openHandler actGrp _win = do
   act - liftIO openAction
   liftIO $ actionGroupAddActionWithAccel actGrp act Nothing
   maybeEvent0 act openProjectDialog

 openProjectDialog :: IO (Maybe (String, HTree))
 openProjectDialog = do
   fc - fileChooserDialogNew (Just Select a project file)
Nothing
FileChooserActionOpen
[]
   fileChooserSetSelectMultiple fc False
   dialogAddButton fc stockCancel ResponseCancel
   dialogAddButton fc stockOk ResponseOk
   widgetShowAll fc
   resp - dialogRun fc
   case resp of
 ResponseOk - runMaybeT $ do
   fp - MaybeT $ fileChooserGetFilename fc
   liftIO $ widgetDestroy fc
   (fp, ) $ liftIO (readProject fp)
 _ - widgetDestroy fc  return Nothing


The `openHandler` function connects the Gtk signal to the
reactive-banana framework.  This uses the helper `maybeEvent0`, which
filters an IO action and triggers a reactive-banana Event when that IO
action actually returns a value.

I've been using this pattern for most of my modal dialogs, and I think
it works very well. The one dialog I haven't used it for is the
starting window, which is straight-line imperative code.

I don't yet have any non-modal dialogs or alternate windows, but there
shouldn't be a problem.  There's nothing special about which window a
widget is in; it can be connected to the FRP framework just like a
widget in the main window.

John L.

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


Re: [Haskell-cafe] How to ensure code executes in the context of a specific OS thread?

2011-07-06 Thread John Lato
Message: 23

 Date: Wed, 06 Jul 2011 10:14:56 +0100
 From: Simon Marlow marlo...@gmail.com
 Subject: Re: [Haskell-cafe] How to ensure code executes in the context
of aspecific OS thread?
 To: Jason Dagit dag...@gmail.com, cvs-...@haskell.org,Haskell
 Cafe
haskell-cafe@haskell.org
 Message-ID: 4e142790.8090...@gmail.com
 Content-Type: text/plain; charset=ISO-8859-1; format=flowed

 On 05/07/2011 20:33, Ian Lynagh wrote:
  On Tue, Jul 05, 2011 at 08:11:21PM +0100, Simon Marlow wrote:
 
  In GHCi it's a different matter, because the main thread is running
  GHCi itself, and all the expressions/statements typed at the prompt
  are run in forkIO'd threads (a new one for each statement, in fact).
  If you want a way to run command-line operations in the main thread,
  please submit a feature request.  I'm not sure it can be done, but
  I'll look into it.
 
  We already have a way: -fno-ghci-sandbox

 Aha, I'd forgotten about that!  Thanks Ian.

 Simon


IIRC a lot of people have had trouble running GUI apps from within GHCi on
OS X, whether they're GLUT, Gtk2hs, WxHaskell, or native, and several users
consider this a large obstacle.  I know that I haven't been successful with
gtk2hs.  However, at this suggestion I just tried running a gtk2hs app I'm
developing with the -fno-ghci-sandbox flag, and it worked perfectly.

Thanks very much, Ian.

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


Re: [Haskell-cafe] Diagnose stack space overflow

2011-07-04 Thread John Lato
 From: Logo Logo sarasl...@gmail.com

 Hi,

 For the following error:

 Stack space overflow: current size 8388608 bytes.
 Use `+RTS -Ksize -RTS' to increase it.

 I want to find out the culprit function and rewrite it tail-recursively. Is
 there a way to find out which function is causing this error other
 than reviewing the code manually?


I'd like to point out that a stack-space overflow in Haskell isn't quite the
same thing as in other functional languages.  In particular, it's possible
for tail-recursive functions to overflow the stack because of laziness.

Consider this tail-recursive sum function:

 trSum :: [Int] - Int
 trSum l = go 0 l
  where
   go acc [] = acc
   go acc (x:xs) = go (acc+x) xs

It's tail-recursive.  But if you enter this in ghci and run it, you'll find
that it uses increasing stack space, and will likely cause a stack overflow
for large enough inputs.  The problem is that the accumulator 'acc' isn't
strict and builds up a thunk of the form:

0+n1+n2+...+nn

The solution is to add strictness.  For this example, a '!' on the
accumulator will do.  GHC will sometimes spot cases where extra strictness
is helpful (it'll figure this one out when compiled with -O), but it often
needs help.

I'd recommend Edward Yang's series of blog posts about debugging, space
leaks, and the Haskell heap.  One useful article is
http://blog.ezyang.com/2011/05/anatomy-of-a-thunk-leak/ , but you may want
to start at the beginning of the heap series.

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


Re: [Haskell-cafe] Patterns for processing large but finite streams

2011-07-01 Thread John Lato

 From: Eugene Kirpichov ekirpic...@gmail.com
 Subject: [Haskell-cafe] Patterns for processing large but finite
streams
 To: Haskell Cafe haskell-cafe@haskell.org
 Message-ID: banlktikdsvq2wv4wjr+qmuvksoav0kt...@mail.gmail.com
 Content-Type: text/plain; charset=ISO-8859-1

 Hi,

 I'm rewriting timeplot to avoid holding the whole input in memory, and
 naturally a problem arises:

 How to represent large but finite streams and functions that process
 them, returning other streams or some kinds of aggregate values?

 Examples:
 * Adjacent differences of a stream of numbers
 * Given a stream of numbers with times, split it into buckets by time
 of given width and produce a stream of (bucket, 50%,75% and 90%
 quantiles in this bucket)
 * Sum a stream of numbers

 Is this, perhaps, what comonads are for? Or iteratees?


This is exactly what iteratees are for.  Specifically, enumeratees are
stream transformers, iteratees are stream consumers, and enumerators are
stream producers.  Consider adjacent differences:

Given the stream [a, b, c, d, e ], you want to produce [b-a, c-b, d-c,
e-d, ...]

This is a stream transformer, so you need an enumeratee.  Using iteratee,
there are at least two obvious ways to produce it:

1)  High-level, but probably not as good performance. Use
Data.Iteratee.ListLike.roll

 import Data.Iteratee as I
 import Control.Applicative

 diff [x,y] = y-x
 diff [x]= 0
 diffs = convStream (map diff $ roll 2 1)


2) somewhat explicit, probably better performance

 import qualified Data.ListLike as LL
 e' iter = do
   h - I.head
   unfoldConvStream f h iter
 where
  f lastEl = do
c - getChunk
if LL.null c
  then return (lastEl, LL.empty)
  else do
let h = LL.head c
 t = LL.tail c
return (LL.last c, LL.cons (h-lastEl) (LL.zipWith (-) t (LL.init
c)))

either of these can be run by using an enumerator:

*Main enumPure1Chunk [1..10] (joinI $ e stream2list) = run
[1,1,1,1,1,1,1,1,1,0]
*Main let e'2 = e' :: Enumeratee [Int] [Int] IO a
*Main enumPure1Chunk [1..10] (joinI $ e'2 stream2list) = run
[1,1,1,1,1,1,1,1,1]

I should optimize 'roll', it wouldn't be hard.

Summing is easy; iteratee has Data.Iteratee.ListLike.sum built-in, but you
could also use a fold.

enumPure1Chunk is only useful for small amounts of data, but iteratee
packages provide enumerators over files, handles, etc., as well as
mechanisms by which you can create your own enumerators.

The e' enumeratee is really just a model; I'd probably write one specific to
whichever type of stream I wanted to work with.  This one assumes a cheap
'cons', for example.

For producing a stream of buckets, if the times are ordered it would be
simple to do with Data.Iteratee.ListLike.breakE.  If the times aren't
ordered, I would probably use 'group' instead to collect a set number of
samples.

In my view, the biggest difference between iteratee and enumerator is the
stream abstraction.  Iteratee provides

 I.Iteratee s m a

where 's' is the stream type, e.g. [Int], String, ByteString, Vector Word8,
etc.  Although the library only processes a chunk at a time (where a chunk
is a subsection of the stream), the type is that of the whole stream.

Enumerator instead provides

 E.Iteratee s m a

here, 's' is the type of the chunk.  Enumerator treats the stream as having
type [s].

The implementations are different too, but ideally that would be hidden from
most users.  Although the iteratee implementation allows you to use = and
$, whereas enumerator sometimes requires you to use == and $$.

I think IterIO mostly follows the same type as Enumerator, although the
implementation is again quite different.

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


Re: [Haskell-cafe] Patterns for processing large but finite streams

2011-07-01 Thread John Lato
After the list discussion, I'm surprised nobody mentioned Max Rabkin/Conal
Elliott's blog posts on folds and zips.

http://squing.blogspot.com/2008/11/beautiful-folding.html
http://conal.net/blog/posts/enhancing-a-zip/

They develop a formalism for zipping functions on lists.

Iteratee's `zip` set of functions are somewhat similar, but not quite the
same.  Specifically they still require multiple traversals of the data, but
only over a bounded portion of it, so they're much more efficient.  Of
course you could combine the above patterns with iteratees by creating
functions as above, then just running them with a 'fold'.

John L.



 From: Eugene Kirpichov ekirpic...@gmail.com

 Thanks but I'm afraid that's still not quite what I'm looking for;
 guess I'll have to define my desire by my implementation - so once
 it's ready I'll show the result to cafe :)

 2011/7/1 Alexey Khudyakov alexey.sklad...@gmail.com:
  On Fri, Jul 1, 2011 at 12:54 PM, Eugene Kirpichov ekirpic...@gmail.com
 wrote:
  Alexey, your definition of mean does not look like liftS2 (/) sum
  length - you have to manually fuse these computations.
 
  Well it was fused for numerical stability
 
  I'm asking for a formalism that does this fusion automatically (and
  guaranteedly).
 
  Joining accumulators is quite straightforward. So is joining of initial
  state. Just creating a
  joinAcc :: (acc1 - x - acc1) - (acc2 - x - acc2) - (acc1,acc2) -
 x - (acc1,acc2)
  joinAcc f1 f2 (s1,s2) x = (f1 s1 x, f2 s2 x)
 
  Still you have to handle them separately.
  sum' = foldl (+) 0
  len ?= foldl (\n _ - n+1) 0
  sumLen = foldl (joinAcc (+) (\n _ - n+1)) (0,0)
 
  There is more regular approach but it only works with statistics.
  (function which do not depend on order of elements in the sample)
  For every statistics monoid for its evaluation could be constructed.
  For example sum:
  newtype Sum a = Sum a
  instance Num a = Monoid (Sum a) where
  ? mempty = Sum 0
  ? mappend (Sum a) (Sum b) = Sum (a+b)
 
  Composition of these monoids becomes trivial. Just use
 
 
  I pursued this approach in monoid-statistics[1] package.
  It's reasonably well documented
 
  ?[1] http://hackage.haskell.org/package/monoid-statistics
 


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


Re: [Haskell-cafe] Data.Enumerator.List.concatMap is to Data.Iteratee.?

2011-06-27 Thread John Lato

 From: David Place d...@vidplace.com

 Hi:

 I've been studying iteratee IO.  Is there a function in the iteratee
 package  that is analogous to Data.Enumerator.List.concatMap?


Iteratee's 'Data.Iteratee.Iteratee.convStream', or the more general
'Data.Iteratee.Iteratee.unfoldConvStream', would be the rough equivalents.
 The difference is that DEL.concatMap operates on each chunk, whereas
DII.convStream operates on the stream.  This makes it possible to specify
operations which work on multiple chunks.

If you want a function more like DEL.concatMap, it would be

 concatMap f = convStream (fmap f getChunk)

Note that stream type 's' in enumerator should generally be translated to
'[s]' in iteratee.

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


Re: [Haskell-cafe] Iteratee IO examples

2011-06-25 Thread John Lato
From: Eric Rasmussen ericrasmus...@gmail.com


 Hi,

 Examples are very helpful to me too -- thank you for sharing. I'm
 especially
 curious to see if there are any examples that allow you to use or convert
 non-iteratee-based functions. I have only just begun reading about
 iteratees
 and might be missing the point, but it seems like many of the examples so
 far rely on explicit recursion or special functions from one of the
 iteratee
 modules.


You might be interested in the attoparsec-enumerator and attoparsec-iteratee
packages, which adapt attoparsec parsers to work with iteratees.  They're
small, self-contained, and quite readable.  Since attoparsec works with
partial parses, it's a natural fit for iteratees.

Honestly I'm quite dis-satisfied with the current state of code which
depends on iteratee/enumerator.  It's nearly all written in a very low-level
style, i.e. directly writing 'liftI step', or 'case x of Yield - ...'.
This is exactly what I would hope users could avoid, by using the functions
in e.g. Data.Iteratee.ListLike.

I've recently added more functions to iteratee which greatly reduce the need
for this type of code.  I don't know about enumerator, but I expect it isn't
rich enough since most user code I've seen is pretty low-level.

For some other iteratee examples, you can 'darcs get
http://www.tiresiaspress.us/haskell/sndfile-enumerators/' and look at the
examples directory (or browse online, of course).



 Is there a way to take a simple function (example below) and use an
 enumerator to feed it a ByteString from a file, or do you have to write
 functions explicitly to work with a given iteratee implementation?

import qualified Data.ByteString.Char8 as B
sortLines = B.unlines . sort . B.lines


For this case, there's no point to using iteratees at all.  Just read the
file in directly to a strict bytestring.  Since you're sorting, you'll need
to see all the lines before results can be returned.  If the file is too big
to fit into memory, you'd need a more sophisticated algorithm for which you
could use iteratees.

In the general case, you need to write for a given iteratee implementation,
but in many specific cases it's not necessary.  If you want to transform
each line of a file, for instance (with iteratee):

import Data.ByteString.Char8 as B
import Data.Iteratee as I
import Data.Iteratee.Char
import System.IO
import Control.Monad.IO.Class

transform :: (ByteString - ByteString) - FilePath - Iteratee [ByteString]
IO ()
transform tFunc oFile = do
  h - liftIO $ openFile oFile WriteMode
  joinI $ rigidMapStream tFunc $ I.mapM_ (B.hPutStrLn h)
  liftIO $ hClose h

rewriteFile :: (ByteString - ByteString) - FilePath - FilePath - IO ()
rewriteFile tFunc iFile oFile = fileDriver (joinI $ enumLinesBS (transform
tFunc oFile)) iFile

An unfolding version would be possible too, which would take a parameter

tFunc :: (s - ByteString - (s, ByteString))

Maybe I'll add these as utilities in the next version of iteratee.

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


Re: [Haskell-cafe] Iteratee IO examples

2011-06-25 Thread John Lato
On Sat, Jun 25, 2011 at 10:18 PM, wren ng thornton w...@freegeek.orgwrote:

 On 6/25/11 6:51 AM, John Lato wrote:
  Honestly I'm quite dis-satisfied with the current state of code which
  depends on iteratee/enumerator.  It's nearly all written in a very
 low-level
  style, i.e. directly writing 'liftI step', or 'case x of Yield -  ...'.
  This is exactly what I would hope users could avoid, by using the
 functions
  in e.g. Data.Iteratee.ListLike.
 
  I've recently added more functions to iteratee which greatly reduce the
 need
  for this type of code.  I don't know about enumerator, but I expect it
 isn't
  rich enough since most user code I've seen is pretty low-level.

 I have a rather large suite of list-like functions for the old version of
 iteratee (used by a project I've been working on for a while). Once I get
 the time to convert the project to the newer iteratee, I'll send a patch
 with any you're still missing.


I'd greatly appreciate it.  Even if they're for the old version; doing the
conversion is fairly mechanical.


 (Though, admittedly, I'm not terribly keen on ListLike. The classes still
 seem too monolithic and ad-hoc. Though I'm not sure there's a way around
 that without something closer to ML's functor modules.)


Refactoring ListLike has been a long-standing objective of mine, but I
haven't put much time into it because it would cause breaking changes which
I didn't think anyone else would appreciate.  No way to tell except to just
release it I guess.

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


Re: [Haskell-cafe] Maybe use advice

2011-06-07 Thread John Lato
Is it necessary (helpful) to use 'rewrite'?  Nearly every time I've tried
it, in the end 'transform' has been a better choice.  Then you wouldn't need
the 'Just's at all, and it should work fine.

John


 From: Lyndon Maydwell maydw...@gmail.com

 (missed including cafe)

 f :: [Modification] - Maybe [Modification]
 and
 f _ = Just $ f ...
 are incompatible

 I managed to get the behaviour I'm after with the use of Either, but
 this really is messy:


 -- Sets of changes
 o (Modifier (Changes [])  i) = Just $ i
 o (Modifier (Changes [c]) i) = Just $ Modifier c i
 o (Modifier (Changes l)   i) = g (f (Left l))
  where
g (Right l) = Just $ Modifier (Changes l) i
g (Left  l) = Nothing

f (Left  (Scale x y : Scale x' y' : l)) =
f $ Right $ Scale (x*x') (y*y') : h (f $ Left l)
f (Left  (Translate x y : Translate x' y' : l)) =
f $ Right $ Translate (x+x') (y+y') : h (f $ Left l)
f (Left  (Rotatex   : Rotatex': l)) =
f $ Right $ Rotate(x+x'): h (f $ Left l)
f x = x

h (Left  l) = l
h (Right l) = l


 On Tue, Jun 7, 2011 at 3:11 AM, Maciej Marcin Piechotka
 uzytkown...@gmail.com wrote:
  On Mon, 2011-06-06 at 23:38 +0800, Lyndon Maydwell wrote:
  I'm writing an optimisation routine using Uniplate. Unfortunately, a
  sub-function I'm writing is getting caught in an infinite loop because
  it doesn't return Nothing when there are no optimisations left.
 
  I'd like a way to move the last Just into f, but this makes recursion
  very messy. I was wondering if there was a nice way to use something
  like the Monad or Applicative instance to help here.
 
  -- Sets of changes
  o (Modifier (Changes []) ?i) = Just $ i
  o (Modifier (Changes [c]) i) = Just $ Modifier c i
  o (Modifier (Changes l) ? i) = Just $ Modifier (Changes (f l)) i
  ? where
  ? ? f (Scale ? ? x y : Scale ? ? x' y' : l) = f $ Scale ? ? (x*x')
 (y*y') : f l
  ? ? f (Translate x y : Translate x' y' : l) = f $ Translate (x+x')
 (y+y') : f l
  ? ? f (Rotate ? ?x ? : Rotate ? ?x' ? ?: l) = f $ Rotate ? ?(x+x') ? ? ?
 ?: f l
  ? ? f l = l
 
 
  Any ideas?
 
  Something like:
 
  ...
  f (Rotate ? ?x ? : Rotate ? ?x' ? ?: l)
  ? ?= Just $ f (Rotate (x+x') : fromMaybe l (f l))
  f l = Nothing -- As far as I understend
 
  Regards
 
  ___

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


Re: [Haskell-cafe] Maybe use advice

2011-06-07 Thread John Lato
If I'm interpreting your code properly, it's not currently catching that
case anyway.

The problem is that you've got two sets of modifiers that both should be
optimized, explicit Modifier constructors in the Image, and a list contained
in Changes.  Since 'Changes' is just a list of Modifiers, and not an Image,
neither rewrite nor transform will descend on it.  You get around this by
explicitly calling rewrite on the modifiers in 'deBlank', but then the rules
from 'optimize' aren't applied.  You can't really use the biplate functions
either because they only match on a single element at a time.  What you
really want to do is be able to express each rule exactly once, which isn't
possible in the current form of your code.

One solution is to move a lot of the reductions of the form 'Modifier x'
from 'optimize' into 'deBlank'.  Then you would have something like this:

 deBlank :: [Modifier] - [Modifier]
 deBlank = db

 db (Scale 1 1 : l)   = db l
 db (Rotate x : Rotate x' : l) = db (Rotate (x+x') : l)
 db (Scale  x y : Scale x' y' : l) = db (Scale (x*x') (y*y') : l)
 db (Translate x y : Translate x' y' : l) = db (Translate (x+x') (y+y') :
l)
 db xs = xs

I actually don't think uniplate gets you anything in this particular
function.

Now deBlank will produce a list of modifiers which is as reduced as possible
(at least by the rules you've provided), and you can use it within a
two-pass optimize:

 optimize = transform o2 . transform o

 o (Modifier _ Blank) = Blank
 o (Modifier (Scale 0 _) _i) = Blank
 -- similar cases omitted

 o (Modifier m2 (Modifier m1 i)) = Modifier (m1 `mappend` m2) i
 o i@(Modifier (Changes _c) _i) = i
 o (Modifier m i) = Modifier (Changes [m]) i
 o i = i

 o2 (Modifier (Changes c) i) = case deBlank c of
  [] - i
  [x] - Modifier x i
  xs - Modifier (Changes c) i
 o2 i = i

Transformations like Scale 0 _ have remained in the Image traversal,
however all other modifications are combined into a single Changes list,
which is then reduced by deBlank in the second pass.  Note that in the first
pass, even single modifications are encapsulated in a Changes; this makes
the logic of the second pass much simpler because then all the reductions of
multiple modifiers are located in the 'deBlank' function instead of split
between there and 'o'.

This presumes there's an appropriate Monoid instance for Modifiers, but if
it doesn't exist it can be written easily enough.

On second thought, I think it would be good to break it up even more, and
keep the reductions of the form

 o (Modifier _ Blank) = Blank
 o (Modifier (Scale 0 _) _i) = Blank

as a third pass, because it's possible some of them could get lost in this
form.  Then  the first pass would just combine terms, the second would apply
'deBlank' and reduce, then the third would be as above.

There are two alternatives which may be simpler:

1)  Expand Changes c into explicit modifications and do all your
reductions on the resulting Image.

2)   Implement a general matrix transform for Diagrams and rewrite
everything in terms of that.  This would be useful for shear transforms
anyway, which I believe are currently inexpressible in Diagrams.

John Lato

On Tue, Jun 7, 2011 at 10:12 AM, Lyndon Maydwell maydw...@gmail.com wrote:

 The fixpoint nature of rewrite catches some cases that transform might
 not if I'm interpreting it correctly.

 (Changes [Translate 1 1, Scale 1 1, Translate 1 1]) could be rewritten
 as (Translate 2 2), but I'm not sure that it could be translated as
 such if it matches against (Changes [Translate _ _, Translate _ _])
 first.

 I have the code on github at

https://github.com/sordina/Diagrams-AST/blob/master/src/Graphics/Rendering/Diagrams/AST/Optimize.hs
 if you're interested.

 At the moment I'm not worrying about speed as I really just wrote this
 optimisation function as a demo of why an AST interface to Diagrams
 might be useful.

 On Tue, Jun 7, 2011 at 5:06 PM, John Lato jwl...@gmail.com wrote:
  Is it necessary (helpful) to use 'rewrite'?  Nearly every time I've
tried
  it, in the end 'transform' has been a better choice.  Then you wouldn't
need
  the 'Just's at all, and it should work fine.
  John
 
 
  From: Lyndon Maydwell maydw...@gmail.com
 
  (missed including cafe)
 
  f :: [Modification] - Maybe [Modification]
  and
  f _ = Just $ f ...
  are incompatible
 
  I managed to get the behaviour I'm after with the use of Either, but
  this really is messy:
 
 
  -- Sets of changes
  o (Modifier (Changes [])  i) = Just $ i
  o (Modifier (Changes [c]) i) = Just $ Modifier c i
  o (Modifier (Changes l)   i) = g (f (Left l))
   where
 g (Right l) = Just $ Modifier (Changes l) i
 g (Left  l) = Nothing
 
 f (Left  (Scale x y : Scale x' y' : l)) =
 f $ Right $ Scale (x*x') (y*y') : h (f $ Left l)
 f (Left  (Translate x y : Translate x' y' : l)) =
 f $ Right $ Translate (x+x') (y+y') : h (f $ Left l)
 f (Left  (Rotatex   : Rotatex': l

Re: [Haskell-cafe] [iteratee] how to do nothing .. properly

2011-06-05 Thread John Lato
Yes, this is expected.  'throwErr' is only meant to be used when the error
should be non-recoverable, and the stream would often be invalid then, so
throwErr doesn't take any steps to preserve it.  You could retain the rest
of the stream with getChunk and use throwRecoverableErr though.

Wrapping an iteratee with ErrorT is fine, and I use this approach often.  I
typically would use an explicit Either rather than ErrorT, but the two
approaches are exactly the same.

Note that wrapping the other way, Iteratee s (ErrorT e m), can sometimes
cause problems, and is best avoided unless you really know what you're
doing.  This may change in a future release.

John

On Thu, Jun 2, 2011 at 4:27 PM, Sergey Mironov ier...@gmail.com wrote:

 I am glad to help! Looks like upgrading to 0.8.5.0 also fixes initial
 problem that involved me into testing!

 I'll take the opportunity and ask another thing about iteratee: Is it
 expected behavior that throwErr consumes all data in current chunk? I
 wish it to stop in place and let after-checkErr code to continue the
 parsing. Well, I already found solution (or workaround?) - I wrap
 Iteratee with ErrorT monad and use ErrorT's raiseError instead of
 throwErr. Is it correct?

 Here is example code

 instance Exception Int

 iter4 = do
I.dropWhile (/= 3)
h-I.head
throwErr $ toException $ (-4::Int)  -- doesn't meter what exactly to
 throw
return h

 -- catch the error with checkErr
 iter5 = do
(_,b)-countBytes $ I.checkErr $ iter4
s - I.stream2list
return (b,s)

 print5 = enumPure1Chunk [1..10] (iter5) = run = print


 Thanks a lot!
 Sergey

 2011/6/2 John Lato jwl...@gmail.com:
  Hi Sergey,
 
  I've got an explanation; quite surprisingly it's a bug in enumPure1Chunk.
  Even though it is an odd case, I'm surprised that it hasn't come up
 before
  now since enumPure1Chunk appears frequently.
 
  I've just uploaded 0.8.5.0 which has the fix.  There's now an additional
  Monoid constraint on enumPure1Chunk, unfortunately.
 
  Thanks very much for reporting this.
 
  John L
 
  On Thu, Jun 2, 2011 at 10:02 AM, Sergey Mironov ier...@gmail.com
 wrote:
 
  Ok. I've checked iteratee-0.8.3.0 and 0.8.4.0. Results are same.
 
  Sergey
 
  2011/6/2 John Lato jwl...@gmail.com:
   Hi Sergey,
   I can't explain this; maybe it's a bug in enumWith?  I'll look into
 it.
   Thanks,
   John
  
  
   Message: 20
  
   Date: Thu, 2 Jun 2011 02:46:32 +0400
   From: Sergey Mironov ier...@gmail.com
   Subject: [Haskell-cafe] [iteratee] how to do nothing .. properly
   To: haskell-cafe@haskell.org
   Message-ID: BANLkTimMFRWgH9Nopt-eua+L7jQcGq+u=g...@mail.gmail.com
   Content-Type: text/plain; charset=ISO-8859-1
  
   Hi. Would anybody explain a situation with iter6 and iter7 below?
   Strange thing - first one consumes no intput, while second consumes
 it
   all, while all the difference is peek  which should do no processing
   (just copy next item in stream and return to user).
   What I am trying to do - is to write an iteratee consuing no input,
   but returning a constant I give to it. I thought (return a) should do
   it, but it seems I was wrong as return actually consumes all unparsed
   stream. iter6 experience tells me that (peekreturn a) is what I
   need, but it's completely confusing and not what I expected.
  
   Thanks,
   Sergey
  
import Data.Iteratee as I
import Data.Iteratee.IO
import Control.Monad
import Control.Exception
import Data.ByteString
import Data.Char
import Data.String
  
-- countBytes :: (..., Num b) = Iteratee s m a - Iteratee s m (a,
 b)
countBytes i = enumWith i I.length
  
iter6 = do
   h - countBytes $ (peek  return 0)
   s - I.stream2list
   return (h,s)
  
iter7 = do
   h - countBytes $ (return 0)
   s - I.stream2list
   return (h,s)
  
print6 = enumPure1Chunk [1..10] (iter6) = run = print
print7 = enumPure1Chunk [1..10] (iter7) = run = print
  
  
   Here is example ghci session
  
   *Main print6
   ((0,0),[1,2,3,4,5,6,7,8,9,10])
   -- read 0 items, returns 0
   *Main print7
   ((0,10),[])
   -- read 10 items (???) returns 0
   *Main
  
  
  
   --
  
   ___
   Haskell-Cafe mailing list
   Haskell-Cafe@haskell.org
   http://www.haskell.org/mailman/listinfo/haskell-cafe
  
  
   End of Haskell-Cafe Digest, Vol 94, Issue 3
   ***
  
  
 
 

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


Re: [Haskell-cafe] [iteratee] how to do nothing .. properly

2011-06-02 Thread John Lato
Hi Sergey,

I can't explain this; maybe it's a bug in enumWith?  I'll look into it.

Thanks,
John


 Message: 20

Date: Thu, 2 Jun 2011 02:46:32 +0400
 From: Sergey Mironov ier...@gmail.com
 Subject: [Haskell-cafe] [iteratee] how to do nothing .. properly
 To: haskell-cafe@haskell.org
 Message-ID: BANLkTimMFRWgH9Nopt-eua+L7jQcGq+u=g...@mail.gmail.com
 Content-Type: text/plain; charset=ISO-8859-1

 Hi. Would anybody explain a situation with iter6 and iter7 below?
 Strange thing - first one consumes no intput, while second consumes it
 all, while all the difference is peek  which should do no processing
 (just copy next item in stream and return to user).
 What I am trying to do - is to write an iteratee consuing no input,
 but returning a constant I give to it. I thought (return a) should do
 it, but it seems I was wrong as return actually consumes all unparsed
 stream. iter6 experience tells me that (peekreturn a) is what I
 need, but it's completely confusing and not what I expected.

 Thanks,
 Sergey

  import Data.Iteratee as I
  import Data.Iteratee.IO
  import Control.Monad
  import Control.Exception
  import Data.ByteString
  import Data.Char
  import Data.String

  -- countBytes :: (..., Num b) = Iteratee s m a - Iteratee s m (a, b)
  countBytes i = enumWith i I.length

  iter6 = do
 h - countBytes $ (peek  return 0)
 s - I.stream2list
 return (h,s)

  iter7 = do
 h - countBytes $ (return 0)
 s - I.stream2list
 return (h,s)

  print6 = enumPure1Chunk [1..10] (iter6) = run = print
  print7 = enumPure1Chunk [1..10] (iter7) = run = print


 Here is example ghci session

 *Main print6
 ((0,0),[1,2,3,4,5,6,7,8,9,10])
 -- read 0 items, returns 0
 *Main print7
 ((0,10),[])
 -- read 10 items (???) returns 0
 *Main



 --

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


 End of Haskell-Cafe Digest, Vol 94, Issue 3
 ***

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


Re: [Haskell-cafe] [iteratee] how to do nothing .. properly

2011-06-02 Thread John Lato
Hi Sergey,

I've got an explanation; quite surprisingly it's a bug in enumPure1Chunk.
Even though it is an odd case, I'm surprised that it hasn't come up before
now since enumPure1Chunk appears frequently.

I've just uploaded 0.8.5.0 which has the fix.  There's now an additional
Monoid constraint on enumPure1Chunk, unfortunately.

Thanks very much for reporting this.

John L

On Thu, Jun 2, 2011 at 10:02 AM, Sergey Mironov ier...@gmail.com wrote:

 Ok. I've checked iteratee-0.8.3.0 and 0.8.4.0. Results are same.

 Sergey

 2011/6/2 John Lato jwl...@gmail.com:
  Hi Sergey,
  I can't explain this; maybe it's a bug in enumWith?  I'll look into it.
  Thanks,
  John
 
 
  Message: 20
 
  Date: Thu, 2 Jun 2011 02:46:32 +0400
  From: Sergey Mironov ier...@gmail.com
  Subject: [Haskell-cafe] [iteratee] how to do nothing .. properly
  To: haskell-cafe@haskell.org
  Message-ID: BANLkTimMFRWgH9Nopt-eua+L7jQcGq+u=g...@mail.gmail.com
  Content-Type: text/plain; charset=ISO-8859-1
 
  Hi. Would anybody explain a situation with iter6 and iter7 below?
  Strange thing - first one consumes no intput, while second consumes it
  all, while all the difference is peek  which should do no processing
  (just copy next item in stream and return to user).
  What I am trying to do - is to write an iteratee consuing no input,
  but returning a constant I give to it. I thought (return a) should do
  it, but it seems I was wrong as return actually consumes all unparsed
  stream. iter6 experience tells me that (peekreturn a) is what I
  need, but it's completely confusing and not what I expected.
 
  Thanks,
  Sergey
 
   import Data.Iteratee as I
   import Data.Iteratee.IO
   import Control.Monad
   import Control.Exception
   import Data.ByteString
   import Data.Char
   import Data.String
 
   -- countBytes :: (..., Num b) = Iteratee s m a - Iteratee s m (a, b)
   countBytes i = enumWith i I.length
 
   iter6 = do
  h - countBytes $ (peek  return 0)
  s - I.stream2list
  return (h,s)
 
   iter7 = do
  h - countBytes $ (return 0)
  s - I.stream2list
  return (h,s)
 
   print6 = enumPure1Chunk [1..10] (iter6) = run = print
   print7 = enumPure1Chunk [1..10] (iter7) = run = print
 
 
  Here is example ghci session
 
  *Main print6
  ((0,0),[1,2,3,4,5,6,7,8,9,10])
  -- read 0 items, returns 0
  *Main print7
  ((0,10),[])
  -- read 10 items (???) returns 0
  *Main
 
 
 
  --
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
  End of Haskell-Cafe Digest, Vol 94, Issue 3
  ***
 
 

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


Re: [Haskell-cafe] How on Earth Do You Reason about Space?

2011-06-01 Thread John Lato

 From: Brandon Moore brandon_m_mo...@yahoo.com


 I was worried data sharing might mean your keys
 retain entire 64K chunks of the input. However, it
 seems enumLines depends on the StringLike ByteString
 instance, which just converts to and from String.
 That can't be efficient, but I suppose it avoids excessive sharing.


That's true for 'enumLines', however the OP is using 'enumLinesBS', which
operates on bytestrings directly.

Data sharing certainly could be an issue here.  I tried performing
Data.ByteString.copy before inserting the key into the map, but that used
more memory.  I don't have an explanation for this; it's not what I would
expect.

The other parameter which affects sharing is the chunk size.  I got a much
better memory profile when using a chunksize of 1024 instead of  65536.

Oddly enough, when using the large chunksize I saw lower memory usage from
Data.Map, but with the small chunksize Data.HashMap has a significant
advantage.

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


Re: [Haskell-cafe] How on Earth Do You Reason about Space?

2011-06-01 Thread John Lato
On Wed, Jun 1, 2011 at 12:55 AM, Aleksandar Dimitrov 
aleks.dimit...@googlemail.com wrote:

 On Tue, May 31, 2011 at 11:30:06PM +0100, John Lato wrote:

  None of these leak space for me (all compiled with ghc-7.0.3 -O2).
  Performance was pretty comparable for every version, although
 Aleksander's
  original did seem to have a very small edge.

 How big were your input corpora?


Today I was using multiple copies of War  Peace, as Brandon specified.
 Total size is about 90M.



 So it seems that I can't get rid of a factor of around 3x the input file
 size.
 Luckily, the dependency seems to be linear. Here's some profiling:

 ghc: 30478883712 bytes, 57638 GCs, 41925397/143688744 avg/max bytes
 residency (189 samples), 322M in use, 0.00 INIT (0.00 elapsed), 23.73 MUT
 (24.94 elapsed), 26.71 GC (27.10 elapsed) :ghc
 ../src/cafe/tools/iterTable 106M_text.txt +RTS -tstderr  50.44s user 1.50s
 system 99% cpu 52.064 total

 ghc itself reports 38MB avg (can live with that,) and 140MB max (too much.)

 Redirecting the program's output to a file will yield a mere 2.2M for the
 data
 gathered by the above script. Since those 2.2M of data are all I care
 about, why
 do I need so much more RAM to compute them?

 Are my demands unreasonable?


I think the issue is data sharing, as Brandon mentioned.  A bytestring
consists of an offset, length, and a pointer.  You're using a chunk size of
64k, which means the generated bytestrings all have a pointer to that 64k of
data.  Suppose there's one new word in that 64k, and it's near the beginning
of the chunk.  Even though the word may only be a few characters long, it'll
reference the entire chunk and keep it from being GC'd.

There are a few solutions to this.  The first is to make a copy of the
bytestring so only the required data is retained.  In my experiments this
wasn't helpful, but it would depend on your corpus.  The second is to start
with smaller chunks.  Using a chunk size of 1024 worked fairly well for me.
 If your corpus is similar to natural language, I think it'll probably work
better for you as well.

Note that Johan's Ngram code also only keeps the minimum required data,
giving it a good memory profile.   I didn't notice this last night because I
was testing with different data, and unfortunately the peculiar distribution
of that data masked this problem.

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


Re: [Haskell-cafe] How on Earth Do You Reason about Space?

2011-05-31 Thread John Lato
From: Edward Z. Yang ezy...@mit.edu


 Hello Aleksandar,

 It is possible that the iteratees library is space leaking; I recall some
 recent discussion to this effect.  Your example seems simple enough that
 you might recompile with a version of iteratees that has -auto-all enabled.
 Unfortunately, it's not really a safe bet to assume your libraries are
 leak free, and if you've pinpointed it down to a single line, and there
 doesn't seem a way to squash the leak, I'd bet it's the library's fault.

 Edward


I can't reproduce the space leak here.  I tried Aleksander's original code,
my iteratee version, the Ngrams version posted by Johan Tibell, and a lazy
bytestring version.

my iteratee version (only f' has changed from Aleksander's code):

f' :: Monad m = I.Iteratee S.ByteString m Wordcounts
f' = I.joinI $ (enumLinesBS I. I.filter (not . S.null)) $ I.foldl' (\t s
- T.insertWith (+) s 1 t) T.empty

my lazy bytestring version

 import Data.Iteratee.Char
 import Data.List (foldl')import Data.Char (toLower)

 import Data.Ord (comparing)
 import Data.List (sortBy)
 import System.Environment (getArgs)
 import qualified Data.ByteString.Lazy.Char8 as L
 import qualified Data.HashMap.Strict as T

 f'2 = foldl' (\t s - T.insertWith (+) s 1 t) T.empty . filter (not .
L.null) . L.lines

 main2 :: IO ()
 main2 = getArgs = L.readFile .head = print . T.keys . f'2

None of these leak space for me (all compiled with ghc-7.0.3 -O2).
Performance was pretty comparable for every version, although Aleksander's
original did seem to have a very small edge.

As someone already pointed out, keep in mind that this will use a lot of
memory anyway, unless there's a lot of repetition of words.

I'd be happy to help track down a space leak in iteratee, but for now I'm
not seeing one.

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


Re: [Haskell-cafe] Haskell School of Expression (graphics)

2011-05-30 Thread John Lato

 From: michael rice nowg...@yahoo.com


I think this is fixed in the gtk2hs source tree, have you tried building
from the repo?

 cabal install gtk2hs-buildtools
 darcs get --lazy http://code.haskell.org/gtk2hs/
 cd gtk2hs
 chmod +x bootstrap.sh
 ./bootstrap.sh

John Lato


 Is this worth chasing down? I loaded the Haskell Platform, which I assume
 has some graphics capability (Cairo?). Maybe my time would be better spent
 getting familiar with that?

 Michael
 --- On Sun, 5/29/11, Andrew Coppin andrewcop...@btinternet.com wrote:

 From: Andrew Coppin andrewcop...@btinternet.com
 Subject: Re: [Haskell-cafe] Haskell School of Expression (graphics)
 To: haskell-cafe@haskell.org
 Date: Sunday, May 29, 2011, 9:45 AM

 On 28/05/2011 08:06 PM, michael rice wrote:

  /tmp/glib-0.11.22906/glib-0.11.2/Gtk2HsSetup.hs:190:70:
  Couldn't match expected type `[PackageDB]'
  with actual type `PackageDB'
  Expected type: PackageDBStack
  Actual type: PackageDB
  In the sixth argument of `registerPackage', namely `packageDb'
  In the expression:
  registerPackage
  verbosity installedPkgInfo pkg lbi inplace packageDb
  cabal: Error: some packages failed to install:
  cairo-0.11.1 failed during the configure step. The exception was:
  ExitFailure 1

 There's some sort of glitch with Gtk2hs (on which SOE depends) that causes
 it to not build with GHC 7.x (?) unless you hand-edit some of the files (!)

 http://hackage.haskell.org/trac/gtk2hs/ticket/1203
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] uniplate (was: code review?)

2011-05-30 Thread John Lato
Hi Neil, thanks for the response.

On Mon, May 30, 2011 at 8:48 PM, Neil Mitchell ndmitch...@gmail.com wrote:

 Hi John,

   While I'm on the topic, I recently wrote a tool that wanted to
   traverse deep data structures as produced by haskell-src-exts. ?I
   wound up with about 50 lines of case expressions and around the time
   my hands were literally beginning to hurt decided that enough was
   enough and I should try a generic approach. ?I heard uniplate was
   pretty easy to use, and was pretty pleased to turn the entire thing
   into a single line. ?It took me a little longer to figure out I needed
   to use universeBi since all the examples were monotyped, but once I
   did it Just Worked. ?Amazing. ?So thanks again! ?And maybe you could
   mention universeBi in the instant introduction?
 
  Yes, I probably should - I'll try and get to that. Of course, I'd also
  happily accept a patch against
  http://community.haskell.org/~ndm/darcs/uniplate
 
  I use Uniplate inside HLint, and it's invaluable - there are a lot of
  times when List Comp + universeBi really hits the spot.
 
  Does Uniplate include an instance for:
  instance Uniplate a = Biplate [a] a

 No, it only includes:

 instance Biplate [Char] Char where
biplate (x:xs) = plate (:) |* x ||* xs
biplate x = plate x

 I am slightly curious why I didn't include the more general a instead
 of Char version, but perhaps it doesn't quite work - polymorphic
 versions of the Direct instances can have problems if you pick weird
 types. I'll have a think, and if it does always work, I'll include it.

 Note that if you use the Typeable or Data versions this instance is
 automatically available. In practice I almost always end up using the
 Data versions of Uniplate, they require no instance definitions are
 are good to get started with - you can switch to Direct only if you
 need the additional performance.


I started with Data, but writing the Direct instance was so simple that I
didn't see a reason not to do it.  My type doesn't have many constructors
yet though, and several of them aren't recursive, so maybe it was easier
than normal.

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


Re: [Haskell-cafe] Status of Haskell + Mac + GUIs graphics

2011-05-26 Thread John Lato
fltk definitely has some good points, but I've always found it hideously
ugly.  Of course the default gtk on osx is ugly too, but some of the
available themes are nice.

However, getting gtk with OpenGL on osx was fairly easy.  Everything worked
out of the box except gtkglext (Haskell package).  I've submitted some
patches for that which hopefully will be applied to the repo soon.

This is what I used:

git
darcs
ghc-7.0.3 (self-compiled)
cabal-install
macports gtk2 +no_x11 +quartz
macports gtkglext +no_x11 +quartz
gtk2hs from source
gtkglext (Haskell) from source


I use a self-compiled ghc, but this should work with any ghc.  Mixing ghc
and macports can cause problems with libiconv, but the solutions are pretty
well-known.  Since I compile ghc, I configure it to use macports's libiconv
so there aren't any conflicts.


 sudo port install gtkglext +no_x11 +quartz
(wait a while...)
 darcs get --lazy http://code.haskell.org/gtk2hs
 cd gtk
 cabal install gtk2hs-buildtools
 chmod +x bootstrap.sh
 ./bootstrap.sh -fhave-quartz-gtk
(wait a while...)
 cd ..
 darcs get --lazy http://code.haskell.org/gtkglext
 cd gtkglext
 darcs apply gtkglext.dpatch
 cabal install


Until the source tree gets patched, you'll have to manually apply the patch
bundle.

If you want to avoid macports, it should be possible to use gtk-osx and
gtkglext from source instead.  However, I've found gtk-osx to be unstable
and quite difficult to build in the past, so I'd strongly recommend
macports, at least for now.  The source install of gtkglext works just fine
and can be used with macports gtk2 (I tested this).  Since this path already
uses macports there's not much benefit though.

Cheers,
John L

On Wed, May 25, 2011 at 9:07 PM, Evan Laforge qdun...@gmail.com wrote:

 fltk supports OpenGL on windows, X11, and OS X, though I've never used
 it.  The thing it doesn't have is a haskell binding, but as I
 mentioned I just bind whatever I need when I need it and since I don't
 need much it's easy.  Dunno if this applies in your case though.

 Maybe it's my NIH, but I like to start with something too simple and
 add what I need rather than start with something that has more than I
 need and try to get it working.

 On Wed, May 25, 2011 at 11:58 AM, Conal Elliott co...@conal.net wrote:
  Thanks, John. Encouraging bit of news. Please do let us know what you
 learn
  when you try.   - Conal
 
  On Tue, May 24, 2011 at 1:28 AM, John Lato jwl...@gmail.com wrote:
 
  You can use gtkglext to get OpenGL support.  With the official release
 of
  gtkglext-1.2.0 there's a bit of hacking involved (that was probably me
  you're referring to), but it looks like the repo head has native Quartz.
  With any luck, you just need to build gtkglext from the repo, then the
  gtkglext package.
 
  I might have some time to try this later today; I'll report back if I
 get
  results.
 
  John Lato
 
  On Tue, May 24, 2011 at 6:01 AM, Conal Elliott co...@conal.net wrote:
 
  Last I tried, there wasn't native support for OpenGL with gtk, and I
 need
  OpenGL. Then more recently, I heard of some progress in that area, but
  requiring lots of hacking to get it all compiling. Any recent news?  -
 Conal
 
  On Mon, May 23, 2011 at 2:33 AM, John Lato jwl...@gmail.com wrote:
 
  Message: 17
  Date: Fri, 20 May 2011 15:59:51 -0700
  From: Evan Laforge qdun...@gmail.com
  Subject: Re: [Haskell-cafe] Status of Haskell + Mac + GUIs  graphics
  To: Erik Hesselink hessel...@gmail.com
  Cc: haskell-cafe@haskell.org
  Message-ID: BANLkTi=74mm6ortu2e192jtoot9g49f...@mail.gmail.com
  Content-Type: text/plain; charset=ISO-8859-1
 
   Note that it is supposed to be possible to build gtk2hs with
 gtk+osx,
   which will not use X11 but use the native OS X GUI. I've not been
   able
   to get this to work, but it's been a while since I tried. The
 Haskell
   wiki mentions it doesn't support Glade, but does support Cairo. If
   this were to work, gtk2hs would be a serious option as well.
 
  I've tried this 3 or 4 times, and failed every time.  It's crazy
  complicated.
 
  I used to use this combination regularly.  IME the difficulties are
  primarily with getting a working gtk+osx build.  Once that was
 accomplished,
  gtk2hs was a straightforward install, provided you build from the src
 repo
  with the -quartz flag.
  Recently I've switched to using macports gtk2 with the quartz, no-x11
  variant, which also uses native cocoa.  This is much more reliable
 than
  gtk+osx.  I don't know if it supports Glade though.
  My biggest problem with wx is that there's no support for building
  64-bit wx applications on OS X.  If that were fixed I might prefer it.
  John Lato
  ___
  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] uniplate (was: code review?)

2011-05-25 Thread John Lato

 From: Neil Mitchell ndmitch...@gmail.com

  While I'm on the topic, I recently wrote a tool that wanted to
  traverse deep data structures as produced by haskell-src-exts. ?I
  wound up with about 50 lines of case expressions and around the time
  my hands were literally beginning to hurt decided that enough was
  enough and I should try a generic approach. ?I heard uniplate was
  pretty easy to use, and was pretty pleased to turn the entire thing
  into a single line. ?It took me a little longer to figure out I needed
  to use universeBi since all the examples were monotyped, but once I
  did it Just Worked. ?Amazing. ?So thanks again! ?And maybe you could
  mention universeBi in the instant introduction?

 Yes, I probably should - I'll try and get to that. Of course, I'd also
 happily accept a patch against
 http://community.haskell.org/~ndm/darcs/uniplate

 I use Uniplate inside HLint, and it's invaluable - there are a lot of
 times when List Comp + universeBi really hits the spot.


Does Uniplate include an instance for:

 instance Uniplate a = Biplate [a] a
?

Since lists are a common case, I was surprised that this instance wasn't
included.  Is there a reason it shouldn't exist?  I was importing
Data.Generics.Uniplate.Direct FWIW.

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


Re: [Haskell-cafe] Status of Haskell + Mac + GUIs graphics

2011-05-24 Thread John Lato
You can use gtkglext to get OpenGL support.  With the official release of
gtkglext-1.2.0 there's a bit of hacking involved (that was probably me
you're referring to), but it looks like the repo head has native Quartz.
With any luck, you just need to build gtkglext from the repo, then the
gtkglext package.

I might have some time to try this later today; I'll report back if I get
results.

John Lato

On Tue, May 24, 2011 at 6:01 AM, Conal Elliott co...@conal.net wrote:

 Last I tried, there wasn't native support for OpenGL with gtk, and I need
 OpenGL. Then more recently, I heard of some progress in that area, but
 requiring lots of hacking to get it all compiling. Any recent news?  - Conal

 On Mon, May 23, 2011 at 2:33 AM, John Lato jwl...@gmail.com wrote:

 Message: 17
 Date: Fri, 20 May 2011 15:59:51 -0700
 From: Evan Laforge qdun...@gmail.com

 Subject: Re: [Haskell-cafe] Status of Haskell + Mac + GUIs  graphics
 To: Erik Hesselink hessel...@gmail.com
 Cc: haskell-cafe@haskell.org
 Message-ID: BANLkTi=74mm6ortu2e192jtoot9g49f...@mail.gmail.com
 Content-Type: text/plain; charset=ISO-8859-1


  Note that it is supposed to be possible to build gtk2hs with gtk+osx,
  which will not use X11 but use the native OS X GUI. I've not been able
  to get this to work, but it's been a while since I tried. The Haskell
  wiki mentions it doesn't support Glade, but does support Cairo. If
  this were to work, gtk2hs would be a serious option as well.

 I've tried this 3 or 4 times, and failed every time.  It's crazy
 complicated.


 I used to use this combination regularly.  IME the difficulties are
 primarily with getting a working gtk+osx build.  Once that was accomplished,
 gtk2hs was a straightforward install, provided you build from the src repo
 with the -quartz flag.

 Recently I've switched to using macports gtk2 with the quartz, no-x11
 variant, which also uses native cocoa.  This is much more reliable than
 gtk+osx.  I don't know if it supports Glade though.

 My biggest problem with wx is that there's no support for building 64-bit
 wx applications on OS X.  If that were fixed I might prefer it.

 John Lato

 ___
 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] Status of Haskell + Mac + GUIs graphics

2011-05-23 Thread John Lato

 Message: 17
 Date: Fri, 20 May 2011 15:59:51 -0700
 From: Evan Laforge qdun...@gmail.com
 Subject: Re: [Haskell-cafe] Status of Haskell + Mac + GUIs  graphics
 To: Erik Hesselink hessel...@gmail.com
 Cc: haskell-cafe@haskell.org
 Message-ID: BANLkTi=74mm6ortu2e192jtoot9g49f...@mail.gmail.com
 Content-Type: text/plain; charset=ISO-8859-1

  Note that it is supposed to be possible to build gtk2hs with gtk+osx,
  which will not use X11 but use the native OS X GUI. I've not been able
  to get this to work, but it's been a while since I tried. The Haskell
  wiki mentions it doesn't support Glade, but does support Cairo. If
  this were to work, gtk2hs would be a serious option as well.

 I've tried this 3 or 4 times, and failed every time.  It's crazy
 complicated.


I used to use this combination regularly.  IME the difficulties are
primarily with getting a working gtk+osx build.  Once that was accomplished,
gtk2hs was a straightforward install, provided you build from the src repo
with the -quartz flag.

Recently I've switched to using macports gtk2 with the quartz, no-x11
variant, which also uses native cocoa.  This is much more reliable than
gtk+osx.  I don't know if it supports Glade though.

My biggest problem with wx is that there's no support for building 64-bit wx
applications on OS X.  If that were fixed I might prefer it.

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


Re: [Haskell-cafe] ANNOUNCE: iterIO-0.1 - iteratee-based IO with pipe operators

2011-05-09 Thread John Lato

 From: dm-list-haskell-c...@scs.stanford.edu

 At Fri, 6 May 2011 10:10:26 -0300,
 Felipe Almeida Lessa wrote:

  So, in the enumerator vs. iterIO challenge, the only big differences I
 see are:
 
   a) iterIO has a different exception handling mechanism.
   b) iterIO can have pure iteratees that don't touch the monad.
   c) iterIO's iteratees can send control messages to ther enumerators.
   d) iterIO's enumerators are enumeratees, but enumerator's enumerators
  are simpler.
   e) enumerator has fewer dependencies.
   f) enumerator uses conventional nomenclature.
   g) enumerator is Haskell 98, while iterIO needs many extensions (e.g.
  MPTC and functional dependencies).
 
  Anything that I missed?
 
  The bottomline: the biggest advantage I see right now in favor of
  iterIO is c),

 I basically agree with this list, but think you are underestimating
 the value of a.  I would rank a as the most important difference
 between the packages.  (a also is the reason for d.)


'a' is important, but I think a lot of people underestimate the value of
'c', which is why a control system was implemented in 'iteratee'.  I would
argue that iteratee's control system is more powerful than you say.  For
example, the only reason iteratee can't implement tell is because it doesn't
keep track of the position in the stream, it's relatively simple for an
enumerator to return data to an iteratee using an IORef for example.  And
adding support to keep track of the stream position would be a pretty simple
(and possibly desirable) change.  But it's definitely not as sophisticated
as IterIO, and probably won't become so unless I have need of those
features.

I like the MonadTrans implementation a lot.  The vast majority of iteratees
are pure, and GHC typically produces more efficient code for pure functions,
so this is possibly a performance win.  Although it makes something like the
mutable-iter package very difficult to implement...

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


Re: [Haskell-cafe] Please add a method for optimized concat to the Semigroup class

2011-05-04 Thread John Lato

 From: Edward Kmett ekm...@gmail.com

 On Tue, May 3, 2011 at 3:43 PM, Yitzchak Gale g...@sefer.org wrote:

  I'm sure there are countless other natural examples of semigroups
  in the wild, and that the typical non-trivial ones will benefit
  from an optimized sconcat.
 

 Sold! (modulo the semantic considerations above)


Somewhat academic, but would there be a case for implementing sconcat in
terms of Foldable (or similar)?

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


Re: [Haskell-cafe] Please add a method for optimized concat to the Semigroup class

2011-05-04 Thread John Lato
On Wed, May 4, 2011 at 1:25 PM, Edward Kmett ekm...@gmail.com wrote:

 On Wed, May 4, 2011 at 7:40 AM, John Lato jwl...@gmail.com wrote:

 From: Edward Kmett ekm...@gmail.com


 On Tue, May 3, 2011 at 3:43 PM, Yitzchak Gale g...@sefer.org wrote:

  I'm sure there are countless other natural examples of semigroups
  in the wild, and that the typical non-trivial ones will benefit
  from an optimized sconcat.
 

 Sold! (modulo the semantic considerations above)


 Somewhat academic, but would there be a case for implementing sconcat in
 terms of Foldable (or similar)?


 There is a Foldable1 in semigroupoids. I could move it into the semigroups
 package, but at the consequence that Data.Semigroup.Foldable wouldn't look
 like Data.Foldable API-wise, since the Semigroupoid package is what
 introduces Apply and Bind, giving you an Applicative sans pure and a Monad
 sans return, which are needed to make most of the analogues to the Foldable
 functions.

 So to do so, I'd need to move those into this package. This is not entirely
 implausible, if somewhat inconvenient from the perspective of keeping the
 semigroups package tiny. The default definition would wind up being
 something like:

 class Semigroup a where
() :: a - a - a

sconcat :: Foldable1 f = f a - a
sconcat = fold1

 class Foldable f = Foldable1 f where
fold1 :: Semigroup a = f a - a
fold1 = foldMap1 id

foldMap1 :: Semigroup a = (b - a) - f b - a
foldMap1 = ...

foldr1 :: ...

foldl1 :: ...

 choosing sconcat = fold1 by default seems pretty much optimal under those
 conditions, saying that if your Semigroup doesn't have an optimized fold,
 you might as well let the container figure out what to do instead.

 If we do that though, I'm hard pressed to find anything better to
 specialize to for most semigroups, which is what I was saying earlier to
 Yitzchak, and why I had omitted sconcat from the original API.

 I suppose you might exploit foldl, foldr, foldl' or foldr' instead to play
 a bit with how your traversal associates by default, or to use a different,
 more efficient intermediate state though.

 However, I am somewhat worried that with the type of the container
 abstracted that it probably won't receive the same love from the strictness
 analyzer though.

 One other annoying implementation consequence is that it would make the
 Data.Semigroup and Data.Semigroup.Foldable modules rather hopelessly
 entangled, so that I'd have to factor out the classes into a common
 Internals module, then re-export the appropriate fragments through separate
 modules. =/


Good points.  I was hoping for a reply like this, since I don't have a good
intuition for how Foldable would fit into the semigroups package.  I don't
have a strong opinion in either direction.

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


Re: [Haskell-cafe] Iteratee: manyToOne

2011-04-29 Thread John Lato

 From: Felipe Almeida Lessa felipe.le...@gmail.com

 On Thu, Apr 28, 2011 at 1:10 PM, Felipe Almeida Lessa
 felipe.le...@gmail.com wrote:
  On Thu, Apr 28, 2011 at 12:09 PM, Felipe Almeida Lessa
  felipe.le...@gmail.com wrote:
  I foresee one problem: what is the leftover of 'manyToOne xs' if each
  x in xs needs different lengths of input?
 
  One possible untested-but-compiling solution:
  [snip]
 
  Like I said, that manyToOne implementation isn't very predictable
  about leftovers. ?But I guess that if all your iteratees consume the
  same input OR if you don't care about leftovers, then it should be
  okay.

 Sorry for replying to myself again. =)

 I think you can actually give predictable semantics to manyToOne:
 namely, the leftovers from the last iteratee are returned.  This new
 implementation should be better:


If you do this, the user needs to take care to order the iteratees so that
the last iteratee has small leftovers.  Consider:

manyToOne [consumeALot, return ()]

In this case, the entire stream consumed by the first iteratee will need to
be retained and passed on by manyToOne.  In many cases, the user may not
know how much each iteratee will consume, which can make these semantics
problematic.

Iteratee has 'enumPair', (renamed 'zip' in HEAD) which returns the leftovers
from whichever iteratee consumes more.  This avoids the problem of retaining
extra data, and seems simpler to reason about.  Although if you really need
to consume a predictable amount of data, the safest is probably to run the
whole thing in a 'take'.

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


Re: [Haskell-cafe] Iteratee: manyToOne

2011-04-29 Thread John Lato
On Fri, Apr 29, 2011 at 12:20 PM, Felipe Almeida Lessa 
felipe.le...@gmail.com wrote:

 On Fri, Apr 29, 2011 at 6:32 AM, John Lato jwl...@gmail.com wrote:
  If you do this, the user needs to take care to order the iteratees so
 that
  the last iteratee has small leftovers.  Consider:
 
  manyToOne [consumeALot, return ()]
 
  In this case, the entire stream consumed by the first iteratee will need
 to
  be retained and passed on by manyToOne.  In many cases, the user may not
  know how much each iteratee will consume, which can make these semantics
  problematic.
 
  Iteratee has 'enumPair', (renamed 'zip' in HEAD) which returns the
 leftovers
  from whichever iteratee consumes more.  This avoids the problem of
 retaining
  extra data, and seems simpler to reason about.  Although if you really
 need
  to consume a predictable amount of data, the safest is probably to run
 the
  whole thing in a 'take'.

 My motivation is: in general it is difficult (impossible?) to choose
 the iteratee that consumed more data because you don't know what the
 data is.  For example, if you give 'Chunks [a,b]' to two iteratees and
 one of them returns 'Chunks [c]' and the other one returns 'Chunks
 [d]', which one consumed more data?  The answer is that it depends on
 the types.  If they are Ints, both consumed the same, if they are
 ByteStrings, you would need to check if one is prefix of the other.
 What if one returns 'Chunks [c]' and the other one returns 'Chunks
 [d,e]'?  If they are ByteStrings, should we compare 'c' against 'd ++
 e'?


This situation results from the implementation in the enumerator package.
 In iteratee it doesn't arise with well-behaved* iteratees, because only one
chunk is ever processed at a time.  It's only necessary to check the length
of the returned chunks to see which consumed more data.

By well-behaved, I mean that the chunk returned by an iteratee must be a
tail of the provided input.  In other words, it returns only unconsumed data
from the stream and doesn't alter the stream.  At least in the iteratee
package, an iteratee which violates this rule is likely to result in
undefined behavior (in general, not just this function).



 So I thought it would be easier to program with an API that is
 predictable and immune to changes in block sizes.  If you don't want
 leftovers, just use 'manyToOne [..., dropWhile (const True)]', which
 guarantees that you won't leak.


Iteratees should be immune to changes in block sizes anyway, although it's
been a while since I looked at the enumerator implementation so it could be
different.

If you use 'manyToOne [..., dropWhile (const True)]', when does it
terminate?

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


Re: [Haskell-cafe] Question about the Monad instance for Iteratee (from the enumerator package)

2011-04-26 Thread John Lato
Joining slightly late...


 From: John Millikin jmilli...@gmail.com

 John Lato's iteratee package is based on IterateeMCPS.hs[1]. I used
 IterateeM.hs for enumerator, because when I benchmarked them the non-CPS
 version was something like 10% faster on most operations.


Based on tests I did before iteratee-0.4, the fastest implementation was
Oleg's alternate design which is in the comments of IterateeM.hs.  I don't
think any current packages use that however, with good reason.

I'd be interested to see the results of a shootout between iteratee and
enumerator.  I would expect them to be basically equivalent most of the
time, with maybe two or three operations with a small (but consistent)
difference one way or the other.

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


Re: [Haskell-cafe] Question about the Monad instance for Iteratee (from the enumerator package)

2011-04-26 Thread John Lato
On Tue, Apr 26, 2011 at 6:32 PM, John Millikin jmilli...@gmail.com wrote:

 On Tuesday, April 26, 2011 7:19:25 AM UTC-7, John Lato wrote:

 I'd be interested to see the results of a shootout between iteratee and
 enumerator.  I would expect them to be basically equivalent most of the
 time, with maybe two or three operations with a small (but consistent)
 difference one way or the other.


 I did some basic benchmarks a few months ago; if I remember correctly, it
 depends almost entirely on how well GHC optimizes CPS on a particular
 platform. The relative performace was very similar to Lennart Kolmodin's
 benchmarks of binary at 
 http://lennartkolmodin.blogspot.com/2011/02/binary-by-numbers.html . In
 particular, CPS/iteratee is faster on 32-bit, while state
 passing/enumerator is faster on 64-bit.

 This difference exists for almost all operations, and was on the order of
 5-15% depending on the shape of the input. I couldn't figure out a good way
 to benchmark the libraries themselves when there's so much noise from the
 compiler.


That figures.  Thanks for sharing this.

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


  1   2   3   4   >