Re: [Haskell-cafe] Stackage with GHC 7.8 has started

2013-10-14 Thread Michael Snoyman
On Mon, Oct 14, 2013 at 3:42 PM, Joachim Breitner
m...@joachim-breitner.dewrote:

 Hi,

 Am Sonntag, den 13.10.2013, 17:50 +0200 schrieb Michael Snoyman:

  I wanted to announce that FP Complete is now running a Jenkins job to
  build Stackage with GHC 7.8. You can see the current results in the
  relevant Github issue[1]. Essentially, we're still trying to get
  version bounds updated so that a build can commence.

 Great!

 Is there a way to view the jenkins build results somewhere?

 For some reason I miss a proper homepage of stackage with links to all
 the various resources (but maybe I’m blind).


No, you're not blind, I just haven't gotten things set up in that manner
yet. Specifically for GHC 7.8, there's nothing to display. Until a pull
request on HTTP is merge[1], there's nothing to show at all from the
Jenkins builds. But once that's done, it would be hard to display the
Jenkins results, since I run half the jobs from my local system, and then
the other half from the FP Complete build server. If anyone has experience
with publishing Jenkin's build reports from two different systems and
wouldn't mind helping me out, please be in touch, it would be nice to get
the information available in a more publicly-accessible manner.

Michael

[1] https://github.com/haskell/HTTP/pull/47
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Stackage with GHC 7.8 has started

2013-10-13 Thread Michael Snoyman
Hi everyone,

I wanted to announce that FP Complete is now running a Jenkins job to build
Stackage with GHC 7.8. You can see the current results in the relevant
Github issue[1]. Essentially, we're still trying to get version bounds
updated so that a build can commence.

I'd like to ask two things from the community:

* If you have a package with a restrictive upper bound, now's a good time
to start testing that package with GHC 7.8 and relaxing those upper bounds.
It would be great if, when GHC 7.8 is released, a large percentage of
Hackage already compiled with it.
* If you have a package on Hackage that is not yet on Stackage, now's a
great time to add it. We're going to be doing daily builds against three
versions of GHC (7.4.2, 7.6.3, and 7.8), which will help ensure your
packages continue to build consistently.

Michael

[1] https://github.com/fpco/stackage/issues/128
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Lifting IO actions into Applicatives

2013-10-01 Thread Michael Snoyman
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


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

2013-10-01 Thread Michael Snoyman
On Tue, Oct 1, 2013 at 12:15 PM, Dan Burton danburton.em...@gmail.comwrote:

 From what you've said, it sounds like you can already write:

 serverSide :: IO a - Form a

 This seems elegant enough to me for your needs. Just encourage it as an
 idiom specific to Forms.

 myBlogForm = Blog $ titleForm * serverSide getCurrentTime *
 contentsForm

 Could you abstract `serverSide` out into a typeclass, such as
 ApplicativeIO? Sure. but why bother? The point is, you've got the
 specialization you need already.



Yes, I agree that to simply solve the problem in yesod-form, this would be
a great solution. But as to why bother with ApplicativeIO: my point in
sending this email was to see if other people have been bothered by this,
and if it's therefore worth coming up with a general purpose solution. If
there's no real interest in it, I don't see a need to create such a general
solution. On the other hand, if people think this is worth a general
ApplicativeIO class, I'd be happy to use that instead of defining an ad-hoc
function in yesod-form.

Thanks to everyone for this great discussion, I'm thoroughly enjoying
following it.

Michael
___
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 Michael Snoyman
On Tue, Oct 1, 2013 at 10:24 AM, Alexey Uimanov s9gf4...@gmail.com wrote:

 Maybe this is needed new typeclass ApplicativeTrans?



There's actually no problem with defining a MonadTrans instance for
non-monads. Obviously this can't follow the laws directly (since they're
defined in terms of monadic bind and return), but I think we could probably
state Applicative versions of those laws (assuming I haven't made a stupid
mistake):

lift . pure = pure
lift (x * y) = lift x * lift y

Michael


 2013/10/1 Michael Snoyman mich...@snoyman.com

 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


___
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 Michael Snoyman
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.



 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

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

2013-09-16 Thread Michael Snoyman
On Tue, Sep 17, 2013 at 4:25 AM, John Lato jwl...@gmail.com wrote:

 On Mon, Sep 16, 2013 at 4:57 AM, Michael Snoyman mich...@snoyman.comwrote:


 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.



OK, I've added both LooseMap, and storable vector instances:

https://github.com/snoyberg/mono-traversable/commit/3f1c78eb12433a1e65d53b51a7fe1eb69ff80eec

Does that look reasonable?

Michael
___
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-13 Thread Michael Snoyman
On Fri, Sep 13, 2013 at 9:18 AM, Mario Blažević blama...@acanac.net wrote:

 On 09/13/13 01:51, Michael Snoyman wrote:

 On Fri, Sep 13, 2013 at 5:38 AM, Mario Blažević blama...@acanac.netmailto:
 blama...@acanac.net wrote:

 On 09/11/13 19:37, John Lato wrote:


 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.


 If monolithic classes bother you, my monoid-subclasses
 package manages to break down the functionality into several
 classes. One big difference is that everything is based off Monoid
 rather than Foldable, and that has some big effects on the interface.



 I'd point out what I'd consider a bigger difference: the type signatures
 have changed in a significant way. With MonoFoldable, folding on a
 ByteString would be:

 (Word8 - b - b) - b - ByteString - b

 With monoid-subclasses, you get:

 (ByteString - b - b) - b - ByteString - b

 There's certainly a performance issue to discuss, but I'm more worried
 about semantics. Word8 tells me something very specific: I have one, and
 precisely one, octet. ByteString tells me I have anywhere from 0 to 2^32 or
 2^64  octets. Yes, we know from context that it will always be of size one,
 but the type system can't enforce that invariant.


 All true, but we can also use this generalization to our advantage.
 For example, the same monoid-subclasses package provides ByteStringUTF8, a
 newtype wrapper around ByteString. It behaves the same as the plain
 ByteString except its atomic factors are not of size 1, instead it folds on
 UTF-8 encoded character boundaries. You can't represent that in Haskell's
 type system.



I can think of two different ways of achieving this approach with
MonoFoldable instead: by setting `Element` to either `Char` or
`ByteStringUTF8`. The two approaches would look like:

newtype ByteStringUTF8A = ByteStringUTF8A S.ByteString
type instance Element ByteStringUTF8A = Char
instance MonoFoldable ByteStringUTF8A where
ofoldr f b (ByteStringUTF8A bs) = ofoldr f b (decodeUtf8 bs)
ofoldl' = undefined

newtype ByteStringUTF8B = ByteStringUTF8B S.ByteString
type instance Element ByteStringUTF8B = ByteStringUTF8B
instance MonoFoldable ByteStringUTF8B where
ofoldr f b (ByteStringUTF8B bs) = ofoldr (f . ByteStringUTF8B .
encodeUtf8 . T.singleton) b (decodeUtf8 bs)
ofoldl' = undefined

I'd personally prefer the first approach, as that gives the right
guarantees at the type level: each time the function is called, it will be
provided with precisely one character. I believe the second approach
provides the same behavior as monoid-subclasses does right now.

Michael
___
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-13 Thread Michael Snoyman
On Fri, Sep 13, 2013 at 10:07 AM, Mario Blažević blama...@acanac.netwrote:

 On 09/13/13 02:28, Michael Snoyman wrote:




 On Fri, Sep 13, 2013 at 9:18 AM, Mario Blažević blama...@acanac.netmailto:
 blama...@acanac.net wrote:

 On 09/13/13 01:51, Michael Snoyman wrote:

 On Fri, Sep 13, 2013 at 5:38 AM, Mario Blažević
 blama...@acanac.net mailto:blama...@acanac.net
 mailto:blama...@acanac.net mailto:blama...@acanac.net wrote:

 On 09/11/13 19:37, John Lato wrote:


 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.


 If monolithic classes bother you, my monoid-subclasses
 package manages to break down the functionality into several
 classes. One big difference is that everything is based
 off Monoid
 rather than Foldable, and that has some big effects on the
 interface.



 I'd point out what I'd consider a bigger difference: the type
 signatures have changed in a significant way. With
 MonoFoldable, folding on a ByteString would be:

 (Word8 - b - b) - b - ByteString - b

 With monoid-subclasses, you get:

 (ByteString - b - b) - b - ByteString - b

 There's certainly a performance issue to discuss, but I'm more
 worried about semantics. Word8 tells me something very
 specific: I have one, and precisely one, octet. ByteString
 tells me I have anywhere from 0 to 2^32 or 2^64  octets. Yes,
 we know from context that it will always be of size one, but
 the type system can't enforce that invariant.


 All true, but we can also use this generalization to our
 advantage. For example, the same monoid-subclasses package
 provides ByteStringUTF8, a newtype wrapper around ByteString. It
 behaves the same as the plain ByteString except its atomic factors
 are not of size 1, instead it folds on UTF-8 encoded character
 boundaries. You can't represent that in Haskell's type system.



 I can think of two different ways of achieving this approach with
 MonoFoldable instead: by setting `Element` to either `Char` or
 `ByteStringUTF8`. The two approaches would look like:

 newtype ByteStringUTF8A = ByteStringUTF8A S.ByteString
 type instance Element ByteStringUTF8A = Char
 instance MonoFoldable ByteStringUTF8A where
 ofoldr f b (ByteStringUTF8A bs) = ofoldr f b (decodeUtf8 bs)
 ofoldl' = undefined

 newtype ByteStringUTF8B = ByteStringUTF8B S.ByteString
 type instance Element ByteStringUTF8B = ByteStringUTF8B
 instance MonoFoldable ByteStringUTF8B where
 ofoldr f b (ByteStringUTF8B bs) = ofoldr (f . ByteStringUTF8B .
 encodeUtf8 . T.singleton) b (decodeUtf8 bs)
 ofoldl' = undefined

 I'd personally prefer the first approach, as that gives the right
 guarantees at the type level: each time the function is called, it will be
 provided with precisely one character. I believe the second approach
 provides the same behavior as monoid-subclasses does right now.


 Right now monoid-subclasses actually provides both approaches. You're
 correct that it provides the second one as instance FactorialMonoid
 ByteStringUTF8, but it also provides the former as instance TextualMonoid
 ByteStringUTF8. The TextualMonoid class is basically what you'd get if you
 restricted MonoFoldable to type Elem=Char. I wanted to keep the package
 extension-free, you see.


Got it, that makes sense.


 My main point is that it's worth considering basing MonoFoldable on
 FactorialMonoid, because it can be considered its specialization. Methods
 like length, take, or reverse, which never mention the item type in their
 signature, can be inherited from the FactorialMonoid superclass with no
 change whatsoever. Other methods would differ in their signatures (and
 performance), but the semantics would carry over.



My immediate concern is that this would enforce a number of restrictions on
what could be a MonoFoldable. For example, you couldn't have an instance
for `Identity a`. Being able to fold over any arbitrary container, even if
it's not a Monoid, can be very useful.

Michael
___
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-12 Thread Michael Snoyman
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.

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.

[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.




 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

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

2013-09-12 Thread Michael Snoyman
On Fri, Sep 13, 2013 at 5:38 AM, Mario Blažević blama...@acanac.net wrote:

 On 09/11/13 19:37, John Lato wrote:

 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.


 If monolithic classes bother you, my monoid-subclasses package
 manages to break down the functionality into several classes. One big
 difference is that everything is based off Monoid rather than Foldable, and
 that has some big effects on the interface.



I'd point out what I'd consider a bigger difference: the type signatures
have changed in a significant way. With MonoFoldable, folding on a
ByteString would be:

(Word8 - b - b) - b - ByteString - b

With monoid-subclasses, you get:

(ByteString - b - b) - b - ByteString - b

There's certainly a performance issue to discuss, but I'm more worried
about semantics. Word8 tells me something very specific: I have one, and
precisely one, octet. ByteString tells me I have anywhere from 0 to 2^32 or
2^64  octets. Yes, we know from context that it will always be of size one,
but the type system can't enforce that invariant.

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


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

2013-09-11 Thread Michael Snoyman
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 ByteString.



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



 ___
 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] Proposal: New syntax for Haskell

2013-09-10 Thread Michael Snoyman
I'll admit, I also thought it was a joke.


On Tue, Sep 10, 2013 at 2:34 PM, Ian Ross i...@skybluetrades.net wrote:

 Me too, but I wasn't brave enough to say so after people seemed to be
 taking it seriously...


 On 10 September 2013 13:33, Roman Cheplyaka r...@ro-che.info wrote:

 * John Wiegley jo...@fpcomplete.com [2013-09-10 04:48:36-0500]
   Niklas Hambüchen m...@nh2.me writes:
 
   Code written in cucumber syntax is concise and easy to read
 
  concise |kənˈsīs|, adj.
 
  giving a lot of information clearly and in a few words; brief but
  comprehensive.
 
  Compare:
 
  Scenario: Defining the function foldl
Given I want do define foldl
Which has the type (in brackets) a to b to a (end of brackets),
   to a, to list of b, to a
And my arguments are called f, acc, and l
When l is empty
Then the result better be acc
Otherwise l is x cons xs
Then the result should be foldl f (in brackets) f acc x
  (end of brackets) xs
 
  To:
 
  foldl :: (a - b - a) - a - [b] - a
  foldl f z [] = z
  foldl f z (x:xs) = foldl f (f z x) xs
 
  How is that more concise or preferable?

 I thought it was a joke.

 Roman

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




 --
 Ian Ross   Tel: +43(0)6804451378   i...@skybluetrades.net
 www.skybluetrades.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] Conduit : is it possible to write this function?

2013-08-23 Thread Michael Snoyman
You can build this up using the = operator[1] in stm-conduit, something
like:

eitherSrc :: MonadResourceBase m
 = Source (ResourceT m) a - Source (ResourceT m) b - Source
(ResourceT m) (Either a b)
eitherSrc src1 src2 = do
join $ lift $ Data.Conduit.mapOutput Left src1 =
Data.Conduit.mapOutput Right src2

I think this can be generalized to work with more base monads with some
tweaks to (=).

[1]
http://haddocks.fpcomplete.com/fp/7.4.2/20130704-120/stm-conduit/Data-Conduit-TMChan.html#v:-62--61--60-


On Fri, Aug 23, 2013 at 11:32 AM, Erik de Castro Lopo
mle...@mega-nerd.comwrote:

 Hi all

 Using the Conduit library is it possible to write the function:

eitherSrc :: MonadResource m
  = Source m a - Source m b - Source m (Either a b)

 which combines two sources into new output source such that data being
 produced aysnchronously by the original two sources will be returned
 as either a Left or Right of tne new source?

 If so, how?

 Cheers,
 Erik
 --
 --
 Erik de Castro Lopo
 http://www.mega-nerd.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] using network+conduit+tls for a client application?

2013-07-29 Thread Michael Snoyman
I've actually been intending to add the client side code to that package,
but I simply haven't gotten around to it yet. It's actually not that
complicated, but it does require some thought on the right interface for
things like approving/rejecting server side certificates. If you open up an
issue on Github for this, I'd be happy to continue the conversation there
and we can try to get out a new version of the library. (I just don't want
to spam the Cafe with an exploratory design discussion.)


On Mon, Jul 29, 2013 at 11:08 AM, Petr Pudlák petr@gmail.com wrote:

 Dear Haskellers,

 I wanted to write a small TLS application (connecting to IMAP over TLS)
 and it seemed natural to use conduit for that. I found the
 network-conduit-tls package, but then I realized it's meant only for server
 applications. Is there something similar for client applications?

   Thank you,
   Petr Pudlak

 __**_
 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] Correct way to catch all exceptions

2013-07-12 Thread Michael Snoyman
When I implemented this stuff yesterday, I included `Deep` variants for
each function which used NFData. I'm debating whether I think the right
recommendation is to, by default, use the `async`/NFData versions of catch,
handle, and try, or to have them as separate functions.

I wrote up the blog post, both on the Yesod blog[1] and School of
Haskell[2]. The latter's a bit easier to use since it includes active code
snippets.

[1] http://www.yesodweb.com/blog/2013/07/catching-all-exceptions
[2]
https://www.fpcomplete.com/user/snoyberg/general-haskell/exceptions/catching-all-exceptions


On Fri, Jul 12, 2013 at 4:03 AM, John Lato jwl...@gmail.com wrote:

 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-11 Thread Michael Snoyman
On Thu, Jul 11, 2013 at 3:44 AM, John Lato jwl...@gmail.com wrote:

 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.



I've spent some time thinking about this, and I'm beginning to think the
separate thread approach is in fact the right way to solve this. I think
there's really an important distinction to be made that we've all gotten
close to, but not specifically identified: the exception type itself isn't
really what we're interested, it's how that exception was thrown which is
interesting. I've put together an interesting demonstration[1].

The test I've created is that a worker thread is spawned. In the worker
thread, we run an action and wrap it in a tryAll function. Meanwhile, in
the main thread, we try to read a file and, when it fails, throw that
IOException to the worker thread. In this case, we want the worker thread
to halt execution immediately. With the naive try implementation (tryAll1)
this will clearly not happen, since the async exception will be caught as
if the subaction itself threw the exception. The more intelligent tryAll3
does the same thing, since it is viewing the thrown exception as
synchronous based on its type, when in reality it was thrown as an async
exception.[2] The only approach that handles the situation correctly is
John's separate thread approach (tryAll3). The reason is that it is
properly differentiating based on how the exception was thrown.

I'm going to play around with this a bit more; in particular, I want to see
how this works with monad transformer stacks. But I at least feel like I
have a slightly better conceptual grasp on what's going on here. Thanks for
pointing this out John.

Michael

[1] https://gist.github.com/snoyberg/5975592
[2] You could also do the reverse: thrown an async exception synchronously,
and similarly get misleading results.
___
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 Michael Snoyman
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


[Haskell-cafe] Correct way to catch all exceptions

2013-07-10 Thread Michael Snoyman
There's a pattern that arises fairly often: catching every exception thrown
by code. The naive approach is to do something like:

result - try someCode
case result of
Left (e :: SomeException) - putStrLn $ It failed:  ++ show e
Right realValue - useRealValue

This seems perfectly valid, except that it catches a number of exceptions
which seemingly should *not* be caught. In particular, it catches the async
exceptions used by both killThread and timeout.

I think it's fair to say that there's not going to be a single function
that solves all cases correctly, but it is a common enough situation that
people need to write code that resumes work in the case of an exception
that I think we need to either have some guidelines for the right approach
here, or perhaps even a utility function along the lines of:

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?
___
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 Michael Snoyman
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 which works
on any instance of Exception, which uses the assumptions I mentioned in the
previous paragraph. If it's then decided that this is generally useful
enough to be included in the Exception typeclass, we have a straightforward
migration path:

   1. Add the new method to the Exception typeclass, with a default
   implementation that conforms with our assumptions.
   2. For any of the special standard exception types (e.g.,
   AsyncException), override that default implementation.
   3. Modify the external package to simply re-export the new method when
   using newer versions of base, using conditional compilation.
   4. Any code written against that external package would work with both
   current and future versions of base.
   5. The only incompatibility would be if someone writes code which
   overrides the typeclass method; that code would only work with newer bases,
   not current ones.

Any thoughts on this? I'm not sure exactly what would be the right method
to add to the Exception typeclass, but if we can come to consensus on that
and there are no major objections to my separate package proposal, I think
this would be something moving forward on, including a library proposal.

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


Re: [Haskell-cafe] ANNOUNCE: new bridge! (prelude-prime)

2013-05-23 Thread Michael Snoyman
On Thu, May 23, 2013 at 11:38 AM, Anton Kholomiov anton.kholom...@gmail.com
 wrote:

 I wish it was possible to use an extension

 CustomPrelude = Prelude.Prime

 In the cabal file



I'm not necessarily opposed to this idea, but I'd like to point out that it
can have a negative impact on readability of an individual module, since
you can't tell which Prelude is being used. This is the same argument used
for putting LANGUAGE pragmas in a modules instead of listing them in a
cabal file. I think in the case of an alternate Prelude, the argument is
stronger, since language extensions often don't change the meaning of code,
but instead allow previously invalid code to be valid.

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


Re: [Haskell-cafe] Stream processing

2013-05-11 Thread Michael Snoyman
It's quite old at this point, but you may be interested in reading the
initial motivations for creating conduit when the iteratee pattern (and
enumerator library in particular) already existed:

https://github.com/snoyberg/conduit/blob/master/README.md#general-goal

I would say the only real component missing from your list is being able to
structure significantly more complicated control flows, such as the use
case of combining a web server and web client into a web proxy. That was
probably the example which finally pushed me to start thinking seriously
about an enumerator replacement. In conduit, this use case is addressed by
connect-and-resume, which essentially allows you to escape the inversion of
control normally introduced by the conduit pattern.


On Fri, May 10, 2013 at 5:56 PM, Ertugrul Söylemez e...@ertes.de wrote:

 Hello everybody,

 I'm trying to formulate the stream processing problem, which doesn't
 seem to be solved fully by the currently existing patterns.  I'm
 experimenting with a new idea, but I want to make sure that I don't miss
 any defining features of the problem, so here is my list.  A stream
 processing abstraction should:

   * have a categorically proven design (solved by iteratees, pipes),

   * be composable (solved by all of them),

   * be reasonably easy to understand and work with (solved by conduit,
 pipes),

   * support leftovers (solved by conduit and to some degree by
 iteratees),

   * be reliable in the presence of async exceptions (solved by conduit,
 pipes-safe),

   * hold on to resources only as long as necessary (solved by conduit
 and to some degree by pipes-safe),

   * ideally also allow upstream communication (solved by pipes and to
 some degree by conduit).

   * be fast (solved by all of them).

 Anything else you would put in that list?


 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] Fwd: Google Summer of Code, news

2013-04-29 Thread Michael Snoyman
I'll throw in that Marcos mentioned this very issue to me about his code
before showing it to me. It was written the way it was for the requirements
of his course. He volunteered to translate the comments for me, but I told
him it wasn't necessary in order to get an initial feel for the code (I
also read Spanish somewhat).


On Mon, Apr 29, 2013 at 5:25 PM, Kristopher Micinski krismicin...@gmail.com
 wrote:

 I second that advice!  I can technically read Spanish, but I find the
 complexity of the language barrier compounded with trying to
 understand the code becomes more confusing than I'd prefer :-).

 Kris


 On Sun, Apr 28, 2013 at 2:19 PM, Mateusz Kowalczyk
 fuuze...@fuuzetsu.co.uk wrote:
  -BEGIN PGP SIGNED MESSAGE-
  Hash: SHA1
 
  On 28/04/13 18:37, Marcos Pividori wrote:
  Greetings,
 
  I am a Computer Science student from Argentina. I am interested in
  working this summer in a project related to Haskell for the Google
  Summer of Code. I have been discussing my idea with Michael Snoyman
  in order to have a clearer idea. Now, I would like to know the
  community interest in this project.
 
  I want to develop a server-side library in Haskell for sending
  push notifications to devices running different OS, such as
  Android, iOS, Windows Phone, BlackBerry, and so on.
 
  To pass a subject, I have recently worked with Yesod (a Web
  Framework based in Haskell) developing a server to comunicate with
  Android-powered devices through Google Cloud Messaging.  (It is
  available: https://github.com/MarcosPividori/Yesod-server-for-GCM
  )
 
  To develop this project, I have read a lot about this service and
  Yesod libraries, and I developed two programs, a server written in
  Haskell and an Android application for mobile phones. Also, I
  developed an EDSL to write programs which exchange information with
  the devices.
 
  I would be grateful if you could give me your opinion about this
  project and the proposal I am starting to write.
 
  While I don't have anything to contribute to the project idea itself,
  I had a look at your code on GitHub and I'd like to recommend that in
  the future, when writing code that will get published and used by
  others, you use English. This especially applies to projects aimed to
  benefit a wider community such as this one. You seem to be mixing the
  two together which doesn't help readability either.
 
 
  - --
  Mateusz K.
  -BEGIN PGP SIGNATURE-
  Version: GnuPG v2.0.19 (GNU/Linux)
 
  iQIcBAEBAgAGBQJRfWhMAAoJEM1mucMq2pqXJH8P/RqWzAHFlbkLPRSzRK3w+Us2
  I+VDOGxF6627RwWSX3P5gY84t8lhGQZ8M9voGptKnNE+2xmArtqQIn6a9Jj01o3n
  PcV6SuacG5qNpHawQdVXSFoIGkQ9tNhSDu4HYgXTRQD1tptxd31pKi9gN2EE6ieA
  HgdR6g688edLjdfbGj18CDNnFxIJhzsFYoqaNgBZB4ZpcCisQzdkwGELx8c3+fa2
  deSbsvA808q/xPiFZ6DDCOF0aXQmvQwtVdCdhyrn4BPMhGF2da9zqcy3VNPHWMd5
  VNnw4USY1vVdsTY6fKts5IyuNhIl7WTGypNUbIMl3gCpH1RWgO8FbKZQmyvosPPv
  xCA7qpPVkc8sg2qSBiQyJ66upg5503bCoijNYxGmCAaFm83bJdUgwrhnOBoyguPC
  S86g6zNUrbV6oQDAPy3unOKLlCGJhlQgEx9dbXPDCQiqWeUqhVipqxf0WHDcTPMW
  prjWzqZTJkm1kq11G4Ues4sXpJDzG0syWroaO4ah0A6aCZzuFFX8NqcQvEufzRCS
  ydOF9Qgr5nuVcBndjekYw9uxA6UtRDKoyvmvr0y5TDfk7w42dC/qPOhK5xkndz7u
  pjXnIGanqBur1B5Fw5jfilzc5eViOYDGGtZqz4/mKV6lfQclTljTVI461HrSQW+H
  SVdK4oqvGU0ZCD94BBHv
  =+KLZ
  -END PGP SIGNATURE-
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe

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

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


Re: [Haskell-cafe] How to design an network client with user program.

2013-04-10 Thread Michael Snoyman
It doesn't seem like you're trying to perform multiple actions
simultaneously. For example, you don't need to be able to read from the
server and send data back at the same time. Instead, you'll have a single
thread of execution. Am I right?

If so, it seems like the simplest thing would be for you to allow users to
write something like:

Conduit MsgFromServer m MsgToServer

Assuming you had conduits to convert an incoming byte stream to a stream of
MsgFromServer and the equivalent for sending, you'd end up with something
like:

appSource appData $$ toMsgFromServer =$ clientSuppliedConduit =$
fromMsgToServer =$ appSink appData

Michael


On Tue, Apr 9, 2013 at 1:09 PM, Alexander V Vershilov 
alexander.vershi...@gmail.com wrote:


 Hello.

 I have next problem: I have a network client that connects to server,
 listens for messages and generate responces. So the control flow can be
 represended as:

 server -- input - {generate output} - output

 Output can be generated using default implementation or can overriden by
 user.

 The main difficulty appeares when I need to add a user program on the top
 of this logic,
 i.e. from user-side I want to have dsl:smth like

 withClient $ do
x - send message
waitFor x
timeout 500
forever $ sendRandomMessage

 i.e. an ability to send messages, waiting for some event (message to
 come), waiting for
 timeout.

 The question is how to define such logic without a big overhead. I see a
 solution using conduit, it's possible to create 3 processes: listener,
 user, sender.

  + user +
  ||
 -input - listener +-+ sender -

 and use TQueue or TChan to send messages between them, however there can
 be another possible solutions, that uses less resources, or another design.


 --
 Alexander

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


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


Re: [Haskell-cafe] How to design an network client with user program.

2013-04-10 Thread Michael Snoyman
On Wed, Apr 10, 2013 at 2:08 PM, Alexander V Vershilov 
alexander.vershi...@gmail.com wrote:


 On 10 April 2013 14:56, Michael Snoyman mich...@snoyman.com wrote:

 It doesn't seem like you're trying to perform multiple actions
 simultaneously. For example, you don't need to be able to read from the
 server and send data back at the same time. Instead, you'll have a single
 thread of execution. Am I right?


 Not  exaclty, user code is not only SeverMessage driven but can generate
 messages and works on it's own (time-events, or some external events).
 For example user code may generate random messages even there is no
 message from server, (i.e. wait for some
 timeout and then feed sender with message), or do some long running
 events, (e.g. wait for 5 minutes), in both
 of those cases one threaded pipeline is broken.


Then some kind of TQueue or TChan approach is going to be necessary.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Conduit] weird action of leftover.

2013-04-08 Thread Michael Snoyman
It's a bug in your implementation of takeLine I believe. It doesn't take
into account that lines can span multiple chunks. When you call takeLine
the first time, you get L1\n. leftover puts a chunk with exactly those
contents back. When you call takeLine the second time, it gets the chunk
L1\n, and your splitAt gives you back L1\n and . The  is then
leftover, and the next call to takeLine gets it.

Your takeLine needs to include logic saying there's no newline in this
chunk at all, let's get the next chunk and try that. You can look at the
source to lines[1] for an example of the concept.

Michael

[1]
http://haddocks.fpcomplete.com/fp/7.4.2/20130313-1/conduit/src/Data-Conduit-Binary.html#lines


On Mon, Apr 8, 2013 at 8:44 AM, Magicloud Magiclouds 
magicloud.magiclo...@gmail.com wrote:

 Say I have code like below. If I comment the leftover in main, I got (Just
 L1\n, Just L2\n, Just L3\n, Just L4\n). But if I did not comment
 the leftover, then I got (Just L1\n, Just L1\n, Just , Just L2\n).
 Why is not it (Just L1\n, Just L1\n, Just L2\n, Just L3\n)?

 takeLine :: (Monad m) = Consumer ByteString m (Maybe ByteString)
 takeLine = do
   mBS - await
   case mBS of
 Nothing - return Nothing
 Just bs -
   case DBS.elemIndex _lf bs of
 Nothing - return $ Just bs
 Just i - do
   let (l, ls) = DBS.splitAt (i + 1) bs
   leftover ls
   return $ Just l

 main = do
   m - runResourceT $ sourceFile test.simple $$ (do
 a - takeLine
 leftover $ fromJust a
 b - takeLine
 c - takeLine
 d - takeLine
 return (a, b, c, d))
   print m

 --
 竹密岂妨流水过
 山高哪阻野云飞

 And for G+, please use magiclouds#gmail.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] GSoC Project Proposal: Markdown support for Haddock

2013-04-08 Thread Michael Snoyman
It supports ```language blocks, but not autolink detection. I have not
fully documented which features are supported. I also haven't done any
performance analysis versus other tools, simply because my goal is in no
way high efficiency. It is fast enough for my use cases, and I don't intend
to spend significant time optimizing unless a problematic level of
inefficiency is discovered. If anyone else wants to put together
benchmarks, I'll be happy to lend some guidance.


On Mon, Apr 8, 2013 at 12:50 PM, Niklas Hambüchen m...@nh2.me wrote:

 Could you elaborate a bit on which markdown features you support (or
 even better: write it into your module haddocks)?

 Thinks like
 - autolink detection
 - ```language blocks?

 Also, you build on performance-oriented libraries - it would be cool if
 you could make a small benchmark comparing with the standard
 C/Python/Ruby parser implementations; AFAIK there is a standard Markdown
 test suite that this could run against.

 Concerning the project proposal:

 I especially find the last feature useful for programming documentation,
 and would love to have them in a potential haddock succesor. I was also
 pleasantly surprised that pandoc seems to handle all of this (even with
 code syntax highlighting).

 On 05/04/13 02:10, Michael Snoyman wrote:
  In case it can be useful in any way for this project, my markdown
  package[1] is certainly available for scavenging, though we'd likely
  want to refactor it to not use conduit (I can't imagine conduit being a
  good dependency for Haddock).
 
  [1] http://hackage.haskell.org/package/markdown

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


Re: [Haskell-cafe] [Conduit] weird action of leftover.

2013-04-08 Thread Michael Snoyman
Yes, that's a fair explanation.


On Tue, Apr 9, 2013 at 7:48 AM, Magicloud Magiclouds 
magicloud.magiclo...@gmail.com wrote:

 Thank you for the reply. I've learnt the code of lines. So it is because
 how ByteString works, that the conduit is not a stream of bytes, but
 chunks, right?


 On Tue, Apr 9, 2013 at 12:12 PM, Michael Snoyman mich...@snoyman.comwrote:

 It's a bug in your implementation of takeLine I believe. It doesn't take
 into account that lines can span multiple chunks. When you call takeLine
 the first time, you get L1\n. leftover puts a chunk with exactly those
 contents back. When you call takeLine the second time, it gets the chunk
 L1\n, and your splitAt gives you back L1\n and . The  is then
 leftover, and the next call to takeLine gets it.

 Your takeLine needs to include logic saying there's no newline in this
 chunk at all, let's get the next chunk and try that. You can look at the
 source to lines[1] for an example of the concept.

 Michael

 [1]
 http://haddocks.fpcomplete.com/fp/7.4.2/20130313-1/conduit/src/Data-Conduit-Binary.html#lines


 On Mon, Apr 8, 2013 at 8:44 AM, Magicloud Magiclouds 
 magicloud.magiclo...@gmail.com wrote:

 Say I have code like below. If I comment the leftover in main, I got
 (Just L1\n, Just L2\n, Just L3\n, Just L4\n). But if I did not
 comment the leftover, then I got (Just L1\n, Just L1\n, Just , Just
 L2\n).
 Why is not it (Just L1\n, Just L1\n, Just L2\n, Just L3\n)?

 takeLine :: (Monad m) = Consumer ByteString m (Maybe ByteString)
 takeLine = do
   mBS - await
   case mBS of
 Nothing - return Nothing
 Just bs -
   case DBS.elemIndex _lf bs of
 Nothing - return $ Just bs
 Just i - do
   let (l, ls) = DBS.splitAt (i + 1) bs
   leftover ls
   return $ Just l

 main = do
   m - runResourceT $ sourceFile test.simple $$ (do
 a - takeLine
 leftover $ fromJust a
 b - takeLine
 c - takeLine
 d - takeLine
 return (a, b, c, d))
   print m

 --
 竹密岂妨流水过
 山高哪阻野云飞

 And for G+, please use magiclouds#gmail.com.

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





 --
 竹密岂妨流水过
 山高哪阻野云飞

 And for G+, please use magiclouds#gmail.com.

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


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

2013-04-04 Thread Michael Snoyman
On Thu, Apr 4, 2013 at 7:49 PM, Johan Tibell johan.tib...@gmail.com wrote:

 Hi all,

 Haddock's current markup language leaves something to be desired once
 you want to write more serious documentation (e.g. several paragraphs
 of introductory text at the top of the module doc). Several features
 are lacking (bold text, links that render as text instead of URLs,
 inline HTML).

 I suggest that we implement an alternative haddock syntax that's a
 superset of Markdown. It's a superset in the sense that we still want
 to support linkifying Haskell identifiers, etc. Modules that want to
 use the new syntax (which will probably be incompatible with the
 current syntax) can set:

 {-# HADDOCK Markdown #-}

 on top of the source file.

 Ticket: http://trac.haskell.org/haddock/ticket/244

 -- Johan

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


+1

In case it can be useful in any way for this project, my markdown
package[1] is certainly available for scavenging, though we'd likely want
to refactor it to not use conduit (I can't imagine conduit being a good
dependency for Haddock).

[1] http://hackage.haskell.org/package/markdown
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Join a transformer

2013-03-13 Thread Michael Snoyman
I'm wondering if this pattern exists and has a name. We have the concept of
joining a Monad:

join :: Monad m = m (m a) - ma

How about joining a monad transformer?

joinT :: (Monad m, MonadTrans t) = t (t m) a - t m a

I believe implementing this in terms of MonadTransControl[1] might be
possible, but I was wondering if there's an already existing idiom for this.

Michael

[1]
http://haddocks.fpcomplete.com/fp/7.4.2/20130301-40/monad-control/Control-Monad-Trans-Control.html
___
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 Michael Snoyman
Just to clarify: the problem was in fact with my code, I was not passing
O_TRUNC to the open system call. Gregory's C code showed me the problem.
Once I add in that option, all the different benchmarks complete in roughly
the same amount of time. So given that our Haskell implementations based on
Handle are just about as fast as a raw C implementation, I'd say Handle is
performing very well.

Apologies if I got anyone overly concerned.


On Fri, Mar 8, 2013 at 12: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.

 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

Re: [Haskell-cafe] File I/O benchmark help (conduit, io-streams and Handle)

2013-03-08 Thread Michael Snoyman
That demonstrated the issue: I'd forgotten to pass O_TRUNC to the open
system call. Adding that back makes the numbers much more comparable.

Thanks for the input everyone, and Gregory for finding the actual problem
(as well as pointing out a few other improvements).


On Fri, Mar 8, 2013 at 12:13 PM, Gregory Collins g...@gregorycollins.netwrote:

 Something must be wrong with the conduit NoHandle code. I increased the
 filesize to 60MB and implemented the copy loop in pure C, the code and
 results are here:

 https://gist.github.com/gregorycollins/5115491

 Everything but the conduit NoHandle code runs in roughly 600-620ms,
 including the pure C version.

 G


 On Fri, Mar 8, 2013 at 10:13 AM, Alexander Kjeldaas 
 alexander.kjeld...@gmail.com wrote:




 On Fri, Mar 8, 2013 at 9:53 AM, Gregory Collins 
 g...@gregorycollins.netwrote:

 On Fri, Mar 8, 2013 at 9:48 AM, John Lato jwl...@gmail.com wrote:

 For comparison, on my system I get
 $ time cp input.dat output.dat

 real 0m0.004s
 user 0m0.000s
 sys 0m0.000s


 Does your workstation have an SSD? Michael's using a spinning disk.


 If you're only copying a GB or so, it should only be memory traffic.

 Alexander



 --
 Gregory Collins g...@gregorycollins.net

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





 --
 Gregory Collins g...@gregorycollins.net

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


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


[Haskell-cafe] File I/O benchmark help (conduit, io-streams and Handle)

2013-03-07 Thread Michael Snoyman
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


Re: [Haskell-cafe] File I/O benchmark help (conduit, io-streams and Handle)

2013-03-07 Thread Michael Snoyman
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


Re: [Haskell-cafe] Simple way to do something like ArrowChoice.right on a Conduit? (version 1.0.0)

2013-03-05 Thread Michael Snoyman
Wow, I hadn't realized that someone had implemented resumable sinks... and
now resumable conduits too! Very interesting.

I'm not sure if I entirely understand your use case, but in general it
should be possible to have multiple Conduits running one after the other.
Here's an example of restarting an accumulator after every multiple of 5:

https://www.fpcomplete.com/user/snoyberg/random-code-snippets/multiple-conduits

Michael


On Mon, Mar 4, 2013 at 6:55 PM, Joey Adams joeyadams3.14...@gmail.comwrote:

 On Sun, Mar 3, 2013 at 10:24 PM, Joey Adams joeyadams3.14...@gmail.comwrote:

 ...

 Here's a possible API for a resumable Conduit:

 newtype ResumableConduit i m o = -- hidden --

 newResumableConduit :: Monad m = Conduit i m o - ResumableConduit i
 m o

 -- | Feed the 'Source' through the conduit, and send any output from
 the
 -- conduit to the 'Sink'.  When the 'Sink' returns, close the
 'Source', but
 -- leave the 'ResumableConduit' open so more data can be passed
 through it.
 runResumableConduit
 :: Monad m
 = ResumableConduit i m o
 - Source m i
 - Sink o m r
 - m (ResumableConduit i m o, r)
 ...


  While trying to implement this, I found a more elegant interface for
 resuming the ResumableConduit:

 -- | Fuse a 'ResumableConduit' to a 'Sink'.  When the 'Sink' returns,
 -- it returns the 'ResumableConduit' so the caller can reuse it.
 (=$++) :: Monad m

= ResumableConduit i m o
- Sink o m r
- Sink i m (ResumableConduit i m o, r)

 This takes advantage of Sink's return value to forward the
 ResumableConduit.  I don't think a ($=++) can be implemented.

 Advantages:

  * (=$++) is easier to implement than 'runResumableConduit' since it only
 has to fuse two pipes together instead of three.

  * Pretty syntax: (resumable', a) - source $$ resumable =$++ sink

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


Re: [Haskell-cafe] Simple way to do something like ArrowChoice.right on a Conduit? (version 1.0.0)

2013-03-05 Thread Michael Snoyman
On Wed, Mar 6, 2013 at 5:48 AM, Joey Adams joeyadams3.14...@gmail.comwrote:

 On Tue, Mar 5, 2013 at 9:24 AM, Michael Snoyman mich...@snoyman.comwrote:

 ...

 I'm not sure if I entirely understand your use case, but in general it
 should be possible to have multiple Conduits running one after the other.
 Here's an example of restarting an accumulator after every multiple of 5:


 https://www.fpcomplete.com/user/snoyberg/random-code-snippets/multiple-conduits


 Neat.  I didn't think to do that with plain Conduits.  I did realize I
 could use a resumable conduit as a temporary filter (basically what your
 example does).  This suggests that a resumable conduit can be used in any
 consumer (Conduit or Sink), not just a sink.  Perhaps it can even be used
 in a producer, though different operators would be needed (+$= instead of
 =$+).

 In my compression example, the incoming message sink needs to feed chunks
 of compressed data to a zlib conduit.  It can't just hand full control of
 the input to zlib; it has to decode messages, and only send CompressedData
 messages through zlib.  I need a resumable conduit for that.


I'm still not sure I follow this. In the example I linked to, the go
function within breaker could arbitrarily modify the data before it gets
passed on to the inner Conduit. So it seems like it should be possible to
achieve your goals this way. But I may just not fully understand your use
case.

Michael


 Here's my current implementation of resumable conduits [1].  I don't know
 much about conduit finalizers; I mostly followed 'connectResume' and
 'pipeL'.

 The main wrinkle is that when the ResumableConduit receives an upstream
 terminator, it forwards it to the sink, rather than telling the conduit
 that the stream ended.  This allows the conduit to be reused.  Only when we
 finish the ResumableConduit () do we send it the stream terminator.

 I'll continue toying with this.  It might be possible to factor out
 terminator forwarding, and generalize connectResume to support resumable
 sources, conduits, and sinks.

 Thanks for the help,
 -Joey

  [1]:
 https://github.com/joeyadams/hs-resumable-conduit/blob/master/ResumableConduit.hs

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


Re: [Haskell-cafe] Simple way to do something like ArrowChoice.right on a Conduit? (version 1.0.0)

2013-03-03 Thread Michael Snoyman
On Fri, Mar 1, 2013 at 4:18 AM, Joey Adams joeyadams3.14...@gmail.comwrote:

 Can I transform a conduit so some values are passed through unchanged, but
 others go through the conduit?  For example:

 right :: Conduit i m o - Conduit (Either x i) m (Either x o)

 This is named after the Control.Arrow combinator of the same name:

 right :: ArrowChoice a = a b c - a (Either d b) (Either d c)

 Here's my use case (simplified): I want to compress data with
 zlib-conduit, which provides:

 compress :: Conduit (Flush ByteString) m (Flush ByteString)

 The 
 Flushhttp://hackage.haskell.org/packages/archive/conduit/latest/doc/html/Data-Conduit.html#t:Flushwrapper
  lets me flush the compressor so it will yield cached data right
 away (though hurting compression a little).

 But before compressing the data, I want to encode it, using this conduit:

 encode :: Conduit Entry m ByteString

 I want to combine these, so that if I send a 'Flush', it bypasses 'encode'
 and feeds to 'compress':

 compressEncode :: Conduit (Flush Entry) m (Flush ByteString)

 Thus, I need a variant of 'encode' that passes 'Flush' along:

 encode' :: Conduit (Flush Entry) m (Flush ByteString)

 In my actual program, I don't use Flush, so providing a Conduit combinator
 just for Flush would not help me.

 Is something like 'right' possible to implement with Conduit's public
 API?  Here's an implementation using Data.Conduit.Internal (untested):

 import Control.Monad (liftM)
 import Data.Conduit.Internal (Pipe(..), ConduitM(..), Conduit)

 right :: Monad m = Conduit i m o - Conduit (Either x i) m (Either x
 o)
 right = ConduitM . rightPipe . unConduitM

 rightPipe :: Monad m
   = Pipe i i o () m ()
   - Pipe (Either x i) (Either x i) (Either x o) () m ()
 rightPipe p0 = case p0 of
 HaveOutput p c o  - HaveOutput (rightPipe p) c (Right o)
 NeedInput p c - NeedInput p' (rightPipe . c)
   where p' (Left x)  = HaveOutput (rightPipe p0) (return ()) (Left
 x)
 p' (Right i) = rightPipe $ p i
 Done r- Done r
 PipeM mp  - PipeM $ liftM rightPipe mp
 Leftover p i  - Leftover (rightPipe p) (Right i)


I'm fairly certain this cannot be implemented using only the public API.
Your implementation looks solid to me.


 I'm wondering if we could have a Data.Conduit.Arrow module, which provides
 a newtype variant of Conduit that implements Arrow, ArrowChoice, etc.:

 import qualified Data.Conduit as C

 newtype Conduit m i o = Conduit (C.Conduit i m o)

 -- May need Monad constraints for these
 instance Category (Conduit m)
 instance Arrow (Conduit m)
 instance ArrowChoice (Conduit m)


As I think you point out in your next email, Conduit can't really be an
instance of Arrow. IIRC, there was quite a bit of talk about that when
pipes came out, but some of the features of a Pipe (such as allowing input
and output to occur at different speeds) means that it can't be achieved.
Nonetheless, I think adding some helping combinators based around Arrows
for Conduit makes sense.


 Does 'Conduit' follow Category, Monad, MonadTrans laws* these days?  I'm
 not talking about Pipe in general, just the special case of it represented
 by the 'Conduit' type alias:

 Conduit i m o = ConduitM i o m () = Pipe i i o () m ()

 Or are there some thorny issues (e.g. leftovers) that make following these
 laws impossible in some cases?


It's easy to prove that a Conduit with leftovers does not follow the
Category laws:

id = awaitForever yield
(.) = (=$=)

id . leftover x /= leftover x

That was the motivation for adding the leftover type parameter to the Pipe
datatype: if you want to get closer to a Category instance (whatever
closer would mean here), you need to make sure that the leftover
parameter is set to Void. However, even in such a case, there's at least
one deviation from strict Category behavior. The order in which finalizers
are run does not fully respect the associative laws[1]. In this case, the
deviation is intentional: conduit is more concerned with ensuring strict
resource usage than associativity. I touched on this point briefly in a
recent conduit 1.0 blog post.

In my opinion, this is evidence that Category is not the right abstraction
to be used for streaming data, since it doesn't give us the ability to
guarantee prompt finalization.

[1] https://github.com/snoyberg/conduit/pull/57


  Thanks for the input,
 -Joey

  * Assume functions that use Data.Conduit.Internal do so correctly.

 ___
 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 Michael Snoyman
On Sun, Mar 3, 2013 at 6:07 PM, 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.


Perhaps there's a good reason why it's impossible to make such an instance.
Are you sure that your MonadCatchIO instance is well founded? What happens
if you use finally? Are you guaranteed that your cleanup function is called
once, and precisely once?

These are the problems I ran into with MonadCatchIO three years ago, almost
precisely. The main monad for Yesod was built around ContT, and I ended up
with double-free bugs. It's true that I had to move away from ContT in
order to get the desired semantics, but that has nothing to do with
MonadCatchIO vs monad-control. The former just made it seem like I had
working code when in fact I had a lurking bug.


 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.

 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've seen the criticisms of monad-control (or at least I believe I have).
What I've seen has been dubious at best. I'll fully agree that the
implementation is hard to follow, but it's designed for efficiency. The
underlying concept is simple: capture the current state and pipe it through
the underlying monad. If you needed to lift a control operation for the
ReaderT or StateT monads, you would likely end up with an almost exact
replica of what monad-control does for you.

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


Re: [Haskell-cafe] RFC: rewrite-with-location proposal

2013-02-26 Thread Michael Snoyman
On Tue, Feb 26, 2013 at 12:06 PM, Simon Peyton-Jones
simo...@microsoft.comwrote:

  Do you mean that the proposal itself won't work, or specifically
 implementing this features in terms of existing rewrite rules won't work?*
 ***

 ** **

 I meant the latter.

 ** **

 I'll admit to ignorance on the internals of GHC, but it seems like doing
 the shallow source location approach would be far simpler than a full
 trace. I'd hate to lose a very valuable feature because we can't implement
 the perfect feature.

 ** **

 I agree with that sentiment. But in fact I suspect that getting a stack is
 little or no harder than the shallow thing.

 ** **

 My “implicit parameter” suggestion was trying to re-use an existing
 feature, with a small twist, to do what you want, rather than to implement
 something brand new.


I personally have very little opinion about how this feature is
implemented. But would this approach implement the shallow trace, or the
full stack trace?

Michael


  

 Simon

 ** **

 *From:* michael.snoy...@gmail.com [mailto:michael.snoy...@gmail.com] *On
 Behalf Of *Michael Snoyman
 *Sent:* 25 February 2013 18:19
 *To:* Simon Peyton-Jones
 *Cc:* Alexander Kjeldaas; Simon Hengel; Haskell Cafe

 *Subject:* Re: [Haskell-cafe] RFC: rewrite-with-location proposal

  ** **

 ** **

 ** **

 On Mon, Feb 25, 2013 at 4:42 PM, Simon Peyton-Jones simo...@microsoft.com
 wrote:

 I’m afraid the rewrite-rule idea won’t work.  RULES are applied during
 optimisation, when tons of inlining has happened and the program has been
 shaken around a lot. No reliable source location information is available
 there.

  

 ** **

 Do you mean that the proposal itself won't work, or specifically
 implementing this features in terms of existing rewrite rules won't work?*
 ***

  

  See http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack; and
 please edit it.

  

  ** **

 One thing I'd disagree with on that page is point (3). While it's
 certainly nice to have a full stack trace, implementing just shallow call
 information is incredibly useful. For logging and test framework usages, it
 in fact completely covers the use case. And even for debugging, I think it
 would be a massive step in the right direction.

 ** **

 I'll admit to ignorance on the internals of GHC, but it seems like doing
 the shallow source location approach would be far simpler than a full
 trace. I'd hate to lose a very valuable feature because we can't implement
 the perfect feature.

  

  One idea I had, which that page does not yet describe, is to have an
 implicit parameter,
 something like ?loc::Location, with

   errLoc :: ?loc:Location = String - a

   errLoc s = error (“At “ ++ ?loc ++ “\n” ++ s)

  

 This behave exactly like an ordinary implicit parameter, EXCEPT that if
 there is no binding for ?loc::Location, then the current location is used.
 Thus

  

 myErr :: ?loc:Location = Int - a

 myErr n = errLoc (show n)

  

 foo :: Int - int

 foo n | n0 = myErr n

 | otherwise = ...whatever...

  

 When typechecking ‘foo’ we need ?loc:Location, and so the magic is that we
 use the location of the call of myErr in foo.

  

 Simon

  

  

  

 *From:* haskell-cafe-boun...@haskell.org [mailto:
 haskell-cafe-boun...@haskell.org] *On Behalf Of *Alexander Kjeldaas
 *Sent:* 25 February 2013 12:16
 *To:* Simon Hengel
 *Cc:* Haskell Cafe
 *Subject:* Re: [Haskell-cafe] RFC: rewrite-with-location proposal

  

 On Mon, Feb 25, 2013 at 12:46 PM, Simon Hengel s...@typeful.net wrote:***
 *

  On Mon, Feb 25, 2013 at 10:40:29AM +0100, Twan van Laarhoven wrote:
  I think there is no need to have a separate REWRITE_WITH_LOCATION
  rule. What if the compiler instead rewrites 'currentLocation' to the
  current location? Then you'd just define the rule:
 
  {-# REWRITE errorLoc error = errorLoc currentLocation #-}

 REWRITE rules are only enabled with -O.  Source locations are also
 useful during development (when you care more about compilation time
 than efficient code and hence use -O0).  So I'm not sure whether it's a
 good idea to lump those two things together.

   

 I could imagine that source locations being useful when debugging rewrite
 rules for example.

  

 I think your argument makes sense, but why not fix that specifically?

  

 {-# REWRITE ALWAYS errorLoc error = errorLoc currentLocation #-}

  

 Alexander

  


 ___
 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] RFC: rewrite-with-location proposal

2013-02-25 Thread Michael Snoyman
On Mon, Feb 25, 2013 at 11:13 AM, Simon Hengel s...@typeful.net wrote:

 On Mon, Feb 25, 2013 at 09:57:04AM +0100, Joachim Breitner wrote:
  Hi,
 
  Am Montag, den 25.02.2013, 08:06 +0200 schrieb Michael Snoyman:
   Quite a while back, Simon Hengel and I put together a proposal[1] for
   a new feature in GHC. The basic idea is pretty simple: provide a new
   pragma that could be used like so:
  
   error :: String - a
   errorLoc :: IO Location - String - a
   {-# REWRITE_WITH_LOCATION error errorLoc #-}
 
  in light of attempts to split base into a pure part (without IO) and
  another part, I wonder if the IO wrapping is really necessary.
 
  Can you elaborate the reason why a simple Location - is not enough?

 The IO helps with reasoning.  Without it you could write code that does
 something different depending on the call site.  Here is an example:


 someBogusThingy :: Int
 someBogusThingy = ..

 someBogusThingyLoc :: Location - Int
 someBogusThingyLoc loc
   | (even . getLine) loc = 23
   | otherwise= someBogusThingyLoc

 {-# REWRITE_WITH_LOCATION someBogusThingy someBogusThingyLoc #-}

 Now someBogusThingy behaves different depending on whether the call site
 is on an even or uneven line number.  Admittedly, the example is
 contrived, but I hope it illustrates the issue.

 I do not insist on keeping it.  If we, as a community, decide, that we
 do not need the IO here.  Then I'm fine with dropping it.


And FWIW, my vote *does* go towards dropping it. I put this proposal in the
same category as rewrite rules in general: it's certainly possible for a
bad implementation to wreak havoc, but it's the responsibility of the
person using the rewrite rules to ensure that doesn't happen.

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


Re: [Haskell-cafe] RFC: rewrite-with-location proposal

2013-02-25 Thread Michael Snoyman
On Mon, Feb 25, 2013 at 2:15 PM, Alexander Kjeldaas 
alexander.kjeld...@gmail.com wrote:

 On Mon, Feb 25, 2013 at 12:46 PM, Simon Hengel s...@typeful.net wrote:

 On Mon, Feb 25, 2013 at 10:40:29AM +0100, Twan van Laarhoven wrote:
  I think there is no need to have a separate REWRITE_WITH_LOCATION
  rule. What if the compiler instead rewrites 'currentLocation' to the
  current location? Then you'd just define the rule:
 
  {-# REWRITE errorLoc error = errorLoc currentLocation #-}

 REWRITE rules are only enabled with -O.  Source locations are also
 useful during development (when you care more about compilation time
 than efficient code and hence use -O0).  So I'm not sure whether it's a
 good idea to lump those two things together.


 I could imagine that source locations being useful when debugging rewrite
 rules for example.

 I think your argument makes sense, but why not fix that specifically?

 {-# REWRITE ALWAYS errorLoc error = errorLoc currentLocation #-}



At that point, we've now made two changes to REWRITE rules:

1. They can takes a new ALWAYS parameters.
2. There's a new, special identifier currentLocation available.

What would be the advantage is of that approach versus introducing a single
new REWRITE_WITH_LOCATION pragma?

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


Re: [Haskell-cafe] RFC: rewrite-with-location proposal

2013-02-25 Thread Michael Snoyman
On Mon, Feb 25, 2013 at 4:42 PM, Simon Peyton-Jones
simo...@microsoft.comwrote:

  I’m afraid the rewrite-rule idea won’t work.  RULES are applied during
 optimisation, when tons of inlining has happened and the program has been
 shaken around a lot. No reliable source location information is available
 there.

 **


Do you mean that the proposal itself won't work, or specifically
implementing this features in terms of existing rewrite rules won't work?


 **

 See http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack; and
 please edit it.

 **


One thing I'd disagree with on that page is point (3). While it's certainly
nice to have a full stack trace, implementing just shallow call information
is incredibly useful. For logging and test framework usages, it in fact
completely covers the use case. And even for debugging, I think it would be
a massive step in the right direction.

I'll admit to ignorance on the internals of GHC, but it seems like doing
the shallow source location approach would be far simpler than a full
trace. I'd hate to lose a very valuable feature because we can't implement
the perfect feature.


 **

 One idea I had, which that page does not yet describe, is to have an
 implicit parameter,
 something like ?loc::Location, with

   errLoc :: ?loc:Location = String - a

   errLoc s = error (“At “ ++ ?loc ++ “\n” ++ s)

 ** **

 This behave exactly like an ordinary implicit parameter, EXCEPT that if
 there is no binding for ?loc::Location, then the current location is used.
 Thus

 ** **

 myErr :: ?loc:Location = Int - a

 myErr n = errLoc (show n)

 ** **

 foo :: Int - int

 foo n | n0 = myErr n

 | otherwise = ...whatever...

 ** **

 When typechecking ‘foo’ we need ?loc:Location, and so the magic is that we
 use the location of the call of myErr in foo.

 ** **

 Simon

 ** **

 ** **

 ** **

 *From:* haskell-cafe-boun...@haskell.org [mailto:
 haskell-cafe-boun...@haskell.org] *On Behalf Of *Alexander Kjeldaas
 *Sent:* 25 February 2013 12:16
 *To:* Simon Hengel
 *Cc:* Haskell Cafe
 *Subject:* Re: [Haskell-cafe] RFC: rewrite-with-location proposal

 ** **

 On Mon, Feb 25, 2013 at 12:46 PM, Simon Hengel s...@typeful.net wrote:***
 *

  On Mon, Feb 25, 2013 at 10:40:29AM +0100, Twan van Laarhoven wrote:
  I think there is no need to have a separate REWRITE_WITH_LOCATION
  rule. What if the compiler instead rewrites 'currentLocation' to the
  current location? Then you'd just define the rule:
 
  {-# REWRITE errorLoc error = errorLoc currentLocation #-}

 REWRITE rules are only enabled with -O.  Source locations are also
 useful during development (when you care more about compilation time
 than efficient code and hence use -O0).  So I'm not sure whether it's a
 good idea to lump those two things together.

  ** **

 I could imagine that source locations being useful when debugging rewrite
 rules for example.

 ** **

 I think your argument makes sense, but why not fix that specifically?

 ** **

 {-# REWRITE ALWAYS errorLoc error = errorLoc currentLocation #-}

 ** **

 Alexander

 ** **

 ___
 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] RFC: rewrite-with-location proposal

2013-02-24 Thread Michael Snoyman
Quite a while back, Simon Hengel and I put together a proposal[1] for a new
feature in GHC. The basic idea is pretty simple: provide a new pragma that
could be used like so:

error :: String - a
errorLoc :: IO Location - String - a
{-# REWRITE_WITH_LOCATION error errorLoc #-}

Then all usages of `error` would be converted into calls to `errorLoc` by
the compiler, passing in the location information of where the call
originated from. Our three intended use cases are:

* Locations for failing test cases in a test framework
* Locations for log messages
* assert/error/undefined

Note that the current behavior of the assert function[2] already includes
this kind of approach, but it is a special case hard-coded into the
compiler. This proposal essentially generalizes that behavior and makes it
available for all functions, whether included with GHC or user-defined.

The proposal spells out some details of this approach, and contrasts with
other methods being used today for the same purpose, such as TH and CPP.

Michael

[1] https://github.com/sol/rewrite-with-location
[2]
http://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Control-Exception.html#v:assert
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: hackage-proxy 0.1.0.0

2013-02-17 Thread Michael Snoyman
I'd like to announce the first release of a new tool called hackage-proxy.
The purpose is to provide a local proxy for a Hackage server, which somehow
modifies files in transport. The motivating case for this was getting more
meaningful error output from Stackage when compiling against GHC HEAD. When
compiling against actual Hackage, cabal will simply refuse to try to build
packages which have upper version bounds such as base  4.7. This
introduces a big dilemma:

* Package authors do not want to bump the version bounds on their packages
until they've tested against that version.

* It's very difficult to do meaningful tests of GHC until packages on
Hackage have been updated.

Hopefully this package can help resolve the dilemma. Instead of requiring
authors to upload new versions of their packages in order to test them,
this proxy will modify the cabal files it downloads and strip off the
version bounds of specified packages. Then, you can test with a newer
version of GHC and find actual compilation errors instead of version bound
constraints.

## Example Usage

1. cabal install hackage-proxy

2. Run hackage-proxy. By default, it will use the official Hackage server
as the source, drop bounds on the packages base, process, directory,
template-haskell, and Cabal, and serve from port 4200. All of this can be
modified via command-line options.

3. Edit your ~/.cabal/config file. Comment out the
hackage.haskell.orglines, and add in something like the following:

remote-repo: hackage-proxy:http://localhost:4200

4. cabal update

5. cabal install your-package-list-here

I think this can be a very valuable tool for anyone wanting to test out
newer versions of GHC. In addition, as part of my normal Stackage work, I'm
now collecting fairly detailed error logs of a number of packages. If this
would be useful for the GHC team or anyone else, let me know and I can try
and provide the logs somehow.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] xml conduit

2013-02-11 Thread Michael Snoyman
OK, after some experimentation, I've decided that this would be something
really cool, but I don't have the experience with lens to do it myself.
Here's what I came up with so far:

https://gist.github.com/snoyberg/4755679

(Also available on School of Haskell[1], but our version of lens is too old
for this snippet.)

So if someone wants to pursue this, I'd be really interested to see the
results.

Michael

[1]
https://haskell.fpcomplete.com/user/snoyberg/random-code-snippets/xml-conduit-lens


On Mon, Feb 11, 2013 at 8:09 AM, Michael Sloan mgsl...@gmail.com wrote:

 I realized that the term payload wouldn't make much sense in the context
 of XML.  What I meant was elementName with elementAttributes (but not
 elementNodes - that's the point).  So, such navigations could yield a
 datatype containing those.

 -Michael


 On Sun, Feb 10, 2013 at 9:41 PM, Michael Sloan mgsl...@gmail.com wrote:

 Err:  That first link into Zipper.hs should instead be:


 https://github.com/ekmett/lens/blob/f8dfe3fd444648f61b8594cd672c25e70c8a30ff/src/Control/Lens/Internal/Zipper.hs#L66


 On Sun, Feb 10, 2013 at 9:40 PM, Michael Sloan mgsl...@gmail.com wrote:

 I'm no lens authority by any means, but indeed, it looks like something
 like Cursor / Axis could be done with the lens zipper.


 https://github.com/snoyberg/xml/blob/0367af336e86d723bd9c9fbb49db0f86d1f989e6/xml-enumerator/Text/XML/Cursor/Generic.hs#L38

 This cursor datatype is very much like the (:) zipper type (I'm linking
 to old code, because that's when I understood it - the newer stuff is
 semantically the same, but more efficient, more confusing, and less
 directly relatable):


 https://github.com/ekmett/lens/blob/f8dfe3fd444648f61b8594cd672c25e70c8a30ff/src/Control/Lens/Internal/Zipper.hs#L317

 Which is built out of the following two datatypes:

 1) parent (and the way to rebuild the tree on the way back up) is
 provided by this datatype:


 https://github.com/ekmett/lens/blob/f8dfe3fd444648f61b8594cd672c25e70c8a30ff/src/Control/Lens/Internal/Zipper.hs#L74

 2) precedingSibling / followingSibling / node is provided by this
 datatype (which is pretty much the familiar list zipper!):


 https://github.com/ekmett/lens/blob/f8dfe3fd444648f61b8594cd672c25e70c8a30ff/src/Control/Lens/Internal/Zipper.hs#L317


 One way that this would be powerful is that some of the Axis
 constructors could return a zipper.  In particular, all of the axis
 yielding functions except the following would be supported:

 parent, precedingSibling, followingSibling, ancestor, descendent,
 orSelf, check

 This is because zippers can be used for modification, which doesn't work
 out very well when you can navigate to something outside of your focii's
 children.  If we have a new datatype, that represents a node's payload,
 then we could conceivably represent all of the axis yielding operations
 except for parent / ancestor.  However, those operations would be
 navigations to payloads - further xml-hierarchy level navigation would be
 impossible because you'd no longer have references to children.  (further
 navigation into payloads on the other hand, would still be possible)

 So, that's just my thoughts after looking at it a bit - I hope it's
 comprehensible / helpful!  An XML zipper would be pretty awesome.

 -Michael


 On Sun, Feb 10, 2013 at 8:34 PM, Michael Snoyman mich...@snoyman.comwrote:




 On Sun, Feb 10, 2013 at 8:51 PM, grant the...@hotmail.com wrote:

 Michael Snoyman michael at snoyman.com writes:

 

 Hi Michael,

 Just one last thought. Does it make any sense that xml-conduit could be
 rewritten as a lens instead of a cursor? Or leverage the lens package
 somehow?


 That's a really interesting idea, I'd never thought about it before.
 It's definitely something worth playing around with. However, I think in
 this case the Cursor is providing a totally different piece of
 functionality than what lenses would do. The Cursor is really working as a
 Zipper, allowing you to walk the node tree and do queries about preceding
 and following siblings and ancestors.

 Now given that every time I'm on #haskell someone mentions zippers in
 the context of lens, maybe lens *would* solve this use case as well, but
 I'm still a lens novice (if that), so I can't really speak on the matter.
 Maybe someone with more lens experience could provide some insight.

 Either way, some kind of lens add-on sounds really useful.

 Michael

 ___
 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] xml conduit

2013-02-10 Thread Michael Snoyman
On Sun, Feb 10, 2013 at 8:51 PM, grant the...@hotmail.com wrote:

 Michael Snoyman michael at snoyman.com writes:

 

 Hi Michael,

 Just one last thought. Does it make any sense that xml-conduit could be
 rewritten as a lens instead of a cursor? Or leverage the lens package
 somehow?


That's a really interesting idea, I'd never thought about it before. It's
definitely something worth playing around with. However, I think in this
case the Cursor is providing a totally different piece of functionality
than what lenses would do. The Cursor is really working as a Zipper,
allowing you to walk the node tree and do queries about preceding and
following siblings and ancestors.

Now given that every time I'm on #haskell someone mentions zippers in the
context of lens, maybe lens *would* solve this use case as well, but I'm
still a lens novice (if that), so I can't really speak on the matter. Maybe
someone with more lens experience could provide some insight.

Either way, some kind of lens add-on sounds really useful.

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


Re: [Haskell-cafe] xml conduit

2013-02-09 Thread Michael Snoyman
Hi Grant,

As you might expect from immutable data structures, there's no way to
update in place. The approach you'd take to XSLT: traverse the tree, check
each node, and output a new structure. I put together the following as an
example, but I could certainly imagine adding more combinators to the
Cursor module to make something like this more convenient.

{-# LANGUAGE OverloadedStrings #-}
import Prelude hiding (readFile, writeFile)
import Text.XML
import Text.XML.Cursor

main = do
doc@(Document pro (Element name attrs _) epi) - readFile def test.xml
let nodes = fromDocument doc $/ update
writeFile def output.xml $ Document pro (Element name attrs nodes) epi
  where
update c =
case node c of
NodeElement (Element f attrs _)
| parentIsE c  gparentIsD c -
[ NodeElement $ Element f attrs
[ NodeContent New content
]
]
NodeElement (Element name attrs _) -
[NodeElement $ Element name attrs $ c $/ update]
n - [n]
parentIsE c = not $ null $ parent c = element e
gparentIsD c = not $ null $ parent c = parent = element d

Michael


On Sat, Feb 9, 2013 at 1:31 AM, grant the...@hotmail.com wrote:

 Hi,

 Is there a nice way to update xml. I want to be able to use xml-conduit
 to find a location in the xml and then add/update that node.

 eg xpath from //d/e/f and then change the content at 'f' or add a new node

 a
 ...
   d
 e
   fsome data to change
   /f
 /e
   /d
 ...
 /a


 Thanks for any help,
 Grant


 ___
 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] Yet another Conduit question

2013-02-04 Thread Michael Snoyman
I think this is probably the right approach. However, there's something
important to point out: flushing based on timing issues must be handled
*outside* of the conduit functionality, since by design conduit will not
allow you to (for example) run `await` for up to a certain amount of time.
You'll probably need to do this outside of your conduit chain, in the
initial Source. It might look something like this:

yourSource = do
mx - timeout somePeriod myAction
yield $ maybe Flush Chunk mx
yourSource


On Sun, Feb 3, 2013 at 5:06 PM, Felipe Almeida Lessa felipe.le...@gmail.com
 wrote:

 I guess you could use the Flush datatype [1] depending on how your
 data is generated.

 Cheers,

 [1]
 http://hackage.haskell.org/packages/archive/conduit/0.5.4.1/doc/html/Data-Conduit.html#t:Flush

 On Fri, Feb 1, 2013 at 6:28 AM, Simon Marechal si...@banquise.net wrote:
  On 01/02/2013 08:21, Michael Snoyman wrote:
  So you're saying you want to keep the same grouping that you had
  originally? Or do you want to batch up a certain number of results?
  There are lots of ways of approaching this problem, and the types don't
  imply nearly enough to determine what you're hoping to achieve here.
 
  Sorry for not being clear. I would like to group them as much as
  possible, that is up to a certain limit, and also within a time
  threshold. I believe that the conduit code will be called only when
  something happens in the conduit, so an actual timer would be useless
  (unless I handle this at the source perhaps, and propagate ticks).
 
  That is why in my first message I talked about stacking things into the
  list until the conduit has no more input available, or a maximum size is
  reached, but was not sure this even made sense.
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe



 --
 Felipe.

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


Re: [Haskell-cafe] Yet another Conduit question

2013-02-04 Thread Michael Snoyman
On Mon, Feb 4, 2013 at 3:47 PM, Simon Marechal si...@banquise.net wrote:

 On 03/02/2013 16:06, Felipe Almeida Lessa wrote:
  I guess you could use the Flush datatype [1] depending on how your
  data is generated.

 Thank you for this suggestion. I tried to do exactly this by modifying
 my bulk Redis source so that it can timeout and send empty lists [1].
 Then I wrote a few helpers conduits[2], such as :

 concatFlush :: (Monad m) = Integer - Conduit [a] m (Flush a)

 which will convert a stream of [a] into a stream of (Flush a), sending
 Flush whenever it encounters and empty list or it send a tunable amount
 of data downstream.

 I finally modified my examples [3]. I realized then it would be nice to
 have fmap for conduits (but I am not sure how to write such a type
 signature). Suggestions are welcome !


Actually `fmap` already exists on the Pipe datatype, it just probably
doesn't do what you want. It modifies the return value, which is only
relevant for Sinks.

What you probably are looking for is mapOutput[1].

Michael

[1] https://haskell.fpcomplete.com/hoogle?q=mapOutput



 [1]

 https://github.com/bartavelle/hslogstash/commit/663bf8f5e6058b476c9ed9b5c9cf087221b79b36
 [2]
 https://github.com/bartavelle/hslogstash/blob/master/Data/Conduit/Misc.hs
 [3]

 https://github.com/bartavelle/hslogstash/blob/master/examples/RedisToElasticsearch.hs

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


Re: [Haskell-cafe] Yet another Conduit question

2013-02-04 Thread Michael Snoyman
Hmm, that's an interesting trick. I can't say that I ever thought bracketP
would be used in that way. The only change I might recommend is using
addCleanup[1] instead, which doesn't introduce the MonadResource constraint.

Michael

[1]
http://haddocks.fpcomplete.com/fp/7.4.2/2012-12-11/conduit/Data-Conduit-Internal.html#v:addCleanup


On Mon, Feb 4, 2013 at 4:37 PM, Kevin Quick qu...@sparq.org wrote:

 While on the subject of conduits and timing, I'm using the following
 conduit to add elapsed timing information:

 timedConduit :: MonadResource m = forall l o u . Pipe l o o u m (u,
 NominalDiffTime)
 timedConduit = bracketP getCurrentTime (\_ - return ()) inner
 where inner st = do r - awaitE
 case r of
   Right x - yield x  inner st
   Left  r - deltaTime st = \t - return (r,t)
   deltaTime st = liftIO $ flip diffUTCTime st $ getCurrentTime

 I'm aware that this is primarily timing the downstream (and ultimately the
 Sink) more than the upstream, and I'm using the bracketP to attempt to
 delay the acquisition of the initial time (st) until the first downstream
 request for data.

 I would appreciate any other insights regarding concerns, issues, or
 oddities that I might encounter with the above.

 Thanks,
   Kevin


 On Mon, 04 Feb 2013 02:25:11 -0700, Michael Snoyman mich...@snoyman.com
 wrote:

  I think this is probably the right approach. However, there's something
 important to point out: flushing based on timing issues must be handled
 *outside* of the conduit functionality, since by design conduit will not
 allow you to (for example) run `await` for up to a certain amount of time.
 You'll probably need to do this outside of your conduit chain, in the
 initial Source. It might look something like this:

 yourSource = do
 mx - timeout somePeriod myAction
 yield $ maybe Flush Chunk mx
 yourSource


 On Sun, Feb 3, 2013 at 5:06 PM, Felipe Almeida Lessa 
 felipe.le...@gmail.com

 wrote:


  I guess you could use the Flush datatype [1] depending on how your
 data is generated.

 Cheers,

 [1]
 http://hackage.haskell.org/**packages/archive/conduit/0.5.**
 4.1/doc/html/Data-Conduit.**html#t:Flushhttp://hackage.haskell.org/packages/archive/conduit/0.5.4.1/doc/html/Data-Conduit.html#t:Flush

 On Fri, Feb 1, 2013 at 6:28 AM, Simon Marechal si...@banquise.net
 wrote:
  On 01/02/2013 08:21, Michael Snoyman wrote:
  So you're saying you want to keep the same grouping that you had
  originally? Or do you want to batch up a certain number of results?
  There are lots of ways of approaching this problem, and the types
 don't
  imply nearly enough to determine what you're hoping to achieve here.
 
  Sorry for not being clear. I would like to group them as much as
  possible, that is up to a certain limit, and also within a time
  threshold. I believe that the conduit code will be called only when
  something happens in the conduit, so an actual timer would be useless
  (unless I handle this at the source perhaps, and propagate ticks).
 
  That is why in my first message I talked about stacking things into the
  list until the conduit has no more input available, or a maximum size
 is
  reached, but was not sure this even made sense.
 
  __**_
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe



 --
 Felipe.



 --
 -KQ


 __**_
 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] branching conduits

2013-01-31 Thread Michael Snoyman
On Thu, Jan 31, 2013 at 11:48 AM, Simon Marechal si...@banquise.net wrote:

 Hello,

 I have found the Conduit abstraction to be very well suited to a
 set of
 problems I am facing. I am however wondering how to implement
 branching conduits, and even conduit pools.

 I am currently in the process of rewriting parts (the simple
 parts) of
 the Logstash tool. There is a sample program that I use here:


 https://github.com/bartavelle/hslogstash/blob/deprecateUtils/examples/RedisToElasticsearch.hs

 As it can be seen, it uses a Redis source, a conduit that
 decodes the
 JSON ByteString into a LogstashMessage, a conduit that stores it into
 Elasticsearch and outputs the result of that action as an Either, and
 finally a sink that prints the errors.

 My problem is that I would like more complex behaviour. For
 example, I
 would like to route messages to another server instead of putting them
 into Elasticsearch when the LogstashMessage has some tag set. But this
 is just an example, and it is probable I will want much more complex
 behavior soon.

 I am not sure how to proceed from here, but have the following
 ideas:

  * investigate how the Conduits are made internally to see if I can
 create a operator similar to $$, but that would have a signature like:
 Source m (Either a b) - Sink a m r - Sink b m r
 and would do the branching in a binary fashion. I am not sure this is
 even possible.

  * create a mvars connectors constructor, which might have a signature
 like this:

  Int -- ^ branch count
  (LogstashMessage - Int) -- ^ branching function
  (Sink LogstashMessage m (), [Source m LogstashMessage])
  -- ^ a suitable sink, several sources for the other conduits

  it would internally create a MVar (Maybe LogstashMessage) for each
 branch, and put putMVar accordingly to the branching function. When the
 Conduit is destroyed, it will putMVar Nothing in all MVars.
  the sources would takeMVar, check if it is Nothing, or just proceed as
 expected.

  The MVar should guarantee the constant space property, but there is the
 risk of inter branch blocking when one of the branches is significantly
 slower than the others. It doesn't really matter to me anyway. And all
 the branch Sinks would have to have some synchronization mechanism so
 that the main thread waits for them (as they are going to be launched by
 a forkIO).



   This is the simplest scheme I have thought of, and it is probably not
 a very good one. I am very interested in suggestions here.

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



Hi Simon,

For your first approach, I think what you're looking to do is combine two
Sinks together, something like:

combine :: Monad m
= Sink i1 m r1
- Sink i2 m r2
- Sink (Either i1 i2) m (r1, r2)

Then you'd be able to use the standard $$ and =$ operators on it. I've put
up an example implementation here[1]. The majority of the code is simple
pattern matching on the different possible combination, but some things to
point out:

* To simplify, we start off with a call to injectLeftovers. This means that
we can entirely ignore the Leftover constructor in the main function.
* Since a Sink will never yield values, we can also ignore the HaveOutput
constructor.
* As soon as either of the Sinks terminates, we terminate the other one as
well and return the results.

You can also consider going the mutable container route if you like.
Instead of creating a lot of stuff from scratch with MVars, you could use
stm-conduit[2]. In fact, that package already contains some kind of merging
behavior for sources, it might make sense to ask the author about including
unmerging behavior for Sinks.

Michael

[1] https://gist.github.com/4682609
[2] http://hackage.haskell.org/package/stm-conduit
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Yet another Conduit question

2013-01-31 Thread Michael Snoyman
Firstly, what's the use case that you want to deal with lists? If it's for
efficiency, you'd probably be better off using a Vector instead.

But I think the inverse of `concat` is `singleton = Data.Conduit.List.map
return`, or `awaitForever $ yield . return`, using the list instance for
Monad. Your conduitMap could be implemented then as:

conduitMap conduit = concat =$= conduit =$= singleton

Michael


On Thu, Jan 31, 2013 at 5:12 PM, Simon Marechal si...@banquise.net wrote:

 I am working with bulk sources and sinks, that is with a type like:

 Source m [a]
 Sink [a] m ()

 The problem is that I would like to work on individual values in my
 conduit. I can have this:

 concat :: (Monad m) = Conduit [a] m a
 concat = awaitForever (mapM_ yield)

 But how can I do it the other way around ? I suppose it involves pattern
 matching on the different states my conduit might me in. But is that
 even possible to do it in a non blocking way, that is catenate data
 while there is something to read (up to a certain threshold), and send
 it as soon as there is nothing left to read ? Or doesn't that make any
 sense in the context of Conduits (in the sense that this conduit will be
 recheck for input before the upstream conduits will have a chance to
 operate) ?

 Another approach would be to have a map equivalent:

 conduitMap :: Conduit i m o - Conduit [i] m [o]

 But I am not sure how to do this either ...

 ___
 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] Yet another Conduit question

2013-01-31 Thread Michael Snoyman
On Fri, Feb 1, 2013 at 8:42 AM, Simon Marechal si...@banquise.net wrote:

 On 02/01/2013 05:21 AM, Michael Snoyman wrote:
  Firstly, what's the use case that you want to deal with lists? If it's
  for efficiency, you'd probably be better off using a Vector instead.

 That is a good point, and I wanted to go that way, but was not sure it
 would help me a lot here. My use case is for services where there is a
 bulk  API, such as Redis pipelining or Elasticsearch bulk inserts. The
 network round-trip gains would exceed by far those from a List to Vector
 conversion.

  But I think the inverse of `concat` is `singleton =
  Data.Conduit.List.map return`, or `awaitForever $ yield . return`, using
  the list instance for Monad. Your conduitMap could be implemented then
 as:
 
  conduitMap conduit = concat =$= conduit =$= singleton

 I can see how to do singleton, but that would gain me ... singletons.
 That means I could not exploit a bulk API.

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



So you're saying you want to keep the same grouping that you had
originally? Or do you want to batch up a certain number of results? There
are lots of ways of approaching this problem, and the types don't imply
nearly enough to determine what you're hoping to achieve here.

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


Re: [Haskell-cafe] How to store Fixed data type in the database with persistent ?

2013-01-27 Thread Michael Snoyman
On Jan 27, 2013 8:46 AM, alexander.vershi...@gmail.com wrote:

 Sat, Jan 26, 2013 at 12:21:02PM +0600, s9gf4...@gmail.com wrote
   According to the documentation, SQLite stores whatever you give it,
   paying very little heed to the declared type.  If you get SQLite to
   *compare* two numbers, it will at that point *convert* them to doubles
   in order to carry out the comparison.  This is quite separate from the
   question of what it can store.
 
  CREATE TABLE t1(val);
  sqlite insert into t1 values ('24.24242424')
 ... ;
  sqlite insert into t1 values ('24.24242423')
 ... ;
  sqlite select * from t1 order by val;
  24.24242423
  24.24242424
  sqlite select * from t1 order by val desc;
  24.24242424
  24.24242423
  sqlite select sum(val) from t1;
  48.48484847
 
  it seems Sqlite can work with arbitrary percission data, very good !
  Persistent must have ability to store Fixed.
 

 It's not correct. SQLlite stores any value, but it will use arithmetic
 operations only with double presicion:

 sqlite select val from t1;
 1
 0.01
 0.0001
 0.01
 0.0001
 0.01
 0.0001
 0.01
 0.0001
 0.01

 sqlite select sum(val) from t1;
 1.0101010101

 as you see it has 14 degree.

 Let's check another well known floating point problem:

 sqlilte create table t2 ('val')
 sqlite insert into t2 values ('0.7');
 sqlite update t2 set val = 11*val-7;

 t2 should remain a const
 sqlite update t2 set val = 11*val-7; -- 4 times
 sqlite select val from t2;
 0.6989597
 sqlite update t2 set val = 11*val-7; -- 10 times mote
 sqlite select val from t2;
 0.430171514341321

 As you see you have errors. So SQLlite doesn't support arbitrary
 presision values.

 As for me Persistent should at least support a Money type and use
 correct backend-specific type for them, either a native for big integer.

Let me clarify a bit:

1. Persistent will currently allow you to create a `Money` datatype which
internally stores as an integer.

2. What Persistent currently lacks is a PersistValue constructor for
arbitrary-precision values. As a result, during marshaling, some data will
be lost when converting from NUMERIC to Double.

3. The upcoming change we're discussing for Persistent would just be to add
such a constructor. We could theoretically provide some extra PersistField
instances as well, but that's not really what's being discussed.

HTH,

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


Re: [Haskell-cafe] How to store Fixed data type in the database with persistent ?

2013-01-26 Thread Michael Snoyman
Very nice to see, I'm happy to stand corrected here. We'll definitely get
some support for fixed into the next major release.

On Saturday, January 26, 2013, wrote:

  According to the documentation, SQLite stores whatever you give it,
  paying very little heed to the declared type.  If you get SQLite to
  *compare* two numbers, it will at that point *convert* them to doubles
  in order to carry out the comparison.  This is quite separate from the
  question of what it can store.

 CREATE TABLE t1(val);
 sqlite insert into t1 values ('24.24242424')
... ;
 sqlite insert into t1 values ('24.24242423')
... ;
 sqlite select * from t1 order by val;
 24.24242423
 24.24242424
 sqlite select * from t1 order by val desc;
 24.24242424
 24.24242423
 sqlite select sum(val) from t1;
 48.48484847

 it seems Sqlite can work with arbitrary percission data, very good !
 Persistent must have ability to store Fixed.

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

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


Re: [Haskell-cafe] How to store Fixed data type in the database with persistent ?

2013-01-25 Thread Michael Snoyman
I can point you to the line of code causing you trouble[1].

The problem is, as you already pointed out, that we don't have a
PersistValue constructor that fits this case correctly. I think the right
solution is to go ahead and add such a constructor for the next release.
I've opened a ticket on Github[2] to track this.

By the way, not all databases supported by Persistent have the ability to
represent NUMERIC with perfect precision. I'm fairly certain the SQLite
will just cast to 8-byte reals, though it's possible that it will keep the
data as strings in some circumstances.

In the short term, you can probably get this to work today by turning your
Fixed values into Integers (by multiplying by some power of 10) to
marshaling to the database, and do the reverse when coming from the
database. I haven't used this technique myself, but I think it should work.

Michael

[1]
https://github.com/yesodweb/persistent/blob/master/persistent-postgresql/Database/Persist/Postgresql.hs#L271
[2] https://github.com/yesodweb/yesod/issues/493


On Fri, Jan 25, 2013 at 8:19 AM, s9gf4...@gmail.com wrote:

 **

 All modern databases has field type NUMERIC(x, y) with arbitrary precision.



 I need to store financial data with absolute accuracy, and I decided to
 use Fixed.

 How can I store Fixed data type as NUMERIC ? I decided to use Snoyman's
 persistent, bit persistent can not use it from the box and there is a
 problem with custom field declaration.



 Here is the instance of PersistField for Fixed I wrote



 instance (HasResolution a) = PersistField (Fixed a) where

 toPersistValue a = PersistText $ T.pack $ show a

 -- fromPersistValue (PersistDouble d) = Right $ fromRational $ toRational d

 fromPersistValue (PersistText d) = case reads dpt of

 [(a, )] - Right a

 _ - Left $ T.pack $ Could not read value  ++ dpt ++  as fixed value

 where dpt = T.unpack d



 fromPersistValue a = Left $ T.append Unexpected data value can not be
 converted to Fixed:  $ T.pack $ show a



 sqlType a = SqlOther $ T.pack $ NUMERIC( ++ (show l) ++ , ++ (show p)
 ++ )

 where

 p = round $ (log $ fromIntegral $ resolution a) / (log 10)

 l = p + 15 -- FIXME: this is maybe not very good

 isNullable _ = False



 I did not found any proper PersistValue to convert into Fixed from. As
 well as converting Fixed to PersistValue is just a converting to string.
 Anyway the saving works properly, but thre reading does not - it just reads
 Doubles with rounding error.



 If you uncomment the commented string in instance you will see, that
 accuracy is not absolute.



 Here is test project to demonstrate the problem.



 https://github.com/s9gf4ult/xres



 If you launch main you will see that precission is not very good because
 of converting database value to Double and then converting to Fixed.



 How can i solve this with persistent or what other framework works well
 with NUMERIC database field type ?



 ___
 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] Stackage mailing list

2013-01-19 Thread Michael Snoyman
I've now created a Stackage mailing list:

https://groups.google.com/d/forum/stackage

I encourage anyone who's interested to join the list.


On Sat, Dec 22, 2012 at 11:50 AM, Joachim Breitner m...@joachim-breitner.de
 wrote:

 Dear Michael,

 I’m wondering if I missed something, but is there a mailing list for
 stackage? Or has one of the standard lists (-cafe, libraries) been
 designated for questions about stackage?


 What I want to know is if you plan to provide a website for stackage
 soon where the list of included packages and their dependencies,
 including the tested and approved version numbers can be seen. I’d like
 to take that and integrate it on
 http://people.debian.org/~nomeata/platform.html
 and
 http://people.debian.org/~nomeata/hackagevsdebian.html

 Also, once you do that, it should be possible to add Stackage to the
 list of Distributions listed on hackage, so that on hackage one already
 sees the package’s stackage status and whether it lags behind there. The
 integrations is rather simple, just provide a file with that format:
 http://people.debian.org/~nomeata/cabalDebianMap.txt
 and bug the hackage maintainers to add it.

 Greetings,
 Joachim

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


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


Re: [Haskell-cafe] Safe 'chr' function?

2013-01-03 Thread Michael Snoyman
You could wrap chr with a call to spoon[1]. It's not the most elegant
solution, but it works.

[1]
http://hackage.haskell.org/packages/archive/spoon/0.3/doc/html/Control-Spoon.html#v:spoon


On Thu, Jan 3, 2013 at 9:50 AM, Myles C. Maxfield
myles.maxfi...@gmail.comwrote:

 Hello,
 I'm working on a general text-processing library [1] and one of my
 quickcheck tests is designed to make sure that my library doesn't throw
 exceptions (it returns an Either type on failure). However, there are some
 inputs that cause me to pass bogus values to the 'chr' function (such
 as 1208914), which causes it to throw an exception. Is there a version of
 that function that is safe? (I'm hoping for something like Int - Maybe
 Char). Alternatively, is there a way to know ahead of time whether or not
 an Int will cause 'chr' to throw an exception?

 Thanks,
 Myles C. Maxfield

 [1] http://hackage.haskell.org/package/punycode

 ___
 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] Type error when trying to adapt http-proxy to new conduit

2012-12-27 Thread Michael Snoyman
On Thu, Dec 27, 2012 at 9:42 AM, Erik de Castro Lopo
mle...@mega-nerd.comwrote:

 Pieter Laeremans wrote:

  Hi,
 
  The http-proxy package isn't  compatible any longer with the latest
  conduit. Since it is open source, I thought, I might as well try to adapt
  it and submit a patch.

 Have you looked int git?

 It currently compiles from git but there is a space leak that
 I haven't managed to fix yet.

 Erik
 --
 --
 Erik de Castro Lopo
 http://www.mega-nerd.com/

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


Hi Erik,

I remember discussing very briefly with you why it wasn't possible to
simply use warp as a library for this project. I wonder if there would be a
way to expose more functionality from warp to make the maintenance burden
easier for http-proxy going forward. I'll be on IRC in a bit if you'd like
to discuss it.

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


Re: [Haskell-cafe] Stackage mailing list

2012-12-22 Thread Michael Snoyman
Sorry for the double-post, sent the first one from the wrong email address.

Hi Joachim,

I have not yet created a mailing list, but it should certainly be done.
There is also not yet a web site for Stackage, but there should be one in
the near future. At the very least, we'll need to host repository
information.

Give me another week or so, I'm putting together a blog post on Stackage
and its current status, and some directions for the future.

MIchael



On Sat, Dec 22, 2012 at 11:50 AM, Joachim Breitner m...@joachim-breitner.de
 wrote:

 Dear Michael,

 I’m wondering if I missed something, but is there a mailing list for
 stackage? Or has one of the standard lists (-cafe, libraries) been
 designated for questions about stackage?


 What I want to know is if you plan to provide a website for stackage
 soon where the list of included packages and their dependencies,
 including the tested and approved version numbers can be seen. I’d like
 to take that and integrate it on
 http://people.debian.org/~nomeata/platform.html
 and
 http://people.debian.org/~nomeata/hackagevsdebian.html

 Also, once you do that, it should be possible to add Stackage to the
 list of Distributions listed on hackage, so that on hackage one already
 sees the package’s stackage status and whether it lags behind there. The
 integrations is rather simple, just provide a file with that format:
 http://people.debian.org/~nomeata/cabalDebianMap.txt
 and bug the hackage maintainers to add it.

 Greetings,
 Joachim

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


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


Re: [Haskell-cafe] Hackage suggestion: Gather the list of the licenses of all dependencies of a package

2012-12-15 Thread Michael Snoyman
On Sat, Dec 15, 2012 at 4:25 PM, Malcolm Wallace malcolm.wall...@me.comwrote:


 On 13 Dec 2012, at 10:41, Petr P wrote:

  In particular, we can have a BSD package that depends on a LGPL package,
 and this is fine for FOSS developers. But for a commercial developer, this
 can be a serious issue that is not apparent until one examines *every*
 transitive dependency.

 This might a good time to remind everyone that every single program
 compiled by a standard GHC is linked against an LGPL library (the Gnu
 multi-precision integer library) - unless you take care first to build your
 own copy of the compiler against the integer-simple package instead of
 integer-gmp.  As far as I know, there are no ready-packaged binary
 installers for GHC that avoid this LGPL'd dependency.

 http://hackage.haskell.org/trac/ghc/wiki/ReplacingGMPNotes

 Just saying.


The difference between a library being (L)GPLed and this GMP issue is that,
in the latter case, we have an escape route. I know of at least two
companies which are actively considering switching entirely to
simple-integer because of this issue. If a widely used package (e.g.,
cpphs) is not available under a permissive license, there's not such escape
route available to users. (And note that I'm not actually *happy* about the
GMP situation, but at least we have a possible solution.)

I would strongly recommend reconsidering the licensing decision of cpphs.
Even if the LICENSE-commercial is sufficient for non-source releases of
software to be protected[1], it introduces a very high overhead for
companies to need to analyze a brand new license. Many companies have
already decided BSD3, MIT, and a number of other licenses are acceptable.
It could be very difficult to explain to a company, Yes, we use this
software which says it's LGPL, but it has this special extra license which,
if I'm reading it correctly, means you can't be sued, but since the author
of the package wrote it himself, I can't really guarantee what its meaning
would be in a court of law.

Looking at the list of reverse dependencies[2], I see some pretty heavy
hitters. Via haskell-src-exts[3] we end up with 75 more reverse
dependencies. I'd also like to point out that cpphs is the only
non-permissively-licensed dependency for a large number of packages.

I can give you more detailed information about my commercial experience
privately. But I can tell you that, in the currently situation, I have
created projects for clients for which Fay[4] would not be an option due to
the cpphs licensing issue.

Michael

[1] I'm not sure of that, since IANAL.
[2] http://packdeps.haskellers.com/reverse/cpphs
 [3] http://packdeps.haskellers.com/reverse/haskell-src-exts
[4] http://packdeps.haskellers.com/licenses/fay
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] LGPL and Haskell (Was: Re: ANNOUNCE: tie-knot library)

2012-12-13 Thread Michael Snoyman
To take this out of the academic realm and into the real-life realm: I've
actually done projects for companies which have corporate policies
disallowing the usage of any copyleft licenses in their toolset. My use
case was a web application, which would not have been affected by a GPL
library usage since we were not distributing binaries. Nonetheless, those
clients would not have allowed usage of any such libraries. You can argue
whether or not this is a good decision on their part, but I don't think the
companies I interacted with were unique in this regard.

So anyone who's considering selling Haskell-based services to companies
could very well be in a situation where any (L)GPL libraries are
non-starters, regardless of actual legal concerns. This affects the open
source realm as well, because I think many of us want our libraries to be
commercial-friendly (I know this is the case for Yesod).

As one specific data point, I initially created the markdown package[1]
because I couldn't use pandoc[2] in one of these situations due to its GPL
license.

MIchael

[1] http://hackage.haskell.org/package/markdown
[2] http://hackage.haskell.org/package/pandoc


On Thu, Dec 13, 2012 at 10:00 AM, Petr P petr@gmail.com wrote:

   Hi Felipe,

 thanks for making me think about the licenses. Without your suggestion, I
 wouldn't be aware of problems LGPL might cause for Haskell projects. And
 I'm considering the possibility of using BSD (or a similar) license in the
 future.

 I'm aware of the issues you pointed out. As you say, since tie-knot is a
 small library, it's not really that important what license it has, it's
 easy to re-implement it if needed. And, until some else contributes to the
 library, anybody can ask me to release the code under a different license,
 if needed.

 I'd say that the recent debate was a bit academic. (That wasn't bad at
 all, it clarified many things for me.) Nobody actually said I want to use
 the library, but I cannot because of the license. Also we're talking about
 LGPL, not GPL, and this makes thing different. Consider this: All packages
 on Hackage have published their source codes. (More than 95% are open
 source, and it's likely that those in OtherLicence are too.) With public
 source codes, there is no problem using a LGPL-ed library! Anybody can
 write a BSD licensed program which uses a LGPL library, and because all
 sources are public, the requirement to allow re-linking is easily
 satisfied. And nobody is forced to (L)GPL (unless the library is modified).
 We can freely mix open-source projects that use LGPL and non-copyleft
 licenses. The LGPL problem manifests only when someone wants to keep
 source codes secret - then (s)he is forced to solve the problem with
 re-linking. [With GPL, this would be very different, the whole project
 would have to be GPL no matter what.]

 I think it would be interesting to make some kind of poll to see what kind
 of software Haskell community writes (FOSS vs closed source) and what
 licensing issues people have. But the usual problem with such polls is that
 only people who have problems vote, so the results are very biased.

   Best regards,
   Petr


 2012/12/12 Felipe Almeida Lessa felipe.le...@gmail.com

 When deciding what license to use, I think one should also think about
 the role of their library.  For example, containers is quite central
 to the Haskell community and not easily replaceable.  The tie-knot
 library, OTOH, may be rewritten from scratch or even just skipped
 (just tie the knot yourself).  A GPLed containers forces the library
 user to somehow get a way of complying to the license.  A GPLed
 tie-knot, OTOH, may be just ignored.

 What I'm trying to say is that if your library is nice but someone may
 just rewrite it without much effort, then using GPL will just drive
 potential users of your library away, which is bad not just for the
 library but also for those potential users as well.  Perhaps you have
 a nice library but it may be replaced (with some small pain) by
 another, similar library.

 (In particular, I'm not saying that tie-knot is a library that should
 be ignored.  On the contrary, I think it's quite nice and it would be
 a shame if I had to ignore it when tying a knot just because of its
 restrictive license.)

 Of course, if everything on Hackage was GPLed, then it wouldn't make
 sense to release something as BSD as you wouldn't be able to use it
 anyway.  But the reality right now is that we have:

 (Apache,3)
 (BSD3,3359)
 (BSD4,3)
 (MIT,269)
 (PublicDomain,142)

 (GPL,409)
 (GPL-2,27)
 (GPL-3,147)
 (LGPL,138)
 (LGPL-2,2)
 (LGPL-2.1,25)
 (LGPL-3,21)

 (OtherLicense,179)

 This data comes from a quick shell session while considering the
 latest .cabal of all Hackage packages, so take it with a grain of salt
 =).

 Cheers,

 On Wed, Dec 12, 2012 at 2:12 PM, Jonathan Fischer Friberg
 odysso...@gmail.com wrote:
  +1
 
  Very similar to my point (see original thread), but put in a better
 way. :)
  As an 

Re: [Haskell-cafe] LGPL and Haskell (Was: Re: ANNOUNCE: tie-knot library)

2012-12-13 Thread Michael Snoyman
On Thu, Dec 13, 2012 at 10:14 AM, Colin Adams colinpaulad...@gmail.comwrote:

 On 13 December 2012 08:09, Michael Snoyman mich...@snoyman.com wrote:

 To take this out of the academic realm and into the real-life realm: I've
 actually done projects for companies which have corporate policies
 disallowing the usage of any copyleft licenses in their toolset. My use
 case was a web application, which would not have been affected by a GPL
 library usage since we were not distributing binaries. Nonetheless, those
 clients would not have allowed usage of any such libraries. You can argue
 whether or not this is a good decision on their part, but I don't think the
 companies I interacted with were unique in this regard.

 So anyone who's considering selling Haskell-based services to companies
 could very well be in a situation where any (L)GPL libraries are
 non-starters, regardless of actual legal concerns.


 Presumably you are talking about companies who want to distribute programs
 (a very small minority of companies, I would think)?


No, read my use case again. I was creating a web application for a company.
The company was not going to distribute my code in any way to their
clients. Nonetheless, the company had a corporate policy to not use *any*
copyleft licenses, and therefore I was unable to use a library such as
Pandoc. (I believe this policy affected me at two separate companies, but I
don't remember all the details tbh.)

I also don't think that distributing programs is as small a market as you
think, and should also be something we support for commercial users of
Haskell.

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


Re: [Haskell-cafe] LGPL and Haskell (Was: Re: ANNOUNCE: tie-knot library)

2012-12-13 Thread Michael Snoyman
On Thu, Dec 13, 2012 at 11:35 AM, Ramana Kumar ramana.ku...@cl.cam.ac.ukwrote:

 On Thu, Dec 13, 2012 at 8:09 PM, Michael Snoyman mich...@snoyman.comwrote:

 I also don't think that distributing programs is as small a market as you
 think, and should also be something we support for commercial users of
 Haskell.


 Distributing programs commercially is compatible with distributing them as
 free software.
 I think it would be helpful not to use commercial users to refer to both
 those with policies against copyleft licenses and those who make money
 distributing software.
 Those groups are not even extensionally equal, and separating them further
 (by having companies reconsider such policies) is, I would think, an
 instrumental goal of the free software movement, which is one reason why
 these tensions arise.


I'm not saying that *every* commercial user of Haskell has these concerns.
But I think it's a fair statement to say that a very large number of
commercial users do not wish to give out their source code. If you want to
claim that this isn't a commercial concern, but simply a concern of many
companies, that's fine, but I think it's irrelevant to the point: in many
cases, you will be unable to use GPLed libraries when creating software for
companies. Ignoring semantics, are you arguing with that claim?

If you want to try and convince companies to change their software policies
by writing some incredibly compelling GPL libraries, more power to you, and
I wish you the best. But I think that's quite separate to the question of
whether usage of the GPL today will hinder your ability to sell your
products or services to a company.

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


Re: [Haskell-cafe] Hackage suggestion: Gather the list of the licenses of all dependencies of a package

2012-12-13 Thread Michael Snoyman
I think that's a great idea. I just implemented this on PackDeps:

http://packdeps.haskellers.com/licenses

As with all features on that site, I'll be happy to deprecate it as soon as
Hackage incorporates the feature in the future.

Michael


On Thu, Dec 13, 2012 at 12:41 PM, Petr P petr@gmail.com wrote:

   Dear Haskellers,

 following up the recent discussion about copyleft licenses, I'd suggest a
 (hopefully minor) improvement of Hackage: For each package, gather the list
 of the licenses of everything it depends on. I think this would help
 considerably people who don't want or can't use software licensed under a
 particular license (most often (L)GPL). In particular, we can have a BSD
 package that depends on a LGPL package, and this is fine for FOSS
 developers. But for a commercial developer, this can be a serious issue
 that is not apparent until one examines *every* transitive dependency.

 This idea is a bit vague, because a dependency is actually a range of
 packages, which in theory could have different licenses. But I suppose this
 will rarely happen in practice, so it'd be safe just to take the last
 package in the range (or maybe take all licences of the packages in the
 range).

   Best regards,
   Petr

 ___
 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] Hackage suggestion: Gather the list of the licenses of all dependencies of a package

2012-12-13 Thread Michael Snoyman
On Thu, Dec 13, 2012 at 3:53 PM, Vincent Hanquez t...@snarc.org wrote:

 On 12/13/2012 12:51 PM, Michael Snoyman wrote:

 I think that's a great idea. I just implemented this on PackDeps:

 http://packdeps.haskellers.**com/licenseshttp://packdeps.haskellers.com/licenses

 As with all features on that site, I'll be happy to deprecate it as soon
 as Hackage incorporates the feature in the future.


 awesome Michael !

 However i think ithis shouldn't take dependencies from tests and
 benchmarks.
 This doesn't make differences for the overall license that the library
 exposes.

 --
 Vincent


Hmm, that's a good point. I'll admit I hadn't really thought this through,
but I can actually see an argument going both ways on this:

* Viral licenses won't actually affect you if they're just used for test
suites.
* But company lawyers will probably be nervous about it anyway.

Nonetheless, I think you have the right of it. Unless people say otherwise,
I'm going to implement Vincent's change.

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


Re: [Haskell-cafe] Hackage suggestion: Gather the list of the licenses of all dependencies of a package

2012-12-13 Thread Michael Snoyman
Are you referring to:

http://code.haskell.org/cpphs/LICENCE-commercial

If the package is dual-licensed BSD3 and LGPL, maybe Malcolm could change
the cabal file to mention the BSD3 so that its package description is less
intimidating?


On Thu, Dec 13, 2012 at 4:12 PM, Felipe Almeida Lessa 
felipe.le...@gmail.com wrote:

 While you're at it, maybe whitelisting cpphs would be nice as well =).

 On Thu, Dec 13, 2012 at 12:03 PM, Michael Snoyman mich...@snoyman.com
 wrote:
 
 
 
  On Thu, Dec 13, 2012 at 3:53 PM, Vincent Hanquez t...@snarc.org wrote:
 
  On 12/13/2012 12:51 PM, Michael Snoyman wrote:
 
  I think that's a great idea. I just implemented this on PackDeps:
 
  http://packdeps.haskellers.com/licenses
 
  As with all features on that site, I'll be happy to deprecate it as
 soon
  as Hackage incorporates the feature in the future.
 
 
  awesome Michael !
 
  However i think ithis shouldn't take dependencies from tests and
  benchmarks.
  This doesn't make differences for the overall license that the library
  exposes.
 
  --
  Vincent
 
 
  Hmm, that's a good point. I'll admit I hadn't really thought this
 through,
  but I can actually see an argument going both ways on this:
 
  * Viral licenses won't actually affect you if they're just used for test
  suites.
  * But company lawyers will probably be nervous about it anyway.
 
  Nonetheless, I think you have the right of it. Unless people say
 otherwise,
  I'm going to implement Vincent's change.
 
  Michael
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



 --
 Felipe.

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


Re: [Haskell-cafe] Hackage suggestion: Gather the list of the licenses of all dependencies of a package

2012-12-13 Thread Michael Snoyman
I'm not quite certain what to make of:

If you have a commercial use for cpphs, and feel the terms of the (L)GPL
are too onerous, you have the option of distributing unmodified binaries
(only, not sources) under the terms of a different licence (see
LICENCE-commercial).

It seems like that's saying if you really want to, use the BSD license
instead. But I'm not sure what the legal meaning of If you have a
commercial use is. Malcolm: could you clarify what the meaning is?


On Thu, Dec 13, 2012 at 6:37 PM, Felipe Almeida Lessa 
felipe.le...@gmail.com wrote:

 From [1] I gather that its license really is LGPL/GPL.  However, when
 used as a preprocessor its license doesn't really matter.  Many
 packages on that list have a LGPL taint because one of its deps use
 cpphs.  So the whitelist of cpphs would be stating that nobody is
 using cpphs as a library (which may be false, but is mostly true ;).

 [1] http://code.haskell.org/cpphs/README

 On Thu, Dec 13, 2012 at 1:08 PM, Michael Snoyman mich...@snoyman.com
 wrote:
  Are you referring to:
 
  http://code.haskell.org/cpphs/LICENCE-commercial
 
  If the package is dual-licensed BSD3 and LGPL, maybe Malcolm could change
  the cabal file to mention the BSD3 so that its package description is
 less
  intimidating?
 
 
  On Thu, Dec 13, 2012 at 4:12 PM, Felipe Almeida Lessa
  felipe.le...@gmail.com wrote:
 
  While you're at it, maybe whitelisting cpphs would be nice as well =).
 
  On Thu, Dec 13, 2012 at 12:03 PM, Michael Snoyman mich...@snoyman.com
  wrote:
  
  
  
   On Thu, Dec 13, 2012 at 3:53 PM, Vincent Hanquez t...@snarc.org
 wrote:
  
   On 12/13/2012 12:51 PM, Michael Snoyman wrote:
  
   I think that's a great idea. I just implemented this on PackDeps:
  
   http://packdeps.haskellers.com/licenses
  
   As with all features on that site, I'll be happy to deprecate it as
   soon
   as Hackage incorporates the feature in the future.
  
  
   awesome Michael !
  
   However i think ithis shouldn't take dependencies from tests and
   benchmarks.
   This doesn't make differences for the overall license that the
   library
   exposes.
  
   --
   Vincent
  
  
   Hmm, that's a good point. I'll admit I hadn't really thought this
   through,
   but I can actually see an argument going both ways on this:
  
   * Viral licenses won't actually affect you if they're just used for
 test
   suites.
   * But company lawyers will probably be nervous about it anyway.
  
   Nonetheless, I think you have the right of it. Unless people say
   otherwise,
   I'm going to implement Vincent's change.
  
   Michael
  
   ___
   Haskell-Cafe mailing list
   Haskell-Cafe@haskell.org
   http://www.haskell.org/mailman/listinfo/haskell-cafe
  
 
 
 
  --
  Felipe.
 
 



 --
 Felipe.

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


Re: [Haskell-cafe] Hackage suggestion: Gather the list of the licenses of all dependencies of a package

2012-12-13 Thread Michael Snoyman
On Thu, Dec 13, 2012 at 9:51 PM, Daniel Trstenjak 
daniel.trsten...@gmail.com wrote:


 On Thu, Dec 13, 2012 at 08:40:09PM +0200, Michael Snoyman wrote:
  If you have a commercial use for cpphs, and feel the terms of the (L)GPL
  are too onerous, you have the option of distributing unmodified binaries
  (only, not sources) under the terms of a different licence (see
  LICENCE-commercial).

 I think that depedencies to binaries, like cpphs, should be treated
 differently than depedencies to libraries, because using a (L)GPL-ed
 binary mostly hasn't any implications for a commercial user and
 also for the output of a (L)GPL-ed binary usually the (L)GPL doesn't apply.

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


In the case of cpphs, there's no way to determine that we're using it as a
library or an executable, since it's just listed in the build-depends.

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


[Haskell-cafe] yaml and aeson Was: Growing Haskell Platform

2012-12-07 Thread Michael Snoyman
On Fri, Dec 7, 2012 at 10:54 AM, Roman Cheplyaka r...@ro-che.info wrote:

 * Michael Snoyman mich...@snoyman.com [2012-12-07 09:52:07+0200]
  Let me bring up one other package: yaml (written by me). I think it's a
  pretty good fit for the standard YAML packaging library, since it simply
  reuses the existing infrastructure from the aeson package (i.e. the
 ToJSON
  and FromJSON typeclasses, and the Value datatype). But I'm actually a bit
  concerned about proposing it, based on some history.

 When I was looking at existing YAML libraries, I rejected yours when I
 saw JSON types. (I did see the do not let that confuse you, it's
 intentional warning, and no, it didn't help.)

 Besides giving the feeling that the API is a hack, this will inevitably
 confuse readers of my code who are not familiar with the library and,
 just based on the names, will assume that the code is working with JSON,
 not YAML.


If you mean the naming is a hack, I agree. But if we pretend for a moment
that the word JSON was actually replaced with YAML everywhere, I think the
abstraction is correct. The Value datatype represents a very sane subset of
YAML that people usually want to deal with. And if they want to deal with
all the glories of aliases and tags, we still have the Text.Libyaml
interface which preserves all information.

In other words, the hack is in the name, not the abstraction.


 IIUC, all of the existing tools for JSON processing are mainly just
 existing FromJSON instances. I am not sure how common this situation is,
 but for that you could define a newtype whose FromYAML instance would
 internally use the FromJSON instance of the underlying type.


It's the two typeclasses and the Value datatype. Don't underestimate the
importance of reusing infrastructure here. If we had our own types and
classes in YAML, then everyone who wants to include serialization classes
in their packages would have to write redundant instances for both
packages. Most likely, that would just mean incomplete instances for both
packages. It would also mean that we'd have to duplicate libraries like
aeson-lens, and duplicate all bugfixes in built-in instances, Generics
code, TH code, etc.

As a side benefit, the current setup allows code to remain
serialization-format-agnostic. For example, Persistent can read
configuration from either JSON to YAML files. Since YAML is a superset of
JSON, that's not such an amazing statement, but it does mean that users can
avoid an extra yaml package dependency if they really are just sticking
with JSON data.


 Or perhaps the JSON-agnostic subset of aeson could be extracted into a
 separate library, which both aeson and yaml would depend on.


I'd be very much in favor of that. I'm not so irked by the name hack to
have bothered bringing this up with Bryan, but if he's willing to make that
change, I'd certainly be grateful. I actually think it would be more
logical for the typeclasses to be called ToValue and FromValue anyway,
since that more directly states what they do.


 As for toYAML/toJSON, I guess most of the time they are different anyway —
 otherwise it's defeating the purpose of YAML to be more human-readable
 than JSON.


I don't think that's true in practice. Most of the readability of YAML
comes from the syntax, not the choice of actual serialization structure.
But I could be mistaken.

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


Re: [Haskell-cafe] yaml and aeson Was: Growing Haskell Platform

2012-12-07 Thread Michael Snoyman
On Fri, Dec 7, 2012 at 12:00 PM, Roman Cheplyaka r...@ro-che.info wrote:

 * Michael Snoyman mich...@snoyman.com [2012-12-07 11:51:40+0200]
   As for toYAML/toJSON, I guess most of the time they are different
 anyway —
   otherwise it's defeating the purpose of YAML to be more human-readable
   than JSON.
  
  
  I don't think that's true in practice. Most of the readability of YAML
  comes from the syntax, not the choice of actual serialization structure.
  But I could be mistaken.

 Not the serialization structure, no.

 I meant that YAML has some flexibility in syntax, which probably should
 be exploited by the instance writer to improve readability.

 For that you'd need a sufficiently adjustable pretty-printer, but that
 also means that you can't reuse ToJSON.

 Roman



I see what you mean. You're talking about pretty-printing features such as
how strings get quoted. That's true, to have full support for this, you
can't use the ToJSON interface, but instead need to use the Text.Libyaml
low-level interface. IMO, that's an acceptable trade-off. I consider the
readability of YAML much more important for human-generated files. But if
you'd like to see a higher-level interface which allows more control, I see
no problem with adding it in.

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


Re: [Haskell-cafe] Conduit and pipelined protocol processing using a threadpool

2012-11-27 Thread Michael Snoyman
I think the stm-conduit package[1] may be helpful for this use case. Each
time you get a new command, you can fork a thread and give it the TBMChan
to write to, and you can use sourceTBMChan to get a source to send to the
client.

Michael

[1] http://hackage.haskell.org/package/stm-conduit


On Tue, Nov 27, 2012 at 12:57 PM, Nicolas Trangez nico...@incubaid.comwrote:

 All,

 I've written a library to implement servers for some protocol using
 Conduit (I'll announce more details later).

 The protocol supports pipelining, i.e. a client can send a 'command'
 which contains some opaque 'handle' chosen by the client, the server
 processes this command, then returns some reply which contains this
 handle. The client is free to send other commands before receiving a
 reply for any previous request, and the server can process these
 commands in any order, sequential or concurrently.

 The library is based on network-conduit's Application style [1], as
 such now I write code like (OTOH)

  application :: AppData IO - IO ()
  application client = appSource client $= handler $$ appSink client
where
  handler = do
  negotiateResult - MyLib.negotiate
  liftIO $ validateNegotiateResult negotiateResult
  MyLib.sendInformation 123
  loop
 
 loop = do
 command - MyLib.getCommand
 case command of
 CommandA handle arg - do
 result - liftIO $ doComplexProcessingA arg
 MyLib.sendReply handle result
 loop
 Disconnect - return ()

 This approach handles commands in-order, sequentially. Since command
 processing can involve quite some IO operations to disk or network, I've
 been trying to support pipelining on the server-side, but as of now I
 was unable to get things working.

 The idea would be to have a pool of worker threads, which receive work
 items from some channel, then return any result on some other channel,
 which should then be returned to the client.

 This means inside loop I would have 2 sources: commands coming from
 the client (using 'MyLib.getCommand :: MonadIO m = Pipe ByteString
 ByteString o u m Command'), as well as command results coming from the
 worker threads through the result channel. Whenever the first source
 produces something, it should be pushed onto the work queue, and
 whenever the second on yields some result it should be sent to the
 client using 'MyLib.sendReply :: Monad m = Handle - Result - Pipe l i
 ByteString u m ()'

 I've been fighting this for a while and haven't managed to get something
 sensible working. Maybe the design of my library is flawed, or maybe I'm
 approaching the problem incorrectly, or ...

 Has this ever been done before, or would anyone have some pointers how
 to tackle this?

 Thanks,

 Nicolas

 [1]

 http://hackage.haskell.org/packages/archive/network-conduit/0.6.1.1/doc/html/Data-Conduit-Network.html#g:2



 ___
 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] Conduit and pipelined protocol processing using a threadpool

2012-11-27 Thread Michael Snoyman
On Tue, Nov 27, 2012 at 7:25 PM, Nicolas Trangez nico...@incubaid.comwrote:

 Michael,

 On Tue, 2012-11-27 at 17:14 +0200, Michael Snoyman wrote:
  I think the stm-conduit package[1] may be helpful for this use case.
  Each time you get a new command, you can fork a thread and give it the
  TBMChan to write to, and you can use sourceTBMChan to get a source to
  send to the client.

 That's +- what I had in mind. I did find stm-conduit before and did try
 to get the thing working using it, but these attempts failed.

 I attached an example which might clarify what I intend to do. I'm aware
 it contains several potential bugs (leaking threads etc), but that's
 beside the question ;-)

 If only I could figure out what to put on the 3 lines of comment I left
 in there...

 Thanks for your help,

 Nicolas


The issue is that you're trying to put everything into a single Conduit,
which forces reading and writing to occur in a single thread of execution.
Since you want your writing to be triggered by a separate event (data being
available on the Chan), you're running into limitations.

The reason network-conduit provides a Source for the incoming data and a
Sink for outgoing data is specifically to address your use case. You want
to take the data from the Source and put it into the Chan in one thread,
and take the data from the other Chan and put it into the Sink in a
separate thread. Something like:

myApp appdata = do
chan1 - ...
chan2 - ...
replicateM_ 5 $ forkIO $ worker chan1 chan2
forkIO $ appSource appdata $$ sinkTBMChan chan1
sourceTBMChan chan2 $$ appSink appdata

You'll also want to make sure to close chan1 and chan2 to make sure that
your threads stop running.

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


Re: [Haskell-cafe] how to inject another source into conduit

2012-11-12 Thread Michael Snoyman
I don't think there's enough information in the snippet you've given to
determine what the problem is. And in general, it's a good idea to include
the actual error message from the compiler.


On Mon, Nov 12, 2012 at 5:02 AM, Alexander V Vershilov 
alexander.vershi...@gmail.com wrote:

 Hello.

 I have problems with writing next code (using network-conduit)

 slightly simplified version:

  app ad = appSource ad $$ sink
where
  cMap = M.fromList [ (upload, cmdUpload), (download, cmdDownload)
 ]
  sink = takeLine = \c - case c of Just run - run ; Nothing -
 return ()
  cmdUpload = {- ... -} CB.sinkFile path
  cmdDownload = do
  {- code here -}
  CB.sourceFile path $$ appSink ad  -- this will not work because
 of
-- type error

 And I'm catching cannot construct the infinite type.

 I've found an example in [1], but it's not exactly solves my problem, as
 all
 the logic is inside conduit, and it will break upload function.

 [1] http://www.yesodweb.com/blog/2012/06/conduit-0-5

 --
 Alexander Vershilov

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


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


Re: [Haskell-cafe] How to handle exceptions in conduit?

2012-11-05 Thread Michael Snoyman
On Mon, Nov 5, 2012 at 9:51 PM, Michael Snoyman mich...@snoyman.com wrote:


 On Nov 5, 2012 2:42 PM, Hiromi ISHII konn.ji...@gmail.com wrote:
 
  Hi, there
 
  On 2012/11/01, at 21:23, Michael Snoyman wrote:
 
   Due to various technical reasons regarding the nature of conduit, you
 can't currently catch exceptions within the Pipe monad. You have two
 options:
  
   * Catch exceptions before `lift`ing.
   * Catch exceptions thrown from the entire Pipe.
  
   Since the exceptions are always originating in the underlying monad,
 the first choice is certainly possible in theory, though may require
 reworking the library you're using a bit.
 
  Thanks. In my case, used library is relatively small so I can rewrite it
 to ignore exception before lifting.
  But I think it is more convenient doing the same thing without modifying
 existing code.
 
  The second choice does not match my case because it cannot resume the
 process from the place just after an exception occurred.

 I agree that it would be great if conduit could meet your use case better.
 I haven't spent enough cycles looking at this yet to determine if the
 reason we don't have this support is a limitation in the conduit approach
 itself, or just a limitation in what I was able to implement so far. If you
 can think of a way to implement more fine-grained exception handling (or
 anyone else for that matter), I'd love to hear about it.

   One other possibility that I haven't actually tried would be to use
 transPipe[1] to catch all of the exceptions, though I'm not sure how well
 that would work in practice.
 
  The type of the first argument of `transPipe` should be general, so I
 think we can't compose it with `catch` function.

 That makes sense.


  -- Hiromi ISHII
  konn.ji...@gmail.com
 
 
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe

  Sorry, small follow-up. It's certainly possible to make some kind of
catching function, e.g.:

catchPipe :: (MonadBaseControl IO m, Exception e) = Pipe l i o u m r - (e
- Pipe l i o u m r) - Pipe l i o u m r
catchPipe (HaveOutput p c o) f = HaveOutput (catchPipe p f) c o
catchPipe (NeedInput p c) f = NeedInput (flip catchPipe f . p) (flip
catchPipe f . c)
catchPipe (Done r) _ = Done r
catchPipe (PipeM mp) f = PipeM $ Control.Exception.Lifted.catch (liftM
(flip catchPipe f) mp) (return . f)
catchPipe (Leftover p l) f = Leftover (catchPipe p f) l

I'm just not certain how useful this is in practice, as it doesn't really
give you any information on what else that Pipe was about to perform. So
you can't really just pick up where you left off.

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


Re: [Haskell-cafe] haskellers.com: Keterconfig incorrect?

2012-11-04 Thread Michael Snoyman
It might have been caused by an overzealous security mechanism: I was only
consuming 1000 bytes of the header, which in some BrowserID cases may not
be enough. I've bumped that limit, can you try again?


On Sun, Nov 4, 2012 at 9:35 AM, Obscaenvs obscae...@gmail.com wrote:

 Excerpt from source: h1Welcome to Keter/h1pThe hostname you have
 provided is not recognized./p.

 This after trying to login using Mozilla Persona:
 http://www.haskellers.com/**auth/page/browserid/**eyJhbGciOiJSUzIhttp://www.haskellers.com/auth/page/browserid/eyJhbGciOiJSUzI

 (Where I have shortened the string at the end)

 f

 __**_
 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] How to handle exceptions in conduit?

2012-11-01 Thread Michael Snoyman
Due to various technical reasons regarding the nature of conduit, you can't
currently catch exceptions within the Pipe monad. You have two options:

* Catch exceptions before `lift`ing.
* Catch exceptions thrown from the entire Pipe.

Since the exceptions are always originating in the underlying monad, the
first choice is certainly possible in theory, though may require reworking
the library you're using a bit.

One other possibility that I haven't actually tried would be to use
transPipe[1] to catch all of the exceptions, though I'm not sure how well
that would work in practice.

If people have ideas on how to improve the exception handling facilities of
conduit, please let me know.

Michael

[1]
http://hackage.haskell.org/packages/archive/conduit/0.5.2.7/doc/html/Data-Conduit.html#v:transPipe


On Thu, Nov 1, 2012 at 6:26 AM, Hiromi ISHII konn.ji...@gmail.com wrote:

 Hi, there

 I'm writing a program communicating with external process, which can be
 sometimes fail, using conduit and process-conduit package.

 Consider the following example, which reads paths from the config file,
 and passes their contents to external process, and output the results:

 ```exc.hs
 module Main where
 import qualified Data.ByteString.Char8 as BS
 import   Data.Conduit
 import qualified Data.Conduit.Binary   as BC
 import qualified Data.Conduit.List as LC
 import   Data.Conduit.Process

 main :: IO ()
 main = runResourceT $
   BC.sourceFile paths.dat $$ BC.lines =$= myConduit =$= LC.mapM_
 (unsafeLiftIO . BS.putStrLn)

 myConduit :: MonadResource m = Conduit BS.ByteString m BS.ByteString
 myConduit = awaitForever $ \path -
   BC.sourceFile (BS.unpack path) =$= conduitCmd ./sometimes-fail
 ```

 ```sometimes-fail.hs
 module Main where
 import System.Random

 main :: IO ()
 main = do
   b - randomRIO (1,10 :: Int)
   if b  9 then interact id else error error!
 ```

 ```paths.dat
 txt/a.dat
 txt/b.dat
 txt/c.dat
 ...bra, bra, bra...
 ```

 As you can see, `sometimes-fail` is a simple echoing program, but
 sometimes fail at random.

 Successful result is below:

 ```
 $ ./exc
 this is a!

 this is b!

 this is c!

 this was d!

 this was e!

 and this is f.
 ```

 but if `sometimes-fail` fails in some place, `exc` exits with exception
 like below:

 ```
 $ ./exc
 this is a!

 this is b!

 this is c!
 sometimes-fail: error!
 ```

 But I want to write the program acts like below:

 ```
 $ ./exc
 this is a!

 this is b!

 this is c!
 sometimes-fail: error!
 this was e!

 and this is f.
 ```

 that is, ignore the exception and continue to process remaining streams.

 So, the question is: how to handle the exception in `myConduit` and
 proceed to remaining works?

 In `conduit` package, `Pipe` type is not an instance of `MonadBaseControl
 IO` so it cannot handle exceptions within it.
 I think this is necessary to make `ResourceT` release resources correctly.

 So, how to write the Conduit that ignores some kind of exceptions and
 proceed to remaining works?
 One sometimes want to ignore the invalid input and/or output and just
 continue to process the remaining stream.

 One solution is that libraries using conduit provide failure-ignore
 version for all the `Pipe`s included in the library, but I think it is too
 heavy solution. It is ideal that `conduit` can package provides combinator
 that makes exsiting `Pipe`s failure-ignore.


 -- Hiromi ISHII
 konn.ji...@gmail.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] Auto-termination and leftovers in Conduits

2012-10-27 Thread Michael Snoyman
The important issue here is that, when using =$, $=, and =$=, leftovers
will discarded. To see this more clearly, realize that the first line of
sink is equivalent to:

  out1 - C.injectLeftovers CT.lines C.+ CL.head

So any leftovers from lines are lost once you move past that line. In order
to get this to work, stick the consume inside the same composition:

sink = C.injectLeftovers CT.lines C.+ do
out1 - CL.head
out2 - CL.consume
return (out1, T.unlines out2)

Or:

sink = CT.lines C.=$ do
out1 - CL.head
out2 - CL.consume
return (out1, T.unlines out2)

Michael

On Sat, Oct 27, 2012 at 9:20 PM, Myles C. Maxfield myles.maxfi...@gmail.com
 wrote:

 Hey,
 Say I have a stream of Data.Text.Text objects flowing through a
 conduit, where the divisions between successive Data.Text.Text items
 occur at arbitrary boundaries (maybe the source is sourceFile $=
 decode utf8). I'd like to create a Sink that returns a tuple of (the
 first line, the rest of the input).

 My first attempt at this looks like this:

 sink = do
   out1 - CT.lines C.=$ CL.head
   out2 - CL.consume
   return (out1, T.concat out2)

 However, the following input provides:

 runIdentity $ CL.sourceList [abc\nde, f\nghi] C.$$ sink
 (Just abc,f\nghi)

 But what I really want is
 (Just abc, \ndef\nghi)

 I think this is due to the auto-termination you mention in [1]. My
 guess is that when CT.lines yields the first value, (CL.head then also
 yields it,) and execution is auto-terminated before CT.lines gets a
 chance to specify any leftovers.

 How can I write this sink? (I know I can just use CL.consume and
 T.break (== '\n'), but I'm not interested in that. I'm trying to
 figure out how to get the behavior I'm looking for with conduits.)

 Thanks,
 Myles

 [1]
 http://hackage.haskell.org/packages/archive/conduit/0.5.2.7/doc/html/Data-Conduit.html

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


Re: [Haskell-cafe] forkProcess, forkIO, and multithreaded runtime

2012-10-16 Thread Michael Snoyman
On Mon, Oct 15, 2012 at 6:30 PM, Joey Hess j...@kitenet.net wrote:

 Michael Snoyman wrote:
  I think I have a misunderstanding of how forkProcess should be working.
  Ultimately this relates to some bugs in the development version of
 keter, but
  I've found some behavior in a simple test program which I wouldn't have
  expected either, which may or may not be related.
 
  With the program at the end of this email, I would expect that, once per
  second, I would get a message printed from each forkIO'd green thread,
 the
  forked process, and the master process. And if I spawn 8 or less child
 threads
  that's precisely what happens. However, as soon as I up that number to
 9, the
  child process is never run. The process is, however, created, as can be
  confirmed by looking at the process table.
 
  This only occurs when using the multithreaded runtime. In other words,
  compiling with ghc --make test.hs seems to always produce the expected
  output, whereas ghc --make -threaded test.hs causes the behavior
 described
  above. Having looked through the code for the process package a bit, my
 initial
  guess is that this is being caused by a signal being sent to the child
 process,
  but I'm not familiar enough with the inner workings to confirm or
 disprove this
  guess.
 
  If anyone has any ideas on this, I'd appreciate it.

 While I'm not reproducing that behavior here with your test case and
 7.4.1, I recently converted a large program to use -threaded (because I
 needed to use yesod in it, actually :), and had large quantities of pain
 involving forkProcess. It seemed to come down to this easily overlooked
 note in the docs:

   forkProcess comes with a giant warning: since any other running threads
   are not copied into the child process, it's easy to go wrong: e.g. by
   accessing some shared resource that was held by another thread in the
   parent.

 In my experience, forkProcess often behaves incomprehensibly (to me)
 with -threaded, typically resulting in a forked process hanging, and
 quite often only some small percentage of the time, which makes it
 really hard to track down and try to diagnose what thunk might not be
 getting forced until after the fork, or whatever.

 I did some analysis and produced a test case for problems caused by
 use of forkProcess in parts of MissingH, here:
 http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=681621

 My understanding is that System.Process avoids these problems by doing
 all the setup around forking a command in C code. I've banished
 forkProcess from my code base entirely, except for a double fork I need
 to daemonize, and I don't even trust that call. :/


Well, I tried switching my code to forking/execing from C in a very similar
manner to the process package, and it seems to work.

Thanks for the input everyone!

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


[Haskell-cafe] forkProcess, forkIO, and multithreaded runtime

2012-10-15 Thread Michael Snoyman
Hi all,

I think I have a misunderstanding of how forkProcess should be working.
Ultimately this relates to some bugs in the development version of keter,
but I've found some behavior in a simple test program which I wouldn't have
expected either, which may or may not be related.

With the program at the end of this email, I would expect that, once per
second, I would get a message printed from each forkIO'd green thread, the
forked process, and the master process. And if I spawn 8 or less child
threads that's precisely what happens. However, as soon as I up that number
to 9, the child process is never run. The process is, however, created, as
can be confirmed by looking at the process table.

This only occurs when using the multithreaded runtime. In other words,
compiling with ghc --make test.hs seems to always produce the expected
output, whereas ghc --make -threaded test.hs causes the behavior
described above. Having looked through the code for the process package a
bit, my initial guess is that this is being caused by a signal being sent
to the child process, but I'm not familiar enough with the inner workings
to confirm or disprove this guess.

If anyone has any ideas on this, I'd appreciate it.

Michael

import System.Posix.Process (forkProcess, getProcessID)
import Control.Concurrent (forkIO, threadDelay)
import System.IO (hFlush, stdout)
import System.Posix.Signals (signalProcess, sigKILL)
import Control.Exception (finally)

main :: IO ()
main = do
mapM_ spawnChild [1..9]
child - forkProcess $ do
putStrLn starting child
hFlush stdout
loop child 0
print (child pid, child)
hFlush stdout

-- I've commented out the finally so that the zombie process stays
alive,
-- to prove that it was actually created.
loop parent 0 -- `finally` signalProcess sigKILL child

spawnChild :: Int - IO ()
spawnChild i = do
_ - forkIO $ loop (spawnChild  ++ show i) 0
return ()

loop :: String - Int - IO ()
loop msg i = do
pid - getProcessID
print (pid, msg, i)
hFlush stdout
threadDelay 100
loop msg (i + 1)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: cabal-install-1.16.0 (and Cabal-1.16.0.1)

2012-10-08 Thread Michael Snoyman
Hi Johan,

I reported issue 1058 on Github:

https://github.com/haskell/cabal/issues/1058

Installing from separate folder with Custom build type fails

Thanks,
Michael

On Mon, Oct 8, 2012 at 6:39 PM, Johan Tibell johan.tib...@gmail.com wrote:

 Hi,

 I'll make a bugfix release for cabal-install and Cabal in a few days
 to include fixes to issues people found so far. If everyone who had
 some problem related to the latest release could please post it here
 so I can make sure that we include a fix for them. If you've already
 reported it elsewhere, please bring it up here anyway to make sure I
 don't miss it.

 -- Johan

 ___
 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] Call for discussion: OverloadedLists extension

2012-09-26 Thread Michael Snoyman
On Tue, Sep 25, 2012 at 6:21 PM, Heinrich Apfelmus
apfel...@quantentunnel.de wrote:
 Michael Snoyman wrote:


 Note that I wasn't necessarily advocating such a pragma. And a lot of
 my XML code actually *does* use two IsString instances at the same
 time, e.g.:

 Element (img :: Name) (singleton (href :: Name) (foo.png ::
 Text)) [NodeComment (No content inside an image :: Text)]


 In this particular case, would it make sense to use smart constructors
 instead?

 The idea is that you can put the polymorphism in two places: either make the
 output polymorphic, or make the input polymorphic. The latter would
 correspond to a type

element :: (IsString name, IsString s, IsMap map)
= name - map name s - [Element]
element name map = Element (toName name) (toMap map)

 One benefit would be that the function will accept any list as a map, not
 just list literals.

Just to clarify: this would be a *replacement* for OverloadedStrings
usage, right? If used in conjunction with OverloadedStrings, we'd run
into the too-much-polymorphism issue you describe in your initial
email in this thread, since `element foo'` would become `element
(fromString foo)` which would become `Element ((toName . fromString)
foo)`, and `toName . fromString` makes it ambiguous what the
intermediate data type is.

Assuming this is meant are a replacement, I see two downsides.
Firstly, this would work for construction, but not for deconstruction.
Currently, I can do something like:

handleList :: Element - Element
handleList (Element ul _ _) = ...
handleList e = e

The other is that we've only solved one specific case by providing a
replacement function. In order to keep code just as terse as it is
now, we'd have to provide a whole slew of replacement functions. For
example, consider the code:

handleList (Element ul attrs _) = case Map.lookup class attrs of 

If we get rid of OverloadedStrings, then we need to either provide a
replacement `lookup` function which performs the conversion from
String to Name, or change all lookup calls to explicitly perform that
lookup.

Michael

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


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-24 Thread Michael Snoyman
On Mon, Sep 24, 2012 at 2:53 PM, George Giorgidze giorgi...@gmail.com wrote:
 Hi Michael,

 Here at the University of Tübingen, I am co-supervising (together with
 Jeroen Weijers) a student project implementing the OverloadedLists
 extension for GHC. Achim Krause is the student who is working on the
 project. We took into consideration earlier discussions on this topic
 [1,2] before embarking on the project.

 Achim has worked on two approaches.

 The first approach is very simple, both from the user's and the
 extension implementor's perspective (it follows the implementation of
 OverloadedStrings closely) and typechecks and desugars lists like

 [] ; [x,y,z] ;  ['a' .. 'z'] ;

 as

 fromList [] ;  fromList [x,y,z] ; fromList ['a' .. 'z'] ;

 where fromList is whatever is in scope with that name. That said, we
 do provide the FromList type class that can be used to overload
 fromList. In the following I give the definition of the class, as well
 as, example instances:

 class FromList l where
   type Item l
   fromList :: [Item l] - l

 instance FromList [a] where
   type Item [a] = a
   fromList = id

 instance (Ord a) = FromList (Set a) where
   type Item (Set a) = a
   fromList = Set.fromList

 instance (Ord k) = FromList (Map k v) where
   type Item (Map k v) = (k,v)
   fromList = Map.fromList

 instance FromList (IntMap v) where
   type Item (IntMap v) = (Int,v)
   fromList = IntMap.fromList

 instance FromList Text where
   type Item Text = Char
   fromList = Text.pack

 This approach has already been implemented by Achim as patch against GHC head.

 This approach is very simple, but can be inefficient as it may result
 into unnecessary construction of lists at runtime. This can be a
 serious issue when constructing large structures from arithmetic
 sequences (e.g., from the [ .. ] notation) or when using non-literal
 expressions (e.g., variables) inside the square brackets.

 Our second approach to OverloadedLists is to avoid the construction of
 lists altogether. By typechecking and desugaring lists like

 [] ; [x,y,z] ;  ['a' .. 'z'] ;

 as

 mempty ; singleton x `mappend` singleton y `mappend` singleton z ;
 genericEnumFromTo 'a' 'z' ;

 We  provide the Singleton and GenericEnum type classes for overloading
 singleton and genericEnum(..) functions. In the following, I give the
 definitions of the classes, as well as, example instances:

 -- Singleton class

 class Singleton l where
   type SingletonItem l
   singleton :: SingletonItem l - l

 -- Singleton instances

 instance Singleton [a] where
   type SingletonItem [a] = a
   singleton a = [a]

 instance (Ord a) = Singleton (Set a) where
   type SingletonItem (Set a) = a
   singleton = Set.singleton

 instance (Ord k) = Singleton (Map k v) where
   type SingletonItem (Map k v) = (k,v)
   singleton (k,v) = Map.singleton k v

 instance Singleton (IntMap v) where
   type SingletonItem (IntMap v) = (Int,v)
   singleton (k,v) = IntMap.singleton k v

 instance Singleton Text where
   type SingletonItem Text = Char
   singleton = Text.singleton

 -- GenericEnum class

 class GenericEnum l where
   type EnumItem l
   genericEnumFrom:: EnumItem l - l
   genericEnumFromThen:: EnumItem l - EnumItem l - l
   genericEnumFromTo  :: EnumItem l - EnumItem l - l
   genericEnumFromThenTo  :: EnumItem l - EnumItem l - EnumItem l - l

 -- GenericEnum instances

 instance (Enum a) = GenericEnum [a] where
   type EnumItem [a] = a
   genericEnumFrom= enumFrom
   genericEnumFromThen= enumFromThen
   genericEnumFromTo  = enumFromTo
   genericEnumFromThenTo  = enumFromThenTo

 instance (Ord a,Enum a) = GenericEnum (Set a) where
   type EnumItem (Set a) = a
   genericEnumFrom   a = Set.fromList (enumFrom a)
   genericEnumFromThen   a b   = Set.fromList (enumFromThen a b)
   genericEnumFromTo a b   = Set.fromList (enumFromTo a b)
   genericEnumFromThenTo a b c = Set.fromList (enumFromThenTo a b c)

 instance (Ord k,Enum (k,v)) = GenericEnum (Map k v) where
   type EnumItem (Map k v) = (k,v)
   genericEnumFrom   a = Map.fromList (enumFrom a)
   genericEnumFromThen   a b   = Map.fromList (enumFromThen a b)
   genericEnumFromTo a b   = Map.fromList (enumFromTo a b)
   genericEnumFromThenTo a b c = Map.fromList (enumFromThenTo a b c)

 instance (Enum (Int,v)) = GenericEnum (IntMap v) where
   type EnumItem (IntMap v) = (Int,v)
   genericEnumFrom   a = IntMap.fromList (enumFrom a)
   genericEnumFromThen   a b   = IntMap.fromList (enumFromThen a b)
   genericEnumFromTo a b   = IntMap.fromList (enumFromTo a b)
   genericEnumFromThenTo a b c = IntMap.fromList (enumFromThenTo a b c)

 instance GenericEnum Text where
   type EnumItem Text = Char
   genericEnumFrom   a = Text.pack (enumFrom a)
   genericEnumFromThen   a b   = Text.pack (enumFromThen a b)
   genericEnumFromTo a b   = Text.pack (enumFromTo a b)
   genericEnumFromThenTo a b c = Text.pack (enumFromThenTo a b c)

 Note that the GenericEnum 

Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-23 Thread Michael Snoyman
On Sun, Sep 23, 2012 at 10:51 AM, Heinrich Apfelmus
apfel...@quantentunnel.de wrote:
 Michael Snoyman wrote:

 (Prettier formatting available at: https://gist.github.com/3761252)

 Many of us use the OverloadedStrings language extension on a regular
 basis. It provides the ability to keep the ease-of-use of string
 literal syntax, while getting the performance and correctness
 advantages of specialized datatypes like ByteString and Text. I think
 we can get the same kind of benefit by allowing another literal syntax
 to be overloaded, namely lists.


 Actually, I am already somewhat reserved about the  OverloadedStrings
 proposal.

 The core point of the OverloadedSomething extensions is that they address a
 syntactic issue, namely that we can write

   example

 instead of

   (pack example)

 The extension does this by making the literal polymorphic.

 Unfortunately, making literals polymorphic does not always achieve the
 desired effect of reducing syntax. In fact, they can instead increase
 syntax! In other words, I would like to point out that there is a trade-off
 involved: is it worth introducing a small syntactic reduction at the cost of
 both a small additional conceptual complexity and some syntactic enlargement
 elsewhere?


 The increase in syntax happened to me while using one of the json libraries.
 The thing is that if a receiver function is agnostic in the string used,
 or if it is otherwise polymorphic,

 receive1 :: IsString s = s - Foo
 receive2 :: JSON s = s - Foo

 then I have to specify the type of the overloaded argument (either by a type
 annotation or a monomorphic function call).

 In other words, without  OverloadedStrings , I was able to write

 receive2 example

 but with the extension, I now have to write

 receive2 (pack example)


 A similar effect can be seen with the good old numeric literals. Sometimes,
 you just have to introduce a type signature (:: Int) to make a program
 unambiguous.


 In this light, I don't think that the trade-off made by the OverloadedLists
 extension is big enough.


 Best regards,
 Heinrich Apfelmus

 --
 http://apfelmus.nfshost.com


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

I agree with your point. But what you've pointed out is that there's a
trade-off involved, and then elaborated on the downsides of the
trade-off. Let's not forget that there are significant upsides as
well. And based on the large amount of code out there that actually
uses OverloadedStrings, I think many people feel that the upsides
outweigh the downsides in many cases. The nice thing about an
extension like OverloadedStrings or OverloadedLists is that it need
not affect your code in any way: if you don't turn it on, your code
will continue to work. And you'll still be able to use libraries that
themselves use the extensions without any ill effects.

That said, it would be great to come up with ways to mitigate the
downsides of unbounded polymorphism that you bring up. One idea I've
seen mentioned before is to modify these extension so that they target
a specific instance of IsString/IsList, e.g.:

{-# STRING_LITERALS_AS Text #-}

foo == (fromString foo :: Text)

Another might be more intelligent/powerful defaulting rules, similar
to what we have already with numeric literal overloading.

Michael

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


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-23 Thread Michael Snoyman
On Sun, Sep 23, 2012 at 5:51 PM, Chris Smith cdsm...@gmail.com wrote:
 Michael Snoyman mich...@snoyman.com wrote:
 That said, it would be great to come up with ways to mitigate the
 downsides of unbounded polymorphism that you bring up. One idea I've
 seen mentioned before is to modify these extension so that they target
 a specific instance of IsString/IsList, e.g.:

 {-# STRING_LITERALS_AS Text #-}

 foo == (fromString foo :: Text)

 That makes sense for OverloadedStrings, but probably not for
 OverloadedLists or overloaded numbers... String literals have the
 benefit that there's one type that you probably always really meant.
 The cases where you really wanted [Char] or ByteString are rare.  On
 the other hand, there really is no sensible I always want this
 answer for lists or numbers.  It seems like a kludge to do it
 per-module if each module is going to give different answers most of
 the time.

 --
 Chris

Note that I wasn't necessarily advocating such a pragma. And a lot of
my XML code actually *does* use two IsString instances at the same
time, e.g.:

Element (img :: Name) (singleton (href :: Name) (foo.png ::
Text)) [NodeComment (No content inside an image :: Text)]

(Courtesy of xml-conduit.)

To prove your point even further, with OverloadedLists we could
replace that `singleton` call with `[(href, foo.png)]` and then be
using two `IsList` instances simultaneously as well (`Map` and `[]`).

Also, I use the `ByteString` instance of `IsString` regularly when
using `http-conduit` and `warp` (for all of the header values), and to
an even greater extent when hacking on the internals of any HTTP
library (whether `http-conduit` or something in the `wai` ecosystem).

Michael

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


[Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-22 Thread Michael Snoyman
(Prettier formatting available at: https://gist.github.com/3761252)

Many of us use the OverloadedStrings language extension on a regular
basis. It provides the ability to keep the ease-of-use of string
literal syntax, while getting the performance and correctness
advantages of specialized datatypes like ByteString and Text. I think
we can get the same kind of benefit by allowing another literal syntax
to be overloaded, namely lists.

## Overly simple approach

The simplest example I can think of is allowing easier usage of Vector:

[1, 2, 3] :: Vector Int

In order to allow this, we could use a typeclass approach similar to
how OverloadedStrings works:

class IsList a where
fromList :: [b] - a b
instance IsList Vector where
fromList = V.fromList
foo :: Vector Int
foo = fromList [1, 2, 3]

## Flaws

However, such a proposal does not allow for constraints, e.g.:

instance IsList Set where
fromList = Set.fromList

No instance for (Ord b)
  arising from a use of `Set.fromList'
In the expression: Set.fromList
In an equation for `fromList': fromList = Set.fromList
In the instance declaration for `IsList Set'

Additionally, it provides for no means of creating instances for
datatypes like Map, where the contained value is not identical to the
value contained in the original list. In other words, what I'd like to
see is:

[(foo, 1), (bar, 2)] :: Map Text Int

## A little better: MPTC

A simplistic approach to solve this would be to just use MultiParamTypeClasses:

class IsList input output where
fromList :: [input] - output
instance IsList a (Vector a) where
fromList = V.fromList
foo :: Vector Int
foo = fromList [1, 2, 3]

Unfortunately, this will fail due to too much polymorphism:

No instance for (IsList input0 (Vector Int))
  arising from a use of `fromList'
Possible fix:
  add an instance declaration for (IsList input0 (Vector Int))
In the expression: fromList [1, 2, 3]
In an equation for `foo': foo = fromList [1, 2, 3]

This can be worked around by giving an explicit type signature on the
numbers in the list, but that's not a robust solution. In order to
solve this properly, I think we need either functional dependencies or
type families:

## Functional dependencies

class IsList input output | output - input where
fromList :: [input] - output
instance IsList a (Vector a) where
fromList = V.fromList
instance Ord a = IsList a (Set a) where
fromList = Set.fromList
instance Ord k = IsList (k, v) (Map k v) where
fromList = Map.fromList

foo :: Vector Int
foo = fromList [1, 2, 3]

bar :: Set Int
bar = fromList [1, 2, 3]

baz :: Map String Int
baz = fromList [(foo, 1), (bar, 2)]

## Type families

class IsList a where
type IsListInput a
fromList :: [IsListInput a] - a
instance IsList (Vector a) where
type IsListInput (Vector a) = a
fromList = V.fromList
instance Ord a = IsList (Set a) where
type IsListInput (Set a) = a
fromList = Set.fromList
instance Ord k = IsList (Map k v) where
type IsListInput (Map k v) = (k, v)
fromList = Map.fromList

foo :: Vector Int
foo = fromList [1, 2, 3]

bar :: Set Int
bar = fromList [1, 2, 3]

baz :: Map String Int
baz = fromList [(foo, 1), (bar, 2)]

## Conclusion

Consider most of this proposal to be a strawman: names and techniques
are completely up to debate. I'm fairly certain that our only two
choices to implement this extension is a useful way is fundeps and
type families, but perhaps there's another approach I'm missing. I
don't have any particular recommendation here, except to say that
fundeps is likely more well supported by other compilers.

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


Re: [Haskell-cafe] Conduit: Where to run monad stacks?

2012-08-28 Thread Michael Snoyman
On Fri, Aug 24, 2012 at 5:03 PM, Niklas Hambüchen m...@nh2.me wrote:
 Hello Michael,

 yes, that does certainly help, and it should definitely be linked to.

 The remaining question is:

 Is it possible to have something like transPipe that runs only once for
 the beginning of the pipe?

 It seems desirable for me to have conduits which encapsulate monads.
 Imagine you have to conduits dealing with stateful encryption/decryption
 and one data-counting one in the middle, like:

 decryptConduit $= countConduit $= encryptConduit

 Would you really want to combine the three different internal monads
 into one single monad of the whole pipe, even though the internal monads
 are implementation details and not necessary for the operation of the
 whole pipe?

I don't disagree with your analysis, but I don't think it's generally
possible to implement the desired transPipe. (If someone can prove
otherwise, I'd be very happy.) It *might* be possible via some (ab)use
of `monad-control` and mutable variables, however.

 The idea with a Ref inside a Reader sounds like a workaround, but has
 the same problem of globalizing/combining effects, somewhat limiting
 composability of conduits.

I wouldn't say that we're globalizing effects at all. It should
theoretically be possible to write some function like:

stateToReader :: MonadIO m = StateT r m a - ReaderT (IORef r) m a

And then `transPipe` will function on the resulting Pipe without issue.

Michael


 Niklas

 On 24/08/12 06:51, Michael Snoyman wrote:
 I agree that the behavior is a bit confusing (Dan Burton just filed an
 issue about this[1], I'm guessing this email is related).

 I put up a wiki page[2] to hopefully explain the issue. Can you review
 it and let me know if it helps? If so, I'll link to it from the
 Haddocks.

 Michael

 [1] https://github.com/snoyberg/conduit/issues/67
 [2] https://github.com/snoyberg/conduit/wiki/Dealing-with-monad-transformers

 On Wed, Aug 22, 2012 at 11:19 PM, Niklas Hambüchen m...@nh2.me wrote:
 Today I was surprised that transPipe is called for every chunk of data
 going through my pipe, rendering the StateT I put in useless, because it
 was always restarted with the initial value.

 It would be nice to have some explanation about this, as it makes it
 easy to write compiling code that has completely unexpected behaviour.


 I wrote this function (also on http://hpaste.org/73538):

 conduitWithState :: (MonadIO m) = Conduit Int (StateT Int m) String
 conduitWithState = do
   liftIO $ putStrLn $ Counting Int-String converter ready!
   awaitForever $ \x - do
 i - lift get
 lift $ modify (+1)
 liftIO $ putStrLn $ Converting  ++ show x ++  to a string!  ++
 Processed so far:  ++ show i
 yield (show x)

 and ran it like this:

 countingConverterConduit :: (MonadIO m) = Conduit Int m String
 countingConverterConduit = transPipe (\stateTint - evalStateT stateTint
 1) conduitWithState

 main :: IO ()
 main = do
   stringList - CL.sourceList [4,1,9,7,3] $=
  countingConverterConduit $$
  CL.consume
   print stringList

 However, the output is not what I expected, but only:

 Processed so far:1
 Processed so far:1
 ...

 Dan Burton proposed a fix, making the whole sink-conduit-source
 construction run on the StateT:

 main = do
   stringList - flip evalStateT 1 $ ...


 So the question is: What is the rationale for this?

 I was expecting that if I have an IO pipe in my main conduit, I could
 easily run stuff on top of that in parts of the pipe.

 Thanks
 Niklas

 ___
 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] Conduit: Where to run monad stacks?

2012-08-23 Thread Michael Snoyman
I agree that the behavior is a bit confusing (Dan Burton just filed an
issue about this[1], I'm guessing this email is related).

I put up a wiki page[2] to hopefully explain the issue. Can you review
it and let me know if it helps? If so, I'll link to it from the
Haddocks.

Michael

[1] https://github.com/snoyberg/conduit/issues/67
[2] https://github.com/snoyberg/conduit/wiki/Dealing-with-monad-transformers

On Wed, Aug 22, 2012 at 11:19 PM, Niklas Hambüchen m...@nh2.me wrote:
 Today I was surprised that transPipe is called for every chunk of data
 going through my pipe, rendering the StateT I put in useless, because it
 was always restarted with the initial value.

 It would be nice to have some explanation about this, as it makes it
 easy to write compiling code that has completely unexpected behaviour.


 I wrote this function (also on http://hpaste.org/73538):

 conduitWithState :: (MonadIO m) = Conduit Int (StateT Int m) String
 conduitWithState = do
   liftIO $ putStrLn $ Counting Int-String converter ready!
   awaitForever $ \x - do
 i - lift get
 lift $ modify (+1)
 liftIO $ putStrLn $ Converting  ++ show x ++  to a string!  ++
 Processed so far:  ++ show i
 yield (show x)

 and ran it like this:

 countingConverterConduit :: (MonadIO m) = Conduit Int m String
 countingConverterConduit = transPipe (\stateTint - evalStateT stateTint
 1) conduitWithState

 main :: IO ()
 main = do
   stringList - CL.sourceList [4,1,9,7,3] $=
  countingConverterConduit $$
  CL.consume
   print stringList

 However, the output is not what I expected, but only:

 Processed so far:1
 Processed so far:1
 ...

 Dan Burton proposed a fix, making the whole sink-conduit-source
 construction run on the StateT:

 main = do
   stringList - flip evalStateT 1 $ ...


 So the question is: What is the rationale for this?

 I was expecting that if I have an IO pipe in my main conduit, I could
 easily run stuff on top of that in parts of the pipe.

 Thanks
 Niklas

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

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


[Haskell-cafe] Haskell position in Israel

2012-08-20 Thread Michael Snoyman
Hi all,

Just passing on this job opportunity for another company. SQream is
looking for Haskellers located in Israel. They are working on high
performance solutions for large databases using Haskell. If you're
interested, please contact me off-list, and I'll pass your information
along.

Thanks,
Michael

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


Re: [Haskell-cafe] [Pipes] Can pipes solve this problem? How?

2012-08-16 Thread Michael Snoyman
On Wed, Aug 15, 2012 at 9:54 PM, Daniel Hlynskyi abcz2.upr...@gmail.comwrote:

 Hello Cafe.
 Consider code, that takes input from handle until special substring
 matched:

  matchInf a res s | a `isPrefixOf` s = reverse res
  matchInf a res (c:cs)   = matchInf a (c:res) cs
  hTakeWhileNotFound str hdl = hGetContents hdl = return.matchInf str []

 It is simple, but the handle is closed after running. That is not good,
 because I want to reuse this function.
 Code can be rewritten without hGetContent, but it is much less
 comprehensible:

 hTakeWhileNotFound str hdl = fmap reverse$ findStr str hdl [0] []
  where
findStr str hdl indeces acc = do
  c - hGetChar hdl
  let newIndeces = [ i+1 | i - indeces, i  length str, str!!i == c]
  if length str `elem` newIndeces
then return (c : acc)
else findStr str hdl (0 : newIndeces) (c : acc)

 So, the question is - can pipes (any package of them) be the Holy Grail in
 this situation, to both keep simple code and better deal with handles (do
 not close them specifically)? How?

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


This is essentially what we do in wai-extra for multipart body parsing[1].
This code uses `conduit`.

The tricky part is that you have to remember that the substring you're
looking for might be spread across multiple chunks, so you need to take
that into account. A simple approach would be:

* If the search string is a substring of the current chunk, success.
* If the end of the current chunk is a prefix of the search string, grab
the next chunk, append the two, and repeat. (Note: there are more efficient
approaches than appending.)
* Otherwise, skip to the next chunk.
* If no more chunks available, the substring was not found.

Michael

[1]
https://github.com/yesodweb/wai/blob/master/wai-extra/Network/Wai/Parse.hs#L270
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Upcoming resourcet 0.4

2012-08-15 Thread Michael Snoyman
Hi all,

I've been working with Aristid on an enhancement to resourcet[1]. Please
see the issue for more details, this email isn't about that change.
Instead, now that we're looking at a new breaking release, I was wondering
if anyone had ideas of something they thought should be changed in
resourcet.

Thanks,
Michael

[1] https://github.com/snoyberg/conduit/issues/61
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Platform Versioning Policy: upper bounds are not our friends

2012-08-15 Thread Michael Snoyman
On Thu, Aug 16, 2012 at 5:38 AM, Conrad Parker con...@metadecks.org wrote:

 On 16 August 2012 03:38, Bryan O'Sullivan b...@serpentine.com wrote:
  Hi, folks -
 
  I'm sure we are all familiar with the phrase cabal dependency hell at
 this
  point, as the number of projects on Hackage that are intended to hack
 around
  the problem slowly grows.
 
  I am currently undergoing a fresh visit to that unhappy realm, as I try
 to
  rebuild some of my packages to see if they work with the GHC 7.6 release
  candidate.

 Likewise ...

  A substantial number of the difficulties I am encountering are related to
  packages specifying upper bounds on their dependencies. This is a
 recurrent
  problem, and its source lies in the recommendations of the PVP itself
  (problematic phrase highlighted in bold):

 I think part of the problem might be that some packages (like
 bytestring, transformers?) have had their major version number
 incremented even despite being backwards-compatible. Perhaps there are
 incompatible changes, but most of the cabal churn I've seen recently
 has involved incrementing the bytestring upper bound to 0.11 without
 requiring any code changes to modules using Data.ByteString.


In general, I've been taking the approach recently that we have two classes
of packages: some (like transformers and bytestring) have mostly-stable
APIs, and most code I write only relies on those APIs. If I'm just using
Data.ByteString for the ByteString type and a few functions like readFile
and map, it's highly unlikely that the next version will introduce some
breaking change. In those cases, I've been leaving off the upper bound
entirely.

For other packages that haven't yet stabilized, I've still been keeping the
upper bound. In many cases, even that isn't necessary. I've tried removing
the upper bounds on those as well, but I almost always end up getting
someone filing a bug report that I left off some upper bound and therefore
a compile failed.

I agree with Bryan's argument, but I'd like to keep consistency for most
packages on Hackage. If the community goes in this direction, I'll go along
too.

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


Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread Michael Snoyman
On Tue, Jul 31, 2012 at 1:13 PM, Alexander Foremny
alexanderfore...@gmail.com wrote:
 Hello list,

 I am currently thinking that a problem of mine would best be solved if
 there was a Map-like data structure in which the value returned is
 parametrized over the lookup type.

 I wonder is this makes sense and if such a data structure exists or if
 it could be created while still being well typed. I essentially want
 to statically define a scope of Key values and dynamically define a
 list of keys.

 -- Scope of possible keys.
 type Label = String
 data Key a where
 KeyStr :: Label - Key String
 KeyInt :: Label - Key Int
 KeyChoice :: Label - [a] - Key a

 -- Some key values, to be extended at runtime.
 strKey Some String
 strKey' Another String
 intKey Some integer
 choiceKey Chose one [ a, b, c ] :: KeyChoice String

 Now I need a data structure to possibly associate a value to the key.

 data MapG = ...
 type Value a = a
 insert :: Key a - Value a - MapG Key Value - MapG Key Value
 lookup :: Key a - MapG Key Value - Maybe (Value a)

 I tried implementing this with multiple Map k a's. I tried adding a
 phantom type on some storage type of to implement KeyChoice as of type
 Key Int, but I ran into troubles with this approach. I wonder if
 Dynamic or Type Families could achieve this, but I am quite at a loss
 and would like to hear your opinion.

 I did try to search for this a bit, but I don't quite know how to
 phrase my problem. I'd like to apologize in advance if this question
 has been asked already.

 Regards,
 Alexander Foremny

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

I think you might be looking for something like vault[1].

HTH,
Michael

[1] http://hackage.haskell.org/package/vault

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


Re: [Haskell-cafe] ghci and TH cannot: unknown symbol `stat64`

2012-07-13 Thread Michael Snoyman
On Thu, Jul 12, 2012 at 7:30 PM, Tristan Ravitch travi...@cs.wisc.eduwrote:

 On Thu, Jul 12, 2012 at 07:20:39PM +0300, Michael Snoyman wrote:
  On Jul 12, 2012 7:13 PM, Tristan Ravitch travi...@cs.wisc.edu wrote:
  
   On Thu, Jul 12, 2012 at 11:07:05AM -0500, Tristan Ravitch wrote:
Are you trying this on a 32 bit system?  And when you compiled that C
program, did you try to add
   
  -D_FILE_OFFSET_BITS=64 -D_LARGEFILE64_SOURCE
   
to the compile command?  When I define those the resulting object
 file
from your example correctly references stat64 instead of stat.
  
   Er sorry, saw your earlier email now.  Could this be a mismatch
   between how your sqlite.so is compiled and how the cbits in
   persistent-sqlite are compiled, particularly with largefile support?
 
  I don't think so. The test case I put together had nothing to do with
  sqlite. Also, persistent-sqlite will either use sqlite.so _or_ the
 included
  sqlite3.c file (based on a compile-time flag). The former works
 perfectly,
  only the latter causes problems.
 
  Michael

 I was looking at the symbols in libc and noticed that it doesn't
 actually export stat64/stat, so that would explain something at least.
 I think your idea about the switch to function pointers versus direct
 calls is probably right - the linker probably does some rewriting of
 calls to stat into __fxstat and company, but for some reason doesn't
 handle references to function pointers.

 I also ran across this stackoverflow post that mentions something
 similar:


 http://stackoverflow.com/questions/5478780/c-and-ld-preload-open-and-open64-calls-intercepted-but-not-stat64

 So stat64 is actually special and in this libc_nonshared.a library (it
 is on my system at least).  It would be ugly to have to link that
 manually - not sure what the right answer is, but at least this might
 explain it.


That's a great find, and it really explains a lot. It seems then that:

* GNU ld has some black magic do know about the stat/stat64 hack.
* Compiling via GHC just uses GNU ld, which is able to make the hack work.
* Interpreting with GHC doesn't get to take advantage of GNU ld's hack.

I've opened a trac ticket[1] for this issue, thank you very much for the
help!

Michael

[1] http://hackage.haskell.org/trac/ghc/ticket/7072
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ghci and TH cannot: unknown symbol `stat64`

2012-07-12 Thread Michael Snoyman
On Wed, Jul 11, 2012 at 9:55 PM, Bardur Arantsson s...@scientician.netwrote:

 On 07/11/2012 05:12 PM, Michael Snoyman wrote:
 
  Thanks for the feedback. However, looking at sqlite3.c, I see the
  necessary #include statements:
 
  #include sys/types.h
  #include sys/stat.h
  #include unistd.h
 
  I'm confident that none of my code is making calls to stat/stat64 via
  the FFI. In case it makes a difference, this problem also disappears
  if I compile the library against the system copy of sqlite3 instead of
  using the C source.

 You may need some extra defines, see the comments in man stat64.

 Regards,


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


I've come up with a minimal example that demonstrates this problem. The
crux of the matter is the following C code:

#include sys/types.h
#include sys/stat.h
#include unistd.h
#include stdio.h

typedef int stat_func(const char*, struct stat*);

stat_func *foo = stat;

void stat_test(void)
{
struct stat buf;

printf(About to stat-test.c\n);
foo(stat-test.c, buf);
printf(Done\n);
}

As you can see, all of the include statements are present as necessary. The
code compiles just fine with -Wall -Werror. And when you compile the
Haskell code as well, everything works just fine. But if you follow these
steps, you can reproduce the error I saw:

* Unpack the attached tarball
* `cabal install` in that folder
* `runghc main.hs` from the `exe` folder

On my system at least, I get:

main.hs:
/home/ubuntu/.cabal/lib/stat-test-0.1.0.0/ghc-7.4.1/HSstat-test-0.1.0.0.o:
unknown symbol `stat'
main.hs: main.hs: unable to load package `stat-test-0.1.0.0'

One thing I noticed is that I needed to use a function pointer to trigger
the bug. When I called `stat` directly the in stat_test function, gcc
automatically inlined the call, so that the disassessmbled code just showed
a `moveq` (i.e., it's making the system call directly). But using a
function pointer, we're avoiding the inlining. I believe this is why this
issue only came up with the sqlite3 upgrade: previous versions did not use
a function pointer, but rather hard-coded in how to make a stat call.

Does this expose any other possibilities?

Michael


stat-test-0.1.0.0.tar.gz
Description: GNU Zip compressed data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ghci and TH cannot: unknown symbol `stat64`

2012-07-12 Thread Michael Snoyman
On Thu, Jul 12, 2012 at 6:29 PM, Michael Snoyman mich...@snoyman.comwrote:



 On Wed, Jul 11, 2012 at 9:55 PM, Bardur Arantsson s...@scientician.netwrote:

 On 07/11/2012 05:12 PM, Michael Snoyman wrote:
 
  Thanks for the feedback. However, looking at sqlite3.c, I see the
  necessary #include statements:
 
  #include sys/types.h
  #include sys/stat.h
  #include unistd.h
 
  I'm confident that none of my code is making calls to stat/stat64 via
  the FFI. In case it makes a difference, this problem also disappears
  if I compile the library against the system copy of sqlite3 instead of
  using the C source.

 You may need some extra defines, see the comments in man stat64.

 Regards,


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


 I've come up with a minimal example that demonstrates this problem. The
 crux of the matter is the following C code:

 #include sys/types.h
  #include sys/stat.h
 #include unistd.h
 #include stdio.h

 typedef int stat_func(const char*, struct stat*);

 stat_func *foo = stat;

 void stat_test(void)
 {
 struct stat buf;

 printf(About to stat-test.c\n);
 foo(stat-test.c, buf);
 printf(Done\n);
 }

 As you can see, all of the include statements are present as necessary.
 The code compiles just fine with -Wall -Werror. And when you compile the
 Haskell code as well, everything works just fine. But if you follow these
 steps, you can reproduce the error I saw:

 * Unpack the attached tarball
 * `cabal install` in that folder
 * `runghc main.hs` from the `exe` folder

 On my system at least, I get:

 main.hs:
 /home/ubuntu/.cabal/lib/stat-test-0.1.0.0/ghc-7.4.1/HSstat-test-0.1.0.0.o:
 unknown symbol `stat'
 main.hs: main.hs: unable to load package `stat-test-0.1.0.0'

 One thing I noticed is that I needed to use a function pointer to trigger
 the bug. When I called `stat` directly the in stat_test function, gcc
 automatically inlined the call, so that the disassessmbled code just showed
 a `moveq` (i.e., it's making the system call directly). But using a
 function pointer, we're avoiding the inlining. I believe this is why this
 issue only came up with the sqlite3 upgrade: previous versions did not use
 a function pointer, but rather hard-coded in how to make a stat call.

 Does this expose any other possibilities?

 Michael


Actually, I just came up with a workaround: declare some local wrappers to
the stat and fstat functions, and use those in place of stat and fstat in
the rest of the code. You can see the change here[1].

Obviously this is a hack, not a real fix. At this point it looks like a GHC
bug to me. Does anything think otherwise? If not, I'll open a ticket.

Michael

[1]
https://github.com/yesodweb/persistent/commit/d7daf0b2fa401fd97ef62e4e74228146d15d8601
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ghci and TH cannot: unknown symbol `stat64`

2012-07-12 Thread Michael Snoyman
On Thu, Jul 12, 2012 at 7:07 PM, Tristan Ravitch travi...@cs.wisc.eduwrote:

 On Thu, Jul 12, 2012 at 06:29:41PM +0300, Michael Snoyman wrote:
  I've come up with a minimal example that demonstrates this problem. The
  crux of the matter is the following C code:
 
  #include sys/types.h
  #include sys/stat.h
  #include unistd.h
  #include stdio.h
 
  typedef int stat_func(const char*, struct stat*);
 
  stat_func *foo = stat;
 
  void stat_test(void)
  {
  struct stat buf;
 
  printf(About to stat-test.c\n);
  foo(stat-test.c, buf);
  printf(Done\n);
  }
 
  As you can see, all of the include statements are present as necessary.
 The
  code compiles just fine with -Wall -Werror. And when you compile the
  Haskell code as well, everything works just fine. But if you follow these
  steps, you can reproduce the error I saw:
 
  * Unpack the attached tarball
  * `cabal install` in that folder
  * `runghc main.hs` from the `exe` folder
 
  On my system at least, I get:
 
  main.hs:
 
 /home/ubuntu/.cabal/lib/stat-test-0.1.0.0/ghc-7.4.1/HSstat-test-0.1.0.0.o:
  unknown symbol `stat'
  main.hs: main.hs: unable to load package `stat-test-0.1.0.0'
 
  One thing I noticed is that I needed to use a function pointer to trigger
  the bug. When I called `stat` directly the in stat_test function, gcc
  automatically inlined the call, so that the disassessmbled code just
 showed
  a `moveq` (i.e., it's making the system call directly). But using a
  function pointer, we're avoiding the inlining. I believe this is why this
  issue only came up with the sqlite3 upgrade: previous versions did not
 use
  a function pointer, but rather hard-coded in how to make a stat call.
 
  Does this expose any other possibilities?
 
  Michael

 Are you trying this on a 32 bit system?  And when you compiled that C
 program, did you try to add

   -D_FILE_OFFSET_BITS=64 -D_LARGEFILE64_SOURCE

 to the compile command?  When I define those the resulting object file
 from your example correctly references stat64 instead of stat.


I'm compiling on a 64 bit system. If I add those definitions, the program
uses stat64 instead, but the only difference is that runghc now prints:

main.hs:
/home/ubuntu/.cabal/lib/stat-test-0.1.0.0/ghc-7.4.1/HSstat-test-0.1.0.0.o:
unknown symbol `stat64'
main.hs: main.hs: unable to load package `stat-test-0.1.0.0'

In other words, it's not the symbol that the object file is referencing
(stat vs stat64) that's the problem: runghc is not able to resolve either
one.

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


Re: [Haskell-cafe] ghci and TH cannot: unknown symbol `stat64`

2012-07-12 Thread Michael Snoyman
On Jul 12, 2012 7:13 PM, Tristan Ravitch travi...@cs.wisc.edu wrote:

 On Thu, Jul 12, 2012 at 11:07:05AM -0500, Tristan Ravitch wrote:
  Are you trying this on a 32 bit system?  And when you compiled that C
  program, did you try to add
 
-D_FILE_OFFSET_BITS=64 -D_LARGEFILE64_SOURCE
 
  to the compile command?  When I define those the resulting object file
  from your example correctly references stat64 instead of stat.

 Er sorry, saw your earlier email now.  Could this be a mismatch
 between how your sqlite.so is compiled and how the cbits in
 persistent-sqlite are compiled, particularly with largefile support?

I don't think so. The test case I put together had nothing to do with
sqlite. Also, persistent-sqlite will either use sqlite.so _or_ the included
sqlite3.c file (based on a compile-time flag). The former works perfectly,
only the latter causes problems.

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


[Haskell-cafe] ghci and TH cannot: unknown symbol `stat64`

2012-07-11 Thread Michael Snoyman
Hi all,

A quick search indicates that this problem has come up in the past,
but I haven't seen any solutions yet. I'm working on the next
Persistent release, and one of the changes is that the included
sqlite3 C library has been updated (I believe that's the trigger
here). I can compile programs against persistent-sqlite, but if
there's TH code involved, or I try to runghc the file, I get an error
message like:

test.hs: 
/home/ubuntu/.cabal/lib/persistent-sqlite-1.0.0/ghc-7.4.1/HSpersistent-sqlite-1.0.0.o:
unknown symbol `stat64'
test.hs: test.hs: unable to load package `persistent-sqlite-1.0.0'

I'm running GHC 7.4.1 on Ubuntu 12.04 64-bit. Does anyone have insight
into what might be causing this?

Thanks,
Michael

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


Re: [Haskell-cafe] ghci and TH cannot: unknown symbol `stat64`

2012-07-11 Thread Michael Snoyman
On Wed, Jul 11, 2012 at 5:47 PM, Brandon Allbery allber...@gmail.com wrote:
 On Wed, Jul 11, 2012 at 10:25 AM, Michael Snoyman mich...@snoyman.com
 wrote:

 test.hs:
 /home/ubuntu/.cabal/lib/persistent-sqlite-1.0.0/ghc-7.4.1/HSpersistent-sqlite-1.0.0.o:
 unknown symbol `stat64'
 test.hs: test.hs: unable to load package `persistent-sqlite-1.0.0'


 The immediate cause is that some C source file is calling stat() or lstat()
 without the right #include files; they go through several levels of backward
 compatibility macros that end in different system calls.  Alternately,
 something is trying to use one of those functions via the FFI instead of
 System.Posix.File.

 --
 brandon s allbery  allber...@gmail.com
 wandering unix systems administrator (available) (412) 475-9364 vm/sms


Hi Brandon,

Thanks for the feedback. However, looking at sqlite3.c, I see the
necessary #include statements:

#include sys/types.h
#include sys/stat.h
#include unistd.h

I'm confident that none of my code is making calls to stat/stat64 via
the FFI. In case it makes a difference, this problem also disappears
if I compile the library against the system copy of sqlite3 instead of
using the C source.

Michael

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


  1   2   3   4   5   6   7   >