From m.farkasdyck at gmail.com Mon Aug 3 06:47:58 2015 From: m.farkasdyck at gmail.com (M Farkas-Dyck) Date: Sun, 2 Aug 2015 22:47:58 -0800 Subject: Proposal: Allow arr =?utf-8?B?4oinIChmaXJz?= =?utf-8?B?dCDiiKg=?= (***)) as minimal definition of Arrow instance Message-ID: <55bf0b2e.2a80460a.9875.ffffc91b@mx.google.com> Add default definitions of first, second in terms of (***) to let one define an Arrow instance in terms of (***) rather than first, which is sometimes more elegant or convenient. To my knowledge this can not break any code. GHC ticket: 10216 From ryan.gl.scott at gmail.com Mon Aug 3 15:42:41 2015 From: ryan.gl.scott at gmail.com (Ryan Scott) Date: Mon, 3 Aug 2015 10:42:41 -0500 Subject: Proposal: instance MonadIO Q Message-ID: Since almost two weeks have passed since I originally started this thread, I'd be willing to submit patches which would 1. Move MonadIO from transformers to base 2. Introduce a MonadIO Q instance I'm not sure what the etiquette for #1 is, however, since that would require a change to a GHC dependency (transformers). Should I first submit a patch that hides Control.Monad.IO.Class from GHC's transformers fork if impl(ghc >= 7.11) (similar to this commit [1]), and then submit an additional patch that adds Control.Monad.IO.Class to base? Or would it suffice to do both in one go? Ryan ----- [1] http://git.haskell.org/packages/transformers.git/commitdiff/refs/heads/wip/T9664 From blamario at ciktel.net Mon Aug 3 17:22:56 2015 From: blamario at ciktel.net (=?UTF-8?B?TWFyaW8gQmxhxb5ldmnEhw==?=) Date: Mon, 03 Aug 2015 13:22:56 -0400 Subject: Proposal: newtype for applicatives of monoids In-Reply-To: References: Message-ID: <55BFA370.8090600@ciktel.net> On 07/26/2015 11:34 PM, David Feuer wrote: > > Sorry for the terrible title, but I think we should add something like > the following to Data.Monoid (I already mentioned this in the > discussion of a Monoid instance for ZipList). > > newtype Appl f m = Appl (f m) > > instance (Applicative f, Monoid m) => Monoid (Appl f m) where > mempty = Appl $ pure mempty > mplus (Appl x) (Appl y) = Appl $ liftA2 mplus x y > The method is called mappend, not mplus. Otherwise +1. > It may be possible to use coercions to improve mplus; I haven't tried it. > > This type is the same as WrappedApplicative from semigroupoids, do it > might be best just to give it that name. > The name Appl is the best fit with the recently-added Alt newtype, so I prefer it. From cma at bitemyapp.com Mon Aug 3 17:30:24 2015 From: cma at bitemyapp.com (Christopher Allen) Date: Mon, 3 Aug 2015 12:30:24 -0500 Subject: Proposal: newtype for applicatives of monoids In-Reply-To: References: Message-ID: Might as well capture all of 'em in one go. +1 w/ aforementioned mappend/mplus fix. On Sun, Jul 26, 2015 at 10:34 PM, David Feuer wrote: > Sorry for the terrible title, but I think we should add something like the > following to Data.Monoid (I already mentioned this in the discussion of a > Monoid instance for ZipList). > > newtype Appl f m = Appl (f m) > > instance (Applicative f, Monoid m) => Monoid (Appl f m) where > mempty = Appl $ pure mempty > mplus (Appl x) (Appl y) = Appl $ liftA2 mplus x y > > It may be possible to use coercions to improve mplus; I haven't tried it. > > This type is the same as WrappedApplicative from semigroupoids, do it > might be best just to give it that name. > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > -- Chris Allen Currently working on http://haskellbook.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From johnw at newartisans.com Mon Aug 3 17:58:03 2015 From: johnw at newartisans.com (John Wiegley) Date: Mon, 03 Aug 2015 10:58:03 -0700 Subject: Proposal: newtype for applicatives of monoids In-Reply-To: (Christopher Allen's message of "Mon, 3 Aug 2015 12:30:24 -0500") References: Message-ID: >>>>> Christopher Allen writes: > Might as well capture all of 'em in one go. > +1 w/ aforementioned mappend/mplus fix. +1 John From ekmett at gmail.com Mon Aug 3 19:10:52 2015 From: ekmett at gmail.com (Edward Kmett) Date: Mon, 3 Aug 2015 15:10:52 -0400 Subject: [core libraries] Re: mapM /= traverse? In-Reply-To: <87a8u8xrfw.fsf@smart-cactus.org> References: <5550FFEF.1000806@gmail.com> <5551B2BC.9050806@gmail.com> <87a8u8xrfw.fsf@smart-cactus.org> Message-ID: At the very least, it does seem like we're going to need to do a broader survey of the instances out there, as well as fix a lot more Applicative instances to have a better (*>) first as well as thoroughly document what to do, if we want to proceed on this front. If we ultimately want to remove mapM from the class to get it a more permissive type signature, and get mapM_ from Foldable to have the more general signature to boot, then we'll need to figure out how to address these concerns. It still strikes me as the right general direction to go in, but this is troubling. -Edward On Mon, Aug 3, 2015 at 12:33 PM, Ben Gamari wrote: > Edward Kmett writes: > > > On Tue, May 12, 2015 at 3:58 AM, Simon Marlow > wrote: > > > >> > >> Yes, I'm not really concerned that mapM is a method of Traversable > rather > >> than just being an alias for traverse, but I'm wondering why we define > it > >> in the list instance rather than using the default. > >> > > > > We were pretty paranoid about introducing space or time regressions and > > didn't have a proof that we wouldn't introduce them by changing something > > there, so we left it alone. > > > On a related note, D924 [1] proposed that mapM_ be redefined in > terms of traverse_. Unfortunately at least one monad in GHC itself was > adversely affected [2] by this change, resulting in non-linear complexity > in > a previously well-behaved function (a minimal demonstration of this can > be found below). > > We discussed this in the GHC weekly meeting and felt that we should > ensure that the libraries group was aware of this issue. > > Cheers, > > - Ben > > > [1] https://phabricator.haskell.org/D924 > [2] https://ghc.haskell.org/trac/ghc/ticket/10711 > [3] Demonstration of regression in complexity of mapM_ when expressed in > terms of `traverse_`, > > {{{ > module Main where > > import Control.Monad hiding (mapM_) > import Prelude hiding (mapM_) > > -- | Testcase derived from Assembler monad in ByteCodeAsm > data Assembler a > = Thing Int (Int -> Assembler a) > | Pure a > > instance Functor Assembler where > fmap = liftM > > instance Applicative Assembler where > pure = return > (<*>) = ap > > instance Monad Assembler where > return = Pure > Pure x >>= f = f x > Thing i k >>= f = Thing i (k >=> f) > > -- This is traverse_ > mapA_ :: (Foldable t, Monad f) => (a -> f b) -> t a -> f () > mapA_ f = foldr ((*>) . f) (pure ()) > > -- This is the current definition > mapM_ :: (Foldable t, Monad f) => (a -> f b) -> t a -> f () > mapM_ f = foldr ((>>) . f) (pure ()) > > test = map (\i->Thing i (const $ return 2)) [0..10000] > > doTestM = mapM_ id test > doTestA = mapA_ id test > > run :: Assembler a -> a > run (Thing i f) = run (f i) > run (Pure r) = r > {-# NOINLINE run #-} > > main :: IO () > main = print $ run doTestM > }}} > > -- > You received this message because you are subscribed to the Google Groups > "haskell-core-libraries" group. > To unsubscribe from this group and stop receiving emails from it, send an > email to haskell-core-libraries+unsubscribe at googlegroups.com. > For more options, visit https://groups.google.com/d/optout. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Mon Aug 3 19:14:25 2015 From: ekmett at gmail.com (Edward Kmett) Date: Mon, 3 Aug 2015 15:14:25 -0400 Subject: Proposal: newtype for applicatives of monoids In-Reply-To: References: Message-ID: To offer a couple more colors for the bikeshed: In my old monoids package, this exists as App: http://hackage.haskell.org/package/monoids-0.3.2/docs/Data-Monoid-Applicative.html In the newer reducers package, it has been shortened to Ap: http://hackage.haskell.org/package/reducers-3.10.3.2/docs/Data-Semigroup-Applicative.html -Edward On Mon, Aug 3, 2015 at 1:58 PM, John Wiegley wrote: > >>>>> Christopher Allen writes: > > > Might as well capture all of 'em in one go. > > +1 w/ aforementioned mappend/mplus fix. > > +1 > > John > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From spam at scientician.net Mon Aug 3 20:08:01 2015 From: spam at scientician.net (Bardur Arantsson) Date: Mon, 3 Aug 2015 22:08:01 +0200 Subject: Proposal: newtype for applicatives of monoids In-Reply-To: References: Message-ID: On 08/03/2015 09:14 PM, Edward Kmett wrote: > To offer a couple more colors for the bikeshed: > > In my old monoids package, this exists as App: > > http://hackage.haskell.org/package/monoids-0.3.2/docs/Data-Monoid-Applicative.html > > In the newer reducers package, it has been shortened to Ap: > > http://hackage.haskell.org/package/reducers-3.10.3.2/docs/Data-Semigroup-Applicative.html > It *must* be App because apps are cool! ... I think? Regards, From casper at unbc.ca Mon Aug 3 20:29:01 2015 From: casper at unbc.ca (David Casperson) Date: Mon, 3 Aug 2015 13:29:01 -0700 (PDT) Subject: Proposal: newtype for applicatives of monoids In-Reply-To: <55BFA370.8090600@ciktel.net> References: <55BFA370.8090600@ciktel.net> Message-ID: On 2015-08-03, Mario Bla?evi? wrote: > Date: Mon, 3 Aug 2015 10:22:56 > From: Mario Bla?evi? > To: libraries at haskell.org > Subject: Re: Proposal: newtype for applicatives of monoids > > On 07/26/2015 11:34 PM, David Feuer wrote: >> >> Sorry for the terrible title, but I think we should add something like the >> following to Data.Monoid (I already mentioned this in the discussion of a >> Monoid instance for ZipList). >> >> newtype Appl f m = Appl (f m) >> >> instance (Applicative f, Monoid m) => Monoid (Appl f m) where >> mempty = Appl $ pure mempty >> mplus (Appl x) (Appl y) = Appl $ liftA2 mplus x y >> > > The method is called mappend, not mplus. Otherwise +1. > > >> It may be possible to use coercions to improve mplus; I haven't tried it. >> >> This type is the same as WrappedApplicative from semigroupoids, do it might >> be best just to give it that name. +1, with mappend. (I just tripped over the Monad instance of the same thing. It's very nice to be able to use (<>) on something like Monad m => Control.Monad.Trans.Exception m ()?.) Cheers, David -- David Casperson, PhD, R.P., | David.Casperson at unbc.ca Associate Professor and Chair, | (250) 960-6672 Fax 960-5544 Computer Science | 3333 University Way University of Northern British Columbia | Prince George, BC V2N 4Z9 | CANADA From david.feuer at gmail.com Mon Aug 3 20:31:59 2015 From: david.feuer at gmail.com (David Feuer) Date: Mon, 3 Aug 2015 16:31:59 -0400 Subject: Proposal: newtype for applicatives of monoids In-Reply-To: References: Message-ID: I don't want to take App because it's probably the most popular name for representing function application in ASTs. On Aug 3, 2015 3:14 PM, "Edward Kmett" wrote: > To offer a couple more colors for the bikeshed: > > In my old monoids package, this exists as App: > > > http://hackage.haskell.org/package/monoids-0.3.2/docs/Data-Monoid-Applicative.html > > In the newer reducers package, it has been shortened to Ap: > > > http://hackage.haskell.org/package/reducers-3.10.3.2/docs/Data-Semigroup-Applicative.html > > -Edward > > On Mon, Aug 3, 2015 at 1:58 PM, John Wiegley > wrote: > >> >>>>> Christopher Allen writes: >> >> > Might as well capture all of 'em in one go. >> > +1 w/ aforementioned mappend/mplus fix. >> >> +1 >> >> John >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Mon Aug 3 23:05:03 2015 From: david.feuer at gmail.com (David Feuer) Date: Mon, 3 Aug 2015 19:05:03 -0400 Subject: [core libraries] Re: mapM /= traverse? In-Reply-To: References: <5550FFEF.1000806@gmail.com> <5551B2BC.9050806@gmail.com> <87a8u8xrfw.fsf@smart-cactus.org> Message-ID: I seem to remember running into this way back, but not being able to figure out which instance was broken. Glad to see someone tracked it down. On Aug 3, 2015 3:10 PM, "Edward Kmett" wrote: > At the very least, it does seem like we're going to need to do a broader > survey of the instances out there, as well as fix a lot more Applicative > instances to have a better (*>) first as well as thoroughly document what > to do, if we want to proceed on this front. > > If we ultimately want to remove mapM from the class to get it a more > permissive type signature, and get mapM_ from Foldable to have the more > general signature to boot, then we'll need to figure out how to address > these concerns. > > It still strikes me as the right general direction to go in, but this is > troubling. > > -Edward > > On Mon, Aug 3, 2015 at 12:33 PM, Ben Gamari wrote: > >> Edward Kmett writes: >> >> > On Tue, May 12, 2015 at 3:58 AM, Simon Marlow >> wrote: >> > >> >> >> >> Yes, I'm not really concerned that mapM is a method of Traversable >> rather >> >> than just being an alias for traverse, but I'm wondering why we define >> it >> >> in the list instance rather than using the default. >> >> >> > >> > We were pretty paranoid about introducing space or time regressions and >> > didn't have a proof that we wouldn't introduce them by changing >> something >> > there, so we left it alone. >> > >> On a related note, D924 [1] proposed that mapM_ be redefined in >> terms of traverse_. Unfortunately at least one monad in GHC itself was >> adversely affected [2] by this change, resulting in non-linear complexity >> in >> a previously well-behaved function (a minimal demonstration of this can >> be found below). >> >> We discussed this in the GHC weekly meeting and felt that we should >> ensure that the libraries group was aware of this issue. >> >> Cheers, >> >> - Ben >> >> >> [1] https://phabricator.haskell.org/D924 >> [2] https://ghc.haskell.org/trac/ghc/ticket/10711 >> [3] Demonstration of regression in complexity of mapM_ when expressed in >> terms of `traverse_`, >> >> {{{ >> module Main where >> >> import Control.Monad hiding (mapM_) >> import Prelude hiding (mapM_) >> >> -- | Testcase derived from Assembler monad in ByteCodeAsm >> data Assembler a >> = Thing Int (Int -> Assembler a) >> | Pure a >> >> instance Functor Assembler where >> fmap = liftM >> >> instance Applicative Assembler where >> pure = return >> (<*>) = ap >> >> instance Monad Assembler where >> return = Pure >> Pure x >>= f = f x >> Thing i k >>= f = Thing i (k >=> f) >> >> -- This is traverse_ >> mapA_ :: (Foldable t, Monad f) => (a -> f b) -> t a -> f () >> mapA_ f = foldr ((*>) . f) (pure ()) >> >> -- This is the current definition >> mapM_ :: (Foldable t, Monad f) => (a -> f b) -> t a -> f () >> mapM_ f = foldr ((>>) . f) (pure ()) >> >> test = map (\i->Thing i (const $ return 2)) [0..10000] >> >> doTestM = mapM_ id test >> doTestA = mapA_ id test >> >> run :: Assembler a -> a >> run (Thing i f) = run (f i) >> run (Pure r) = r >> {-# NOINLINE run #-} >> >> main :: IO () >> main = print $ run doTestM >> }}} >> >> -- >> You received this message because you are subscribed to the Google Groups >> "haskell-core-libraries" group. >> To unsubscribe from this group and stop receiving emails from it, send an >> email to haskell-core-libraries+unsubscribe at googlegroups.com. >> For more options, visit https://groups.google.com/d/optout. >> > > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Tue Aug 4 03:21:01 2015 From: david.feuer at gmail.com (David Feuer) Date: Mon, 3 Aug 2015 23:21:01 -0400 Subject: Proposal: newtype for applicatives of monoids In-Reply-To: References: Message-ID: Ap seems a good name, and it's already used for that, so I'd support that bike shed color. On Aug 3, 2015 3:14 PM, "Edward Kmett" wrote: > To offer a couple more colors for the bikeshed: > > In my old monoids package, this exists as App: > > > http://hackage.haskell.org/package/monoids-0.3.2/docs/Data-Monoid-Applicative.html > > In the newer reducers package, it has been shortened to Ap: > > > http://hackage.haskell.org/package/reducers-3.10.3.2/docs/Data-Semigroup-Applicative.html > > -Edward > > On Mon, Aug 3, 2015 at 1:58 PM, John Wiegley > wrote: > >> >>>>> Christopher Allen writes: >> >> > Might as well capture all of 'em in one go. >> > +1 w/ aforementioned mappend/mplus fix. >> >> +1 >> >> John >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From andreas.abel at ifi.lmu.de Wed Aug 5 09:15:45 2015 From: andreas.abel at ifi.lmu.de (Andreas Abel) Date: Wed, 05 Aug 2015 11:15:45 +0200 Subject: Proposal: newtype for applicatives of monoids In-Reply-To: References: Message-ID: <55C1D441.1070509@ifi.lmu.de> +1 to Ap. On 04.08.2015 05:21, David Feuer wrote: > Ap seems a good name, and it's already used for that, so I'd support > that bike shed color. > > On Aug 3, 2015 3:14 PM, "Edward Kmett" > wrote: > > To offer a couple more colors for the bikeshed: > > In my old monoids package, this exists as App: > > http://hackage.haskell.org/package/monoids-0.3.2/docs/Data-Monoid-Applicative.html > > In the newer reducers package, it has been shortened to Ap: > > http://hackage.haskell.org/package/reducers-3.10.3.2/docs/Data-Semigroup-Applicative.html > > -Edward > > On Mon, Aug 3, 2015 at 1:58 PM, John Wiegley > wrote: > > >>>>> Christopher Allen > writes: > > > Might as well capture all of 'em in one go. > > +1 w/ aforementioned mappend/mplus fix. > > +1 > > John > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -- Andreas Abel <>< Du bist der geliebte Mensch. Department of Computer Science and Engineering Chalmers and Gothenburg University, Sweden andreas.abel at gu.se http://www2.tcs.ifi.lmu.de/~abel/ From oleg.grenrus at iki.fi Wed Aug 5 10:01:55 2015 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Wed, 5 Aug 2015 13:01:55 +0300 Subject: Proposal: newtype for applicatives of monoids In-Reply-To: <55C1D441.1070509@ifi.lmu.de> References: <55C1D441.1070509@ifi.lmu.de> Message-ID: <0F7F8B2F-9DA2-4B87-BD05-0EE057B4E97D@iki.fi> There is also http://hackage.haskell.org/package/free-4.12.1/docs/Control-Applicative-Free.html#t:Ap , which is totally different thing, yet related to Applicative. reducers Ap has getApp field name, which is probably copy&paste mistake: http://hackage.haskell.org/package/reducers-3.10.3.2/docs/Data-Semigroup-Applicative.html#t:Ap In that light I?d prefer - Appl with getAppl, - Ap unchanged in free package - App left free > On 05 Aug 2015, at 12:15, Andreas Abel wrote: > > +1 to Ap. > > On 04.08.2015 05:21, David Feuer wrote: >> Ap seems a good name, and it's already used for that, so I'd support >> that bike shed color. >> >> On Aug 3, 2015 3:14 PM, "Edward Kmett" > > wrote: >> >> To offer a couple more colors for the bikeshed: >> >> In my old monoids package, this exists as App: >> >> http://hackage.haskell.org/package/monoids-0.3.2/docs/Data-Monoid-Applicative.html >> >> In the newer reducers package, it has been shortened to Ap: >> >> http://hackage.haskell.org/package/reducers-3.10.3.2/docs/Data-Semigroup-Applicative.html >> >> -Edward >> >> On Mon, Aug 3, 2015 at 1:58 PM, John Wiegley > > wrote: >> >> >>>>> Christopher Allen > writes: >> >> > Might as well capture all of 'em in one go. >> > +1 w/ aforementioned mappend/mplus fix. >> >> +1 >> >> John >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > > > -- > Andreas Abel <>< Du bist der geliebte Mensch. > > Department of Computer Science and Engineering > Chalmers and Gothenburg University, Sweden > > andreas.abel at gu.se > http://www2.tcs.ifi.lmu.de/~abel/ > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 842 bytes Desc: Message signed with OpenPGP using GPGMail URL: From petr.mvd at gmail.com Wed Aug 12 08:09:52 2015 From: petr.mvd at gmail.com (=?UTF-8?B?UGV0ciBQdWRsw6Fr?=) Date: Wed, 12 Aug 2015 08:09:52 +0000 Subject: Proposal: newtype for applicatives of monoids In-Reply-To: References: Message-ID: IIRC the accessor is still called getApp in reducers, which is slightly inconsistent. Perhaps it'd be worth fixing on some future release that will bring other incompatible changes. Thanks Petr Dne po 3. 8. 2015 21:14 u?ivatel Edward Kmett napsal: To offer a couple more colors for the bikeshed: In my old monoids package, this exists as App: http://hackage.haskell.org/package/monoids-0.3.2/docs/Data-Monoid-Applicative.html In the newer reducers package, it has been shortened to Ap: http://hackage.haskell.org/package/reducers-3.10.3.2/docs/Data-Semigroup-Applicative.html -Edward On Mon, Aug 3, 2015 at 1:58 PM, John Wiegley wrote: >>>>> Christopher Allen writes: > Might as well capture all of 'em in one go. > +1 w/ aforementioned mappend/mplus fix. +1 John _______________________________________________ Libraries mailing list Libraries at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________ Libraries mailing list Libraries at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Wed Aug 12 15:54:29 2015 From: ekmett at gmail.com (Edward Kmett) Date: Wed, 12 Aug 2015 11:54:29 -0400 Subject: Proposal: newtype for applicatives of monoids In-Reply-To: References: Message-ID: It was fixed in HEAD for a while. I've now shipped that fix as part of 3.11. -Edward On Wed, Aug 12, 2015 at 4:09 AM, Petr Pudl?k wrote: > IIRC the accessor is still called getApp in reducers, which is slightly > inconsistent. Perhaps it'd be worth fixing on some future release that will > bring other incompatible changes. > > Thanks > Petr > > Dne po 3. 8. 2015 21:14 u?ivatel Edward Kmett napsal: > > To offer a couple more colors for the bikeshed: > > In my old monoids package, this exists as App: > > > http://hackage.haskell.org/package/monoids-0.3.2/docs/Data-Monoid-Applicative.html > > In the newer reducers package, it has been shortened to Ap: > > > http://hackage.haskell.org/package/reducers-3.10.3.2/docs/Data-Semigroup-Applicative.html > > -Edward > > On Mon, Aug 3, 2015 at 1:58 PM, John Wiegley > wrote: > > >>>>> Christopher Allen writes: > > > Might as well capture all of 'em in one go. > > +1 w/ aforementioned mappend/mplus fix. > > +1 > > John > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From petr.mvd at gmail.com Wed Aug 12 16:03:30 2015 From: petr.mvd at gmail.com (=?UTF-8?B?UGV0ciBQdWRsw6Fr?=) Date: Wed, 12 Aug 2015 16:03:30 +0000 Subject: Proposal: newtype for applicatives of monoids In-Reply-To: References: Message-ID: Thanks! Petr Dne st 12. 8. 2015 17:54 u?ivatel Edward Kmett napsal: > It was fixed in HEAD for a while. I've now shipped that fix as part of > 3.11. > > -Edward > > On Wed, Aug 12, 2015 at 4:09 AM, Petr Pudl?k wrote: > >> IIRC the accessor is still called getApp in reducers, which is slightly >> inconsistent. Perhaps it'd be worth fixing on some future release that will >> bring other incompatible changes. >> >> Thanks >> Petr >> >> Dne po 3. 8. 2015 21:14 u?ivatel Edward Kmett napsal: >> >> To offer a couple more colors for the bikeshed: >> >> In my old monoids package, this exists as App: >> >> >> http://hackage.haskell.org/package/monoids-0.3.2/docs/Data-Monoid-Applicative.html >> >> In the newer reducers package, it has been shortened to Ap: >> >> >> http://hackage.haskell.org/package/reducers-3.10.3.2/docs/Data-Semigroup-Applicative.html >> >> -Edward >> >> On Mon, Aug 3, 2015 at 1:58 PM, John Wiegley >> wrote: >> >> >>>>> Christopher Allen writes: >> >> > Might as well capture all of 'em in one go. >> > +1 w/ aforementioned mappend/mplus fix. >> >> +1 >> >> John >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From dan.doel at gmail.com Wed Aug 12 16:14:33 2015 From: dan.doel at gmail.com (Dan Doel) Date: Wed, 12 Aug 2015 12:14:33 -0400 Subject: IsString [Char] instance In-Reply-To: References: Message-ID: So, I rather lost track of this. It has been (significantly) more than the specified amount of time, though. No one has stepped up to specify/implement the new extended defaulting to my knowledge. I'm not sure how much time is left before 7.12, but I would guess it'd be tight for someone to start on this now. Perhaps I'm wrong. Anyhow, I think we should modify the instance at this point. I think it's even cool to say we can roll it back if someone decides to beef up defaulting, in which case rolling it back should cause no regressions. But it doesn't seem like defaulting is going to happen. -- Dan On Sun, May 17, 2015 at 8:08 PM, Dan Doel wrote: > Greetings, > > Today, someone came into #haskell and asked why they couldn't type the > equivalent of: > > > "hi" ++ "bye" > > into GHCi with OverloadedStrings enabled. The answer is that it's ambiguous, > because (++) only determines the strings to be [a], and not [Char]. > > I noticed that this could actually be solved by making the instance: > > instance (a ~ Char) => IsString [a] where ... > > Which causes [Char] to be inferred as soon as [a] is. I then searched my > libraries mail and noticed that we'd discussed this two years ago. The > proposal for this instance change was rejected based on ExtendedDefaultRules > being beefed up to solve this case. But then no one actually implemented the > better defaulting. > > So, I'm proposing that the issue be fixed for real. I'm not terribly > concerned with how it gets fixed, but there's not a great reason for this to > not behave better than it currently does. If someone steps up and makes > defaulting better, than that's great. But if not, then the libraries > committee can fix this very easily for GHC 7.12, and I think it's better to > do so than to wait if there are no signs that the alternative is going to > happen. > > I don't think we need to nail down which of the two solutions we're going to > choose right now, but it'd be good to resolve that we're going to fix it, > one way or another, by some well defined date. > > Here's a link to the previous discussion: > > http://comments.gmane.org/gmane.comp.lang.haskell.libraries/20088 > > Discussion period: 2 weeks > > -- Dan From ekmett at gmail.com Thu Aug 13 03:44:59 2015 From: ekmett at gmail.com (Edward Kmett) Date: Wed, 12 Aug 2015 23:44:59 -0400 Subject: IsString [Char] instance In-Reply-To: References: Message-ID: I'm fully on board with just moving ahead with this simple change for now. It'd be nice to have a better defaulting story, but I'm not sure there _is_ a perfect solution in the wings. -Edward On Wed, Aug 12, 2015 at 12:14 PM, Dan Doel wrote: > So, I rather lost track of this. It has been (significantly) more than > the specified amount of time, though. > > No one has stepped up to specify/implement the new extended defaulting > to my knowledge. I'm not sure how much time is left before 7.12, but I > would guess it'd be tight for someone to start on this now. Perhaps > I'm wrong. > > Anyhow, I think we should modify the instance at this point. I think > it's even cool to say we can roll it back if someone decides to beef > up defaulting, in which case rolling it back should cause no > regressions. But it doesn't seem like defaulting is going to happen. > > -- Dan > > On Sun, May 17, 2015 at 8:08 PM, Dan Doel wrote: > > Greetings, > > > > Today, someone came into #haskell and asked why they couldn't type the > > equivalent of: > > > > > "hi" ++ "bye" > > > > into GHCi with OverloadedStrings enabled. The answer is that it's > ambiguous, > > because (++) only determines the strings to be [a], and not [Char]. > > > > I noticed that this could actually be solved by making the instance: > > > > instance (a ~ Char) => IsString [a] where ... > > > > Which causes [Char] to be inferred as soon as [a] is. I then searched my > > libraries mail and noticed that we'd discussed this two years ago. The > > proposal for this instance change was rejected based on > ExtendedDefaultRules > > being beefed up to solve this case. But then no one actually implemented > the > > better defaulting. > > > > So, I'm proposing that the issue be fixed for real. I'm not terribly > > concerned with how it gets fixed, but there's not a great reason for > this to > > not behave better than it currently does. If someone steps up and makes > > defaulting better, than that's great. But if not, then the libraries > > committee can fix this very easily for GHC 7.12, and I think it's better > to > > do so than to wait if there are no signs that the alternative is going to > > happen. > > > > I don't think we need to nail down which of the two solutions we're > going to > > choose right now, but it'd be good to resolve that we're going to fix it, > > one way or another, by some well defined date. > > > > Here's a link to the previous discussion: > > > > http://comments.gmane.org/gmane.comp.lang.haskell.libraries/20088 > > > > Discussion period: 2 weeks > > > > -- Dan > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Thu Aug 13 03:47:54 2015 From: michael at snoyman.com (Michael Snoyman) Date: Thu, 13 Aug 2015 06:47:54 +0300 Subject: IsString [Char] instance In-Reply-To: References: Message-ID: I'm in favor of this as well. On Thu, Aug 13, 2015 at 6:44 AM, Edward Kmett wrote: > I'm fully on board with just moving ahead with this simple change for now. > It'd be nice to have a better defaulting story, but I'm not sure there _is_ > a perfect solution in the wings. > > -Edward > > On Wed, Aug 12, 2015 at 12:14 PM, Dan Doel wrote: > >> So, I rather lost track of this. It has been (significantly) more than >> the specified amount of time, though. >> >> No one has stepped up to specify/implement the new extended defaulting >> to my knowledge. I'm not sure how much time is left before 7.12, but I >> would guess it'd be tight for someone to start on this now. Perhaps >> I'm wrong. >> >> Anyhow, I think we should modify the instance at this point. I think >> it's even cool to say we can roll it back if someone decides to beef >> up defaulting, in which case rolling it back should cause no >> regressions. But it doesn't seem like defaulting is going to happen. >> >> -- Dan >> >> On Sun, May 17, 2015 at 8:08 PM, Dan Doel wrote: >> > Greetings, >> > >> > Today, someone came into #haskell and asked why they couldn't type the >> > equivalent of: >> > >> > > "hi" ++ "bye" >> > >> > into GHCi with OverloadedStrings enabled. The answer is that it's >> ambiguous, >> > because (++) only determines the strings to be [a], and not [Char]. >> > >> > I noticed that this could actually be solved by making the instance: >> > >> > instance (a ~ Char) => IsString [a] where ... >> > >> > Which causes [Char] to be inferred as soon as [a] is. I then searched my >> > libraries mail and noticed that we'd discussed this two years ago. The >> > proposal for this instance change was rejected based on >> ExtendedDefaultRules >> > being beefed up to solve this case. But then no one actually >> implemented the >> > better defaulting. >> > >> > So, I'm proposing that the issue be fixed for real. I'm not terribly >> > concerned with how it gets fixed, but there's not a great reason for >> this to >> > not behave better than it currently does. If someone steps up and makes >> > defaulting better, than that's great. But if not, then the libraries >> > committee can fix this very easily for GHC 7.12, and I think it's >> better to >> > do so than to wait if there are no signs that the alternative is going >> to >> > happen. >> > >> > I don't think we need to nail down which of the two solutions we're >> going to >> > choose right now, but it'd be good to resolve that we're going to fix >> it, >> > one way or another, by some well defined date. >> > >> > Here's a link to the previous discussion: >> > >> > http://comments.gmane.org/gmane.comp.lang.haskell.libraries/20088 >> > >> > Discussion period: 2 weeks >> > >> > -- Dan >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at well-typed.com Thu Aug 27 14:06:22 2015 From: ben at well-typed.com (Ben Gamari) Date: Thu, 27 Aug 2015 16:06:22 +0200 Subject: DEPRECATED pragma for exports In-Reply-To: <87zj1c6e4t.fsf@smart-cactus.org> Message-ID: <87zj1c6e4t.fsf@smart-cactus.org> Hello everyone, I was looking through the list of bugs milestoned for 7.12 today and stumbled across #4879. This ticket has been with us since 7.0.1 and proposes support for the DEPRECATE pragma on exports. I seem to remember seeing this feature being requested numerous times to help in dealing with transitional issues in the core libraries. If this is the case then we should aim to get this feature in to 7.12. This shouldn't be a difficult task as there is a working patch [1] in need of only a bit of minor refactoring already attached to the ticket. What we need to make this happen is for someone to step up and write a specification (on the GHC Wiki) defining the syntax and its semantics, and then check that the patch faithfully implements that specification. Would any of you be willing to do this? Cheers, - Ben [1] https://phabricator.haskell.org/D638 -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From hvr at gnu.org Sat Aug 29 06:56:53 2015 From: hvr at gnu.org (Herbert Valerio Riedel) Date: Sat, 29 Aug 2015 08:56:53 +0200 Subject: Please help beta test "no-reinstall Cabal" (was: Cabal and simultaneous installations of the same package) In-Reply-To: <68326f3ebbd943768effe6b0f2ff522c@DB4PR30MB030.064d.mgd.msft.net> (Simon Peyton Jones's message of "Mon, 23 Mar 2015 08:45:48 +0000") References: <68326f3ebbd943768effe6b0f2ff522c@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <87fv32lgzu.fsf@gmail.com> Good news, everyone! ...you may be interested to know this has finally come to fruition (just in time for HIW): http://blog.ezyang.com/2015/08/help-us-beta-test-no-reinstall-cabal/ Cheers, hvr On 2015-03-23 at 09:45:48 +0100, Simon Peyton Jones wrote: > Dear Cabal developers > > You'll probably have seen the thread about the Haskell Platform. > > Among other things, this point arose: > > | Another thing we should fix is the (now false) impression that HP gets in > | the way of installing other packages and versions due to cabal hell. > > People mean different things by "cabal hell", but the inability to > simultaneously install multiple versions of the same package, > compiled against different dependencies > is certainly one of them, and I think it is the one that Yitzchak is referring to here. > > But some time now GHC has allowed multiple versions of the same > package (compiled against different dependencies) to be installed > simultaneously. So all we need to do is to fix Cabal to allow it too, > and thereby kill of a huge class of cabal-hell problems at one blow. > > But time has passed and it hasn't happened. Is this because I'm misunderstanding? Or because it is harder than I think? Or because there are much bigger problems? Or because there is insufficient effort available? Or what? > > Unless I'm way off beam, this "multiple installations of the same package" thing has been a huge pain forever, and the solution is within our grasp. What's stopping us grasping it? From asr at eafit.edu.co Sun Aug 30 01:08:21 2015 From: asr at eafit.edu.co (=?UTF-8?B?QW5kcsOpcyBTaWNhcmQtUmFtw61yZXo=?=) Date: Sat, 29 Aug 2015 20:08:21 -0500 Subject: Problem running zlib test suite: ghc: unrecognised flag: -fno-stack-protector Message-ID: Hi, I'm trying of running the zlib test suite using GHC 7.10.2 and hsc2hs 0.67: $ darcs get http://code.haskell.org/zlib/ $ cd zlib $ cabal install $ cd test $ make test hsc2hs --cc=ghc --ld=ghc --lflag=-lz -o ../Codec/Compression/Zlib/Stream.hs ../Codec/Compression/Zlib/Stream.hsc ghc: unrecognised flag: -fno-stack-protector ... compiling ../Codec/Compression/Zlib/Stream_hsc_make.c failed (exit code 1) command was: ghc -c ../Codec/Compression/Zlib/Stream_hsc_make.c -o ../Codec/Compression/Zlib/Stream_hsc_make.o -fno-stack-protector -I/usr/local/stow/ghc-7.10.2/lib/ghc-7.10.2/include/ Am I doing something wrong? Best, -- Andr?s From rf at rufflewind.com Sun Aug 30 02:00:37 2015 From: rf at rufflewind.com (Phil Ruffwind) Date: Sat, 29 Aug 2015 22:00:37 -0400 Subject: Documentation for GHC.IO.Exception Message-ID: On Hackage, there seems to be no documentation for GHC.IO.Exception in base, but the package can in fact be imported so it's not exactly an internal package. directory and likely many other packages do use the GHC-specific error types like InappropriateType in exceptions, so it would be useful if there were a documentation page for these things even if there isn't any text. As it is right now, the discoverability of these error types is very low as you need to know the magical URL to show the source code: https://hackage.haskell.org/package/base/docs/src/GHC.IO.Exception.html That's also partly a problem with Haddock; AFAIK there's no way to navigate to the Source Code packages of modules whose documentation is disabled, even though they are in fact present if you can figure out the URL. So would it be OK to open up this module or is there a reason for keeping them discreet? From ferminreig at fastmail.fm Mon Aug 31 17:54:38 2015 From: ferminreig at fastmail.fm (Fermin Reig) Date: Mon, 31 Aug 2015 18:54:38 +0100 Subject: Proposal: generalise Monoid's mconcat Message-ID: <55E494DE.3080000@fastmail.fm> We could generalise: mconcat:: [a] -> a mconcat = foldr mappend memtpy to: mconcat:: Foldable t => t a -> a mconcat = foldr mappend memtpy -- even -- mconcat = fold Fermin PS: I cannot find a proposal for this in the archives, apologies if it's been raised before and I missed it. From david.feuer at gmail.com Mon Aug 31 18:03:10 2015 From: david.feuer at gmail.com (David Feuer) Date: Mon, 31 Aug 2015 14:03:10 -0400 Subject: Proposal: generalise Monoid's mconcat In-Reply-To: <55E494DE.3080000@fastmail.fm> References: <55E494DE.3080000@fastmail.fm> Message-ID: That sounds reasonable. On Aug 31, 2015 1:54 PM, "Fermin Reig" wrote: > We could generalise: > > mconcat:: [a] -> a > mconcat = foldr mappend memtpy > > to: > > mconcat:: Foldable t => t a -> a > mconcat = foldr mappend memtpy > -- even > -- mconcat = fold > > > Fermin > > PS: I cannot find a proposal for this in the archives, apologies if it's > been raised before and I missed it. > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rwbarton at gmail.com Mon Aug 31 18:47:53 2015 From: rwbarton at gmail.com (Reid Barton) Date: Mon, 31 Aug 2015 14:47:53 -0400 Subject: Proposal: generalise Monoid's mconcat In-Reply-To: <55E494DE.3080000@fastmail.fm> References: <55E494DE.3080000@fastmail.fm> Message-ID: On Mon, Aug 31, 2015 at 1:54 PM, Fermin Reig wrote: > We could generalise: > > mconcat:: [a] -> a > mconcat = foldr mappend memtpy > > to: > > mconcat:: Foldable t => t a -> a > mconcat = foldr mappend memtpy > -- even > -- mconcat = fold > I don't understand the appeal of generalizing the type of a function when the generalization already exists; but in this case it's not a viable option anyways because mconcat is a class method of Monoid, and the definition of the Foldable class already refers to Monoid. Creating a circular dependency of Monoid on Foldable would be a headache best avoided. Regards, Reid Barton -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Mon Aug 31 19:00:10 2015 From: david.feuer at gmail.com (David Feuer) Date: Mon, 31 Aug 2015 15:00:10 -0400 Subject: Proposal: generalise Monoid's mconcat In-Reply-To: References: <55E494DE.3080000@fastmail.fm> Message-ID: The theory of mconcat is that it should handle monoids that need to be summed in some special way. I don't know if anyone actually uses it so, however. Still, Reid is right that the circular dependency sets a very high bar. On Aug 31, 2015 2:47 PM, "Reid Barton" wrote: > On Mon, Aug 31, 2015 at 1:54 PM, Fermin Reig > wrote: > >> We could generalise: >> >> mconcat:: [a] -> a >> mconcat = foldr mappend memtpy >> >> to: >> >> mconcat:: Foldable t => t a -> a >> mconcat = foldr mappend memtpy >> -- even >> -- mconcat = fold >> > > I don't understand the appeal of generalizing the type of a function when > the generalization already exists; but in this case it's not a viable > option anyways because mconcat is a class method of Monoid, and the > definition of the Foldable class already refers to Monoid. Creating a > circular dependency of Monoid on Foldable would be a headache best avoided. > > Regards, > Reid Barton > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Mon Aug 31 19:01:45 2015 From: david.feuer at gmail.com (David Feuer) Date: Mon, 31 Aug 2015 15:01:45 -0400 Subject: Proposal: generalise Monoid's mconcat In-Reply-To: References: <55E494DE.3080000@fastmail.fm> Message-ID: That bar will be particularly hard to exceed in the presence of toList. On Aug 31, 2015 3:00 PM, "David Feuer" wrote: > The theory of mconcat is that it should handle monoids that need to be > summed in some special way. I don't know if anyone actually uses it so, > however. Still, Reid is right that the circular dependency sets a very high > bar. > On Aug 31, 2015 2:47 PM, "Reid Barton" wrote: > >> On Mon, Aug 31, 2015 at 1:54 PM, Fermin Reig >> wrote: >> >>> We could generalise: >>> >>> mconcat:: [a] -> a >>> mconcat = foldr mappend memtpy >>> >>> to: >>> >>> mconcat:: Foldable t => t a -> a >>> mconcat = foldr mappend memtpy >>> -- even >>> -- mconcat = fold >>> >> >> I don't understand the appeal of generalizing the type of a function when >> the generalization already exists; but in this case it's not a viable >> option anyways because mconcat is a class method of Monoid, and the >> definition of the Foldable class already refers to Monoid. Creating a >> circular dependency of Monoid on Foldable would be a headache best avoided. >> >> Regards, >> Reid Barton >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> -------------- next part -------------- An HTML attachment was scrubbed... URL: From petr.mvd at gmail.com Mon Aug 31 20:19:31 2015 From: petr.mvd at gmail.com (=?UTF-8?B?UGV0ciBQdWRsw6Fr?=) Date: Mon, 31 Aug 2015 22:19:31 +0200 Subject: Proposal: generalise Monoid's mconcat In-Reply-To: References: <55E494DE.3080000@fastmail.fm> Message-ID: 2015-08-31 21:00 GMT+02:00 David Feuer : > The theory of mconcat is that it should handle monoids that need to be > summed in some special way. I don't know if anyone actually uses it so, > however. Still, Reid is right that the circular dependency sets a very high > bar. > > I guess the [a] monoid is a good example where using mconcat can make a difference. What seems to be an omission is that Dual has no implementation of mconcat. It'd make sense to define 'mconcat = mconcat . reverse' - if the original monoid benefits from a certain order of operations, we should keep the order. -------------- next part -------------- An HTML attachment was scrubbed... URL: