From mblazevic at stilo.com Thu Dec 1 00:40:02 2016 From: mblazevic at stilo.com (=?UTF-8?Q?Mario_Bla=c5=beevi=c4=87?=) Date: Wed, 30 Nov 2016 19:40:02 -0500 Subject: Many functions can be generalised In-Reply-To: References: Message-ID: On 2016-11-30 04:08 AM, Baldur Blöndal wrote: > What about functions that aren't expected to preserve structure like > ‘lookup’ and (new) suggestions > >> lookup :: Eq a => k -> Foldable f => f (k, v) -> Maybe v >> lookup = lookupOf folded -1. It needs to die. >> elemIndex :: Eq a => a -> Foldable f => f a -> Maybe Int >> elemIndex = elemIndexOf folded > >> elemIndices :: Eq a => a -> Foldable f => f a -> Maybe Int >> elemIndices = elemIndicesOf folded > >> findIndex :: (a -> Bool) -> Foldable f => f a -> Maybe Int >> findIndex = findIndexOf folded > >> findIndices :: (a -> Bool) -> Foldable f => f a -> [Int] >> findIndices = findIndicesOf folded I'm +0.5 on these but only if they come in together with the (!!) operator, which should then be added as a Foldable class method to allow for optimizations. Without (!!) there'd be no way to express the laws these operations need to satisfy. From dave at zednenem.com Fri Dec 2 23:14:13 2016 From: dave at zednenem.com (David Menendez) Date: Fri, 2 Dec 2016 18:14:13 -0500 Subject: Many functions can be generalised In-Reply-To: References: <20161127170817.GA15884@glow> Message-ID: On Mon, Nov 28, 2016 at 4:41 PM, wren romano wrote: > I'd much rather see the above functions as: > > mapMaybes :: Foo f => (a -> Maybe b) -> f a -> f b > catMaybes :: Foo f => f (Maybe a) -> f a > A while back, I found myself deriving this class: class Functor f => Siftable f where siftWith :: (a -> Maybe b) -> f a -> f b sift :: (a -> Bool) -> f a -> f a sift f = siftWith (\a -> if f a then Just a else Nothing) which is essentially Witherable minus Traversable. It has the nice property that it’s a functor from the Kleisli category for Maybe to Hask, so the laws are intuitive and easily expressed. You can even express wither using siftWith and traverse wither :: (Siftable t, Traversable t, Applicative f) => (a -> f (Maybe b)) -> t a -> f (t b) wither f = fmap (siftWith id) . traverse f But it turns out that there aren’t many instances of Siftable that aren’t also Traversable. The most obvious would be infinite streams, but even they have a traversal if you restrict yourself to lazy applicatives. -- Dave Menendez -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Sat Dec 3 05:50:27 2016 From: david.feuer at gmail.com (David Feuer) Date: Sat, 3 Dec 2016 00:50:27 -0500 Subject: Many functions can be generalised In-Reply-To: References: <20161127170817.GA15884@glow> Message-ID: On Dec 2, 2016 6:14 PM, "David Menendez" wrote: A while back, I found myself deriving this class: class Functor f => Siftable f where siftWith :: (a -> Maybe b) -> f a -> f b sift :: (a -> Bool) -> f a -> f a sift f = siftWith (\a -> if f a then Just a else Nothing) I would expect several classes, corresponding to different methods of Witherable: class Siftable a m | m -> a where sift :: (a -> Bool) -> m -> m default sift :: SiftWithable f => (a -> Bool) -> f a -> f a sift p = siftWith (\x -> x <$ guard (p x)) class Functor f => SiftWithable f where siftWith :: (a -> Maybe b) -> f a -> f b class Siftable a m => SiftableA a m where siftA :: Applicative g => (a -> g Bool) -> m -> g m default siftA :: (SiftWithAAble f, Applicative g) => (a -> g Bool) -> f a -> g (f a) siftA p = siftWithA (\x -> (x <$) . guard <$> p x) class (Traversable f, SiftWithAble f) => SiftWithAAble f where siftWithA :: Applicative g => (a -> g (Maybe b)) -> f a -> g (f a) -------------- next part -------------- An HTML attachment was scrubbed... URL: From ganesh at earth.li Sat Dec 3 18:45:24 2016 From: ganesh at earth.li (Ganesh Sittampalam) Date: Sat, 3 Dec 2016 18:45:24 +0000 Subject: cabal new-build: what does foo-setup~> mean? Message-ID: <059610b2-28d3-6cf8-6e80-0568cb8307af@earth.li> Hi, How should I interpret the following dependency solving error from cabal new-build? Resolving dependencies... cabal: Could not resolve dependencies: trying: time-setup.time~>entropy-setup.time-1.1.2.3 (dependency of time-1.1.2.3) trying: time-setup.Cabal~>entropy-setup.Cabal-1.20.0.4 (dependency of time-1.1.2.3) Dependency tree exhaustively searched. FWIW I'm trying to build the HTTP package with GHC 7.0 and the following options. The solver takes ~10 minutes before failing. --constraint 'time==1.1.2.3' --constraint 'entropy<0.2.2.4' -f-warp-tests --constraint 'HUnit<1.4' cabal configure does seem to be able to find a solution. Cheers, Ganesh From dave at zednenem.com Sat Dec 3 19:17:29 2016 From: dave at zednenem.com (David Menendez) Date: Sat, 3 Dec 2016 14:17:29 -0500 Subject: Many functions can be generalised In-Reply-To: References: <20161127170817.GA15884@glow> Message-ID: On Sat, Dec 3, 2016 at 12:50 AM, David Feuer wrote: > On Dec 2, 2016 6:14 PM, "David Menendez" wrote: > > A while back, I found myself deriving this class: > > class Functor f => Siftable f where > siftWith :: (a -> Maybe b) -> f a -> f b > sift :: (a -> Bool) -> f a -> f a > sift f = siftWith (\a -> if f a then Just a else Nothing) > > > I would expect several classes, corresponding to different methods of > Witherable: > > class Siftable a m | m -> a where > sift :: (a -> Bool) -> m -> m > default sift :: SiftWithable f => (a -> Bool) -> f a -> f a > sift p = siftWith (\x -> x <$ guard (p x)) > > class Functor f => SiftWithable f where > siftWith :: (a -> Maybe b) -> f a -> f b > > class Siftable a m => SiftableA a m where > siftA :: Applicative g => (a -> g Bool) -> m -> g m > default siftA :: (SiftWithAAble f, Applicative g) => (a -> g Bool) -> f > a -> g (f a) > siftA p = siftWithA (\x -> (x <$) . guard <$> p x) > > class (Traversable f, SiftWithAble f) => SiftWithAAble f where > siftWithA :: Applicative g => (a -> g (Maybe b)) -> f a -> g (f a) > Yes, sift is more general than siftWith (which I should have called siftMap, in hindsight). But, so far as I know, the only things you can define sift for but not siftWith are sets and set-like things. At the time, I had also rejected sift by itself because I couldn’t think of any laws, but now that I look at it again, I guess they would be: sift (const True) = id sift (\x -> p x && q x) = sift q . sift p I think those would make sift a monoid homomorphism. These still allow some weird instances, like sift _ = id, or something like this: newtype Weird a = Map a Bool instance Ord a => Siftable a (Weird a) where sift p (Weird m) = Weird (Map.union (Map.updateMin (const False) yes) no) where (yes, no) = Map.partitionWithKey (const . p) m I imagine it isn’t worth making the laws tighter to forbid this. -- Dave Menendez -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Sat Dec 3 19:32:44 2016 From: david.feuer at gmail.com (David Feuer) Date: Sat, 3 Dec 2016 14:32:44 -0500 Subject: Many functions can be generalised In-Reply-To: References: <20161127170817.GA15884@glow> Message-ID: You can also sift monomorphic containers using my class, which should probably be called MonoSiftable. data IntList = Cons !Int IntList | Nil instance Siftable Int IntList where sift _ Nil = Nil sift p (Cons x xs) | p x = Cons x (sift p xs) | otherwise = sift p xs On Dec 3, 2016 2:17 PM, "David Menendez" wrote: > On Sat, Dec 3, 2016 at 12:50 AM, David Feuer > wrote: > >> On Dec 2, 2016 6:14 PM, "David Menendez" wrote: >> >> A while back, I found myself deriving this class: >> >> class Functor f => Siftable f where >> siftWith :: (a -> Maybe b) -> f a -> f b >> sift :: (a -> Bool) -> f a -> f a >> sift f = siftWith (\a -> if f a then Just a else Nothing) >> >> >> I would expect several classes, corresponding to different methods of >> Witherable: >> >> class Siftable a m | m -> a where >> sift :: (a -> Bool) -> m -> m >> default sift :: SiftWithable f => (a -> Bool) -> f a -> f a >> sift p = siftWith (\x -> x <$ guard (p x)) >> >> class Functor f => SiftWithable f where >> siftWith :: (a -> Maybe b) -> f a -> f b >> >> class Siftable a m => SiftableA a m where >> siftA :: Applicative g => (a -> g Bool) -> m -> g m >> default siftA :: (SiftWithAAble f, Applicative g) => (a -> g Bool) -> f >> a -> g (f a) >> siftA p = siftWithA (\x -> (x <$) . guard <$> p x) >> >> class (Traversable f, SiftWithAble f) => SiftWithAAble f where >> siftWithA :: Applicative g => (a -> g (Maybe b)) -> f a -> g (f a) >> > > Yes, sift is more general than siftWith (which I should have called > siftMap, in hindsight). But, so far as I know, the only things you can > define sift for but not siftWith are sets and set-like things. > > At the time, I had also rejected sift by itself because I couldn’t think > of any laws, but now that I look at it again, I guess they would be: > > sift (const True) = id > sift (\x -> p x && q x) = sift q . sift p > > I think those would make sift a monoid homomorphism. > > These still allow some weird instances, like sift _ = id, or something > like this: > > newtype Weird a = Map a Bool > > instance Ord a => Siftable a (Weird a) where > sift p (Weird m) = Weird (Map.union (Map.updateMin (const False) > yes) no) > where > (yes, no) = Map.partitionWithKey (const . p) m > > I imagine it isn’t worth making the laws tighter to forbid this. > > -- > Dave Menendez > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From dave at zednenem.com Sun Dec 4 05:22:56 2016 From: dave at zednenem.com (David Menendez) Date: Sun, 4 Dec 2016 00:22:56 -0500 Subject: Many functions can be generalised In-Reply-To: References: <20161127170817.GA15884@glow> Message-ID: On Sat, Dec 3, 2016 at 2:32 PM, David Feuer wrote: > You can also sift monomorphic containers using my class, which should > probably be called MonoSiftable. > > data IntList = Cons !Int IntList | Nil > > instance Siftable Int IntList where > sift _ Nil = Nil > sift p (Cons x xs) > | p x = Cons x (sift p xs) > | otherwise = sift p xs > You can also use it with contra-variant or invariant type constructors, e.g., instance Siftable a (a -> Bool) where sift f g = \x -> f x && g x -- Dave Menendez -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Sun Dec 4 05:44:31 2016 From: david.feuer at gmail.com (David Feuer) Date: Sun, 4 Dec 2016 00:44:31 -0500 Subject: Many functions can be generalised In-Reply-To: References: <20161127170817.GA15884@glow> Message-ID: On Dec 4, 2016 12:22 AM, "David Menendez" wrote: You can also use it with contra-variant or invariant type constructors, e.g., instance Siftable a (a -> Bool) where sift f g = \x -> f x && g x That looks backwards for your composition law, but I'm a bit tired so I wouldn't swear to it. Surely you can do the same with the constructor class. newtype Ab a = Ab (a -> Bool) instance Siftable Ab where siftAway _ = Ab (const False) sift p (Ab g) = Ab ... I'm not sure if my siftAway excludes anything it shouldn't.... -------------- next part -------------- An HTML attachment was scrubbed... URL: From ezyang at mit.edu Sun Dec 4 18:55:13 2016 From: ezyang at mit.edu (Edward Z. Yang) Date: Sun, 04 Dec 2016 10:55:13 -0800 Subject: cabal new-build: what does foo-setup~> mean? In-Reply-To: <059610b2-28d3-6cf8-6e80-0568cb8307af@earth.li> References: <059610b2-28d3-6cf8-6e80-0568cb8307af@earth.li> Message-ID: <1480877569-sup-6286@sabre> Hello Ganesh, You should go ahead and file a bug on the Cabal tracker; the dep solver folks will be able to help you there. ~> indicates "linking". In the code comments: -- The modular solver has a number of package goals to solve for, and can only -- pick a single package version for a single goal. In order to allow to -- install multiple versions of the same package as part of a single solution -- the solver uses qualified goals. For example, @0.P@ and @1.P@ might both -- be qualified goals for @P@, allowing to pick a difference version of package -- @P@ for @0.P@ and @1.P at . -- -- Linking is an essential part of this story. In addition to picking a specific -- version for @1.P@, the solver can also decide to link @1.P@ to @0.P@ (or -- vice versa). It means that @1.P@ and @0.P@ really must be the very same package -- (and hence must have the same build time configuration, and their -- dependencies must also be the exact same). -- -- See for details. I haven't studied the actual error you have too closely. Hope that helps, Edward Excerpts from Ganesh Sittampalam's message of 2016-12-03 18:45:24 +0000: > Hi, > > How should I interpret the following dependency solving error from cabal > new-build? > > Resolving dependencies... > cabal: Could not resolve dependencies: > trying: time-setup.time~>entropy-setup.time-1.1.2.3 (dependency of > time-1.1.2.3) > trying: time-setup.Cabal~>entropy-setup.Cabal-1.20.0.4 (dependency of > time-1.1.2.3) > Dependency tree exhaustively searched. > > FWIW I'm trying to build the HTTP package with GHC 7.0 and the following > options. The solver takes ~10 minutes before failing. > > --constraint 'time==1.1.2.3' --constraint 'entropy<0.2.2.4' > -f-warp-tests --constraint 'HUnit<1.4' > > cabal configure does seem to be able to find a solution. > > Cheers, > > Ganesh From dave at zednenem.com Sun Dec 4 23:45:24 2016 From: dave at zednenem.com (David Menendez) Date: Sun, 4 Dec 2016 18:45:24 -0500 Subject: Many functions can be generalised In-Reply-To: References: <20161127170817.GA15884@glow> Message-ID: On Sun, Dec 4, 2016 at 12:44 AM, David Feuer wrote: > On Dec 4, 2016 12:22 AM, "David Menendez" wrote: > > > You can also use it with contra-variant or invariant type constructors, > e.g., > > instance Siftable a (a -> Bool) where > sift f g = \x -> f x && g x > > > That looks backwards for your composition law, but I'm a bit tired so I > wouldn't swear to it. > You’re right. Of course, they’re all the same if we assume total functions. Surely you can do the same with the constructor class. > > newtype Ab a = Ab (a -> Bool) > instance Siftable Ab where > siftAway _ = Ab (const False) > sift p (Ab g) = Ab ... > Ab is contravariant, so you would need something like siftContraMap :: (a -> Maybe b) -> f b -> f a > I'm not sure if my siftAway excludes anything it shouldn't.... > I’m not sure it’s possible to define siftAway so that it isn’t equal to sift (const Nothing). -- Dave Menendez -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Mon Dec 5 00:33:16 2016 From: david.feuer at gmail.com (David Feuer) Date: Sun, 4 Dec 2016 19:33:16 -0500 Subject: Many functions can be generalised In-Reply-To: References: <20161127170817.GA15884@glow> Message-ID: On Sun, Dec 4, 2016 at 6:45 PM, David Menendez wrote: >> Surely you can do the same with the constructor class. >> >> newtype Ab a = Ab (a -> Bool) >> instance Siftable Ab where >> siftAway _ = Ab (const False) >> sift p (Ab g) = Ab ... > > > Ab is contravariant, so you would need something like > > siftContraMap :: (a -> Maybe b) -> f b -> f a That's the Functor version, which entirely excludes contravariant things. For the plain sift :: (a -> Bool) -> f a -> f a version, you can use instance Siftable Ab where sift f (Ab g) = Ab (\x -> g x && f x) siftAway (Ab g) = Ab (const False) >> I'm not sure if my siftAway excludes anything it shouldn't.... > > I’m not sure it’s possible to define siftAway so that it isn’t equal to sift > (const Nothing). As you pointed out, your laws for the plain Siftable don't exclude sift _ = id for an arbitrary Siftable. Adding siftAway with that law ensures that sift (const Nothing) actually "empties" the container. I doubt it actually makes sense to add it to the API, though. As for names, I think for consistency with the rest of the world, the method names that make the most sense are filter, mapMaybe, filterM, and traverseMaybe. The filterM name is a bit unfortunate, since it only needs an Applicative constraint, but that seems to be what people like. The monad-extras package uses the name mapMaybeM, but that strikes me as a terrible name because it's really much more like traverse than like map. David From david.feuer at gmail.com Mon Dec 5 19:18:05 2016 From: david.feuer at gmail.com (David Feuer) Date: Mon, 5 Dec 2016 14:18:05 -0500 Subject: Proposal: Expose Coercions for unboxed arrays Message-ID: As discussed in [1], we now have type role Array nominal representational type role IOArray nominal representational type role UArray nominal nominal type role IOUArray nominal nominal type role StorableArray nominal nominal type role STArray nominal nominal representational type role STUArray nominal nominal nominal There are good reasons for these, as described in the ticket, but in some particular cases, they're overkill. It might be nice to expose the representational equivalence locally, with the understanding that the user has to ensure that the Ix, Storable, etc., instances are compatible. I think the place for these is likely Data.Array.Unsafe, although they'd need to be defined in GHC.Arr. For boxed arrays, it's sufficient to expose a Coercion between partially applied constructors. For unboxed arrays, such a coercion doesn't do much (because the element type has a nominal role), so I think only Coercions between the fully-applied constructors are really useful for those. For STArray and STUArray, I don't *think* we want to expose a coercion to change the state thread type; anyone fussing at such a low level is probably importing GHC.Arr anyway. arrayCoercion :: Coercible i j => Coercion (Array i) (Array j) ioarrayCoercion :: ... uarrayCoercion :: (Coercible i j, Coercible a b) => Coercion (UArray i a) (UArray j b) iouarrayCoercion :: ... storablearrayCoercion :: ... starrayCoercion :: Coercible i j => Coercion (STArray s i) (STArray s j) stuarrayCoercion :: (Coercible i j, Coercible a b) => Coercion (STUArray s i a) (STUArray s j b) [1] https://ghc.haskell.org/trac/ghc/ticket/9220 From ganesh at earth.li Mon Dec 5 19:24:23 2016 From: ganesh at earth.li (Ganesh Sittampalam) Date: Mon, 5 Dec 2016 19:24:23 +0000 Subject: cabal new-build: what does foo-setup~> mean? In-Reply-To: <1480877569-sup-6286@sabre> References: <059610b2-28d3-6cf8-6e80-0568cb8307af@earth.li> <1480877569-sup-6286@sabre> Message-ID: <7c663576-2699-e57a-4093-18bf323a5b1e@earth.li> Thanks: https://github.com/haskell/cabal/issues/4154 On 04/12/2016 18:55, Edward Z. Yang wrote: > Hello Ganesh, > > You should go ahead and file a bug on the Cabal tracker; the > dep solver folks will be able to help you there. > > ~> indicates "linking". In the code comments: > > -- The modular solver has a number of package goals to solve for, and can only > -- pick a single package version for a single goal. In order to allow to > -- install multiple versions of the same package as part of a single solution > -- the solver uses qualified goals. For example, @0.P@ and @1.P@ might both > -- be qualified goals for @P@, allowing to pick a difference version of package > -- @P@ for @0.P@ and @1.P at . > -- > -- Linking is an essential part of this story. In addition to picking a specific > -- version for @1.P@, the solver can also decide to link @1.P@ to @0.P@ (or > -- vice versa). It means that @1.P@ and @0.P@ really must be the very same package > -- (and hence must have the same build time configuration, and their > -- dependencies must also be the exact same). > -- > -- See for details. > > I haven't studied the actual error you have too closely. > > Hope that helps, > > Edward > > Excerpts from Ganesh Sittampalam's message of 2016-12-03 18:45:24 +0000: >> Hi, >> >> How should I interpret the following dependency solving error from cabal >> new-build? >> >> Resolving dependencies... >> cabal: Could not resolve dependencies: >> trying: time-setup.time~>entropy-setup.time-1.1.2.3 (dependency of >> time-1.1.2.3) >> trying: time-setup.Cabal~>entropy-setup.Cabal-1.20.0.4 (dependency of >> time-1.1.2.3) >> Dependency tree exhaustively searched. >> >> FWIW I'm trying to build the HTTP package with GHC 7.0 and the following >> options. The solver takes ~10 minutes before failing. >> >> --constraint 'time==1.1.2.3' --constraint 'entropy<0.2.2.4' >> -f-warp-tests --constraint 'HUnit<1.4' >> >> cabal configure does seem to be able to find a solution. >> >> Cheers, >> >> Ganesh > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > From david.feuer at gmail.com Wed Dec 7 04:05:17 2016 From: david.feuer at gmail.com (David Feuer) Date: Tue, 6 Dec 2016 23:05:17 -0500 Subject: Proposal: Expose Coercions for unboxed arrays In-Reply-To: <7F89666B-F85B-4D77-B372-4268B1472D4B@cis.upenn.edu> References: <7F89666B-F85B-4D77-B372-4268B1472D4B@cis.upenn.edu> Message-ID: Richard, there's currently no way to change the roles in different modules, but it's possible to "tunnel" through the roles using Coercions exposed by the defining module (in which the user-provided roles are ignored). On Dec 6, 2016 10:40 PM, "Richard Eisenberg" wrote: > I don't have an opinion about whether or not David's design is desirable, > but I can comment on implementation feasibility. > > GHC doesn't have a built-in way to have certain roles in some modules and > other roles in other modules. I don't see anything drastically wrong with > such a feature, but it does not currently exist. So to implement David's > suggestion, we would have to have version of these types exposed from some > Unsafe module and then newtypes around each one exposed in the normal > interface. > > Unless someone sees another way, which I may well have missed. > > Richard > > > On Dec 5, 2016, at 2:18 PM, David Feuer wrote: > > > > As discussed in [1], we now have > > > > type role Array nominal representational > > type role IOArray nominal representational > > type role UArray nominal nominal > > type role IOUArray nominal nominal > > type role StorableArray nominal nominal > > type role STArray nominal nominal representational > > type role STUArray nominal nominal nominal > > > > There are good reasons for these, as described in the ticket, but in > > some particular cases, they're overkill. It might be nice to expose > > the representational equivalence locally, with the understanding that > > the user has to ensure that the Ix, Storable, etc., instances are > > compatible. I think the place for these is likely Data.Array.Unsafe, > > although they'd need to be defined in GHC.Arr. For boxed arrays, it's > > sufficient to expose a Coercion between partially applied > > constructors. For unboxed arrays, such a coercion doesn't do much > > (because the element type has a nominal role), so I think only > > Coercions between the fully-applied constructors are really useful for > > those. For STArray and STUArray, I don't *think* we want to expose a > > coercion to change the state thread type; anyone fussing at such a low > > level is probably importing GHC.Arr anyway. > > > > arrayCoercion :: Coercible i j => Coercion (Array i) (Array j) > > ioarrayCoercion :: ... > > > > uarrayCoercion :: (Coercible i j, Coercible a b) => Coercion (UArray i > > a) (UArray j b) > > iouarrayCoercion :: ... > > storablearrayCoercion :: ... > > > > starrayCoercion :: Coercible i j => Coercion (STArray s i) (STArray s j) > > stuarrayCoercion :: (Coercible i j, Coercible a b) => Coercion > > (STUArray s i a) (STUArray s j b) > > > > [1] https://ghc.haskell.org/trac/ghc/ticket/9220 > > _______________________________________________ > > 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 andrew.thaddeus at gmail.com Sun Dec 11 16:14:44 2016 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Sun, 11 Dec 2016 11:14:44 -0500 Subject: Move Data.Functor.Contravariant into base Message-ID: <20161211161444.GA22705@thadasaurus> The typeclass Contravariant (from the contravariant package) is both useful and fundamental. I would like to see this moved into base. One additional motivating factor is that it would become possible for a DeriveContravariant extension to be written in a future GHC release. I'd love to hear other people's thoughts, even if it's as simple as a yea or nay. Thanks. -Andrew Martin From shachaf at gmail.com Sun Dec 11 20:05:05 2016 From: shachaf at gmail.com (Shachaf Ben-Kiki) Date: Sun, 11 Dec 2016 12:05:05 -0800 Subject: Move Data.Functor.Contravariant into base In-Reply-To: <20161211161444.GA22705@thadasaurus> References: <20161211161444.GA22705@thadasaurus> Message-ID: Putting Contravariant in base sounds like a reasonable thing to do. It's a pretty basic class. Deriving Contravariant seems a bit tricky. If Contravariant is in base and part of the deriving code, what Functor/Contravariant instances do you derive for e.g. newtype Compose f g a = Compose (f (g a))? Shachaf On Sun, Dec 11, 2016 at 8:14 AM, Andrew Martin wrote: > The typeclass Contravariant (from the contravariant package) is both > useful and fundamental. I would like to see this moved into base. > One additional motivating factor is that it would become possible > for a DeriveContravariant extension to be written in a future GHC > release. I'd love to hear other people's thoughts, even if it's as > simple as a yea or nay. Thanks. > > -Andrew Martin > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From andrew.thaddeus at gmail.com Sun Dec 11 22:10:24 2016 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Sun, 11 Dec 2016 17:10:24 -0500 Subject: Move Data.Functor.Contravariant into base In-Reply-To: References: <20161211161444.GA22705@thadasaurus> Message-ID: <20161211221024.GA26997@thadasaurus> That's a good point about the deriving ambiguity. I had not really thought that through all the way. Additionally, I just stumbled across https://github.com/ekmett/contravariant/issues/17, which makes it pretty clear that there actually isn't a good way to handle all cases. I think that it might still be nice to have a DeriveContravariant that is simply weaker than DeriveFunctor. It could just complain and error out in ambiguous cases. The ambiguous cases would be all types parameterized by more than one higher-kinded type. And DeriveFunctor could just be left alone, continuing to derive the Functor instance for Compose the same way it already does. Usually, when I write Contravariant instances, it's for stuff like this that doesn't even involve anything higher-kinded: data Encoding c a = Encoding (Vector (c, a -> c)) Of course, I could be totally wrong about the rule I suggested for figuring out ambiguous cases. I guess I probably need to think about it more. Regardless, I'm glad to hear that someone else is in favor of moving Contravariant into base. On Sun, Dec 11, 2016 at 12:05:05PM -0800, Shachaf Ben-Kiki wrote: > Putting Contravariant in base sounds like a reasonable thing to do. > It's a pretty basic class. > > Deriving Contravariant seems a bit tricky. If Contravariant is in base > and part of the deriving code, what Functor/Contravariant instances do > you derive for e.g. newtype Compose f g a = Compose (f (g a))? > > Shachaf > > On Sun, Dec 11, 2016 at 8:14 AM, Andrew Martin > wrote: > > The typeclass Contravariant (from the contravariant package) is both > > useful and fundamental. I would like to see this moved into base. > > One additional motivating factor is that it would become possible > > for a DeriveContravariant extension to be written in a future GHC > > release. I'd love to hear other people's thoughts, even if it's as > > simple as a yea or nay. Thanks. > > > > -Andrew Martin > > _______________________________________________ > > Libraries mailing list > > Libraries at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From ekmett at gmail.com Tue Dec 13 18:35:57 2016 From: ekmett at gmail.com (Edward Kmett) Date: Tue, 13 Dec 2016 13:35:57 -0500 Subject: Move Data.Functor.Contravariant into base In-Reply-To: <20161211161444.GA22705@thadasaurus> References: <20161211161444.GA22705@thadasaurus> Message-ID: I have no particular issue with moving Contravariant into base. That said, DeriveContravariant doesn't work out as well as you'd think. See the discussion in here: https://github.com/ekmett/contravariant/issues/17 (There were other, longer discussions elsewhere that were er.. more of a discussion, but they were mostly on places like #haskell-lens which aren't logged and I can't find them at the moment.) With covariance you can just ignore that contravariant cases exist and get reasonable deriving. With contravariance composition of contravariant functors is covariant. You have the f (g a) problem. Which of the two is contravariant? This doesn't arise solely from type arguments. When faced with a concrete data type, you can't just look for a Contravariant or Functor instance for it, because both might be available (think Proxy). So the whole extension becomes a bug-addled mess. e.g. There are two sensible Contravariant instances for Compose, but neither one is canonical. The other DeriveFoo definitions all do reasonable things. This can't do a reasonable thing in any non-trivial situation. -Edward On Sun, Dec 11, 2016 at 11:14 AM, Andrew Martin wrote: > The typeclass Contravariant (from the contravariant package) is both > useful and fundamental. I would like to see this moved into base. > One additional motivating factor is that it would become possible > for a DeriveContravariant extension to be written in a future GHC > release. I'd love to hear other people's thoughts, even if it's as > simple as a yea or nay. Thanks. > > -Andrew Martin > _______________________________________________ > 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 abela at chalmers.se Tue Dec 13 20:34:13 2016 From: abela at chalmers.se (Andreas Abel) Date: Tue, 13 Dec 2016 21:34:13 +0100 Subject: Move Data.Functor.Contravariant into base In-Reply-To: <20161211161444.GA22705@thadasaurus> References: <20161211161444.GA22705@thadasaurus> Message-ID: -1. I think to move something into base there should be some hard evidence for its popularity. Such could be provided by a reverse dependency search on hackage. --Andreas On 11.12.2016 17:14, Andrew Martin wrote: > The typeclass Contravariant (from the contravariant package) is both > useful and fundamental. I would like to see this moved into base. > One additional motivating factor is that it would become possible > for a DeriveContravariant extension to be written in a future GHC > release. I'd love to hear other people's thoughts, even if it's as > simple as a yea or nay. Thanks. > > -Andrew Martin > _______________________________________________ > 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 ekmett at gmail.com Tue Dec 13 21:45:28 2016 From: ekmett at gmail.com (Edward Kmett) Date: Tue, 13 Dec 2016 16:45:28 -0500 Subject: Move Data.Functor.Contravariant into base In-Reply-To: References: <20161211161444.GA22705@thadasaurus> Message-ID: Just to articulate a few more points on each side: To Andreas point, one issue with contravariant in base is that there are no types in base that would serve as reasonable instances. You'd get a scattershot pile of mostly 'nonsensical' instances for stuff like the GHC.Generics types. On the other hand, but a far lesser concern, it'd shed the dependencies the package has, which would be good for things like lens-style Getters which use the constraint. Being able to use or supply more types of lenses with no dependencies is a minor good point. On the other other hand, rehoming a lot of the 'nonsensical' style instances to the packages that have their dependencies inverted is a fair chunk of work. On the other other other hand, this would fix the weird dependency inversion between StateVar and contravariant forced by the haskell platform. Er... that is a lot of hands. I personally don't care much one way or the other. Doing nothing is literally the default option. If there winds a lot of noise against this I'm happy to stick with the status quo, which is not THAT broken. On the other other other other hand, if there is a huge upwell of support, we could make a go of it. -Edward Note to self: I need to stop counting hands in unary. On Tue, Dec 13, 2016 at 3:34 PM, Andreas Abel wrote: > -1. I think to move something into base there should be some hard > evidence for its popularity. Such could be provided by a reverse > dependency search on hackage. > > --Andreas > > > On 11.12.2016 17:14, Andrew Martin wrote: > >> The typeclass Contravariant (from the contravariant package) is both >> useful and fundamental. I would like to see this moved into base. >> One additional motivating factor is that it would become possible >> for a DeriveContravariant extension to be written in a future GHC >> release. I'd love to hear other people's thoughts, even if it's as >> simple as a yea or nay. Thanks. >> >> -Andrew Martin >> _______________________________________________ >> 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: From andrew.thaddeus at gmail.com Thu Dec 15 01:11:27 2016 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Wed, 14 Dec 2016 20:11:27 -0500 Subject: Move Data.Functor.Contravariant into base In-Reply-To: References: <20161211161444.GA22705@thadasaurus> Message-ID: <20161215011127.GA6475@thadasaurus> The reverse dependency count can be found here: http://packdeps.haskellers.com/reverse The contravariant library has 73 reverse dependencies. Just as a reference point, bifunctors currently has 112 dependencies, and Data.Bifunctor was moved into base-4.9. Whether or not you believe that 73 reverse deps is sufficient is up to you, but those are the most relevant numbers I can provide. -Andrew Martin On Tue, Dec 13, 2016 at 09:34:13PM +0100, Andreas Abel wrote: > -1. I think to move something into base there should be some hard evidence > for its popularity. Such could be provided by a reverse dependency search > on hackage. > > --Andreas > > On 11.12.2016 17:14, Andrew Martin wrote: > >The typeclass Contravariant (from the contravariant package) is both > >useful and fundamental. I would like to see this moved into base. > >One additional motivating factor is that it would become possible > >for a DeriveContravariant extension to be written in a future GHC > >release. I'd love to hear other people's thoughts, even if it's as > >simple as a yea or nay. Thanks. > > > >-Andrew Martin > >_______________________________________________ > >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 andrew.thaddeus at gmail.com Thu Dec 15 01:25:06 2016 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Wed, 14 Dec 2016 20:25:06 -0500 Subject: Move Data.Functor.Contravariant into base In-Reply-To: References: <20161211161444.GA22705@thadasaurus> Message-ID: <20161215012506.GB6475@thadasaurus> The deriving problem is annoying indeed. I stumbled across that github issue shortly after proposing this change. The only sensible thing I can think of for a DeriveContravariant would be to only allow it if a data type were only parameterized by things that were not higher-kinded. I'm guessing that this is what you are describing when you say: The other DeriveFoo definitions all do reasonable things. This can't do a reasonable thing in any non-trivial situation. Although I think that those "trivial situations" are common enough that a necessarily imperfect DeriveContravariant could still be useful. Regardless, it's the move into base that I care more about, so I'm glad to hear that you find that agreeable. -Andrew Martin On Tue, Dec 13, 2016 at 01:35:57PM -0500, Edward Kmett wrote: > I have no particular issue with moving Contravariant into base. > > That said, DeriveContravariant doesn't work out as well as you'd think. See > the discussion in here: https://github.com/ekmett/contravariant/issues/17 > (There were other, longer discussions elsewhere that were er.. more of a > discussion, but they were mostly on places like #haskell-lens which aren't > logged and I can't find them at the moment.) > > With covariance you can just ignore that contravariant cases exist and get > reasonable deriving. > > With contravariance composition of contravariant functors is covariant. You > have the f (g a) problem. Which of the two is contravariant? This doesn't > arise solely from type arguments. When faced with a concrete data type, you > can't just look for a Contravariant or Functor instance for it, because > both might be available (think Proxy). So the whole extension becomes a > bug-addled mess. > > e.g. There are two sensible Contravariant instances for Compose, but > neither one is canonical. > > The other DeriveFoo definitions all do reasonable things. This can't do a > reasonable thing in any non-trivial situation. > > -Edward > > On Sun, Dec 11, 2016 at 11:14 AM, Andrew Martin > wrote: > > > The typeclass Contravariant (from the contravariant package) is both > > useful and fundamental. I would like to see this moved into base. > > One additional motivating factor is that it would become possible > > for a DeriveContravariant extension to be written in a future GHC > > release. I'd love to hear other people's thoughts, even if it's as > > simple as a yea or nay. Thanks. > > > > -Andrew Martin > > _______________________________________________ > > Libraries mailing list > > Libraries at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > From mblazevic at stilo.com Fri Dec 16 14:46:31 2016 From: mblazevic at stilo.com (=?UTF-8?Q?Mario_Bla=c5=beevi=c4=87?=) Date: Fri, 16 Dec 2016 09:46:31 -0500 Subject: Move Data.Functor.Contravariant into base In-Reply-To: References: <20161211161444.GA22705@thadasaurus> Message-ID: On 2016-12-13 04:45 PM, Edward Kmett wrote: > To Andreas point, one issue with contravariant in base is that there are > no types in base that would serve as reasonable instances. You'd get a > scattershot pile of mostly 'nonsensical' instances for stuff like the > GHC.Generics types. We could add a non-nonsensical¹ instance easily enough: > newtype Flip f a b = Flip {flipBack :: f b a} > > instance Contravariant (Flip (->) a) where > contramap f (Flip g) = Flip (g . f) Or, if FlexibleInstances are a problem: > newtype Inverse a b = Inverse {applyInverse :: b -> a} > > instance Contravariant (Inverse a) where > contramap f (Inverse g) = Inverse (g . f) (¹): apparently sensical is not a word, which is nonsensible From baldurpet at gmail.com Sat Dec 24 00:02:18 2016 From: baldurpet at gmail.com (=?UTF-8?Q?Baldur_Bl=C3=B6ndal?=) Date: Sat, 24 Dec 2016 00:02:18 +0000 Subject: Data.Functor.{Product,Sum} functions Message-ID: Let's see if any of these are useful (a lot more at https://ghc.haskell.org/trac/ghc/ticket/13026) (||||) :: (f a -> b) -> (g a -> b) -> ((Sum f g) a -> b) f |||| g = \case InL fa -> f fa InR ga -> g ga (&&&&) :: (a -> f b) -> (a -> g b) -> (a -> (Product f g) b) (f &&&& g) a = f a `Pair` g a I couldn't think of any for Data.Functor.Compose, names are up for bikeshedding -------------- next part -------------- An HTML attachment was scrubbed... URL: From jon.fairbairn at cl.cam.ac.uk Sat Dec 24 10:06:20 2016 From: jon.fairbairn at cl.cam.ac.uk (Jon Fairbairn) Date: Sat, 24 Dec 2016 10:06:20 +0000 Subject: Data.Functor.{Product,Sum} functions References: Message-ID: Baldur Blöndal writes: > Let's see if any of these are useful (a lot more at > https://ghc.haskell.org/trac/ghc/ticket/13026) > > (||||) :: (f a -> b) -> (g a -> b) -> ((Sum f g) a -> b) > f |||| g = \case > InL fa -> f fa > InR ga -> g ga > > (&&&&) :: (a -> f b) -> (a -> g b) -> (a -> (Product f g) b) > (f &&&& g) a = f a `Pair` g a > > I couldn't think of any for Data.Functor.Compose, names are up for > bikeshedding I don’t have any particular preference for names, but I’d say that any name consisting of more than three consecutive identical symbols is going to be too hard to read (particularly if the symbol is “|”). There’s a whole unicode alphabet out there. -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk From david.feuer at gmail.com Sat Dec 24 12:43:17 2016 From: david.feuer at gmail.com (David Feuer) Date: Sat, 24 Dec 2016 07:43:17 -0500 Subject: Data.Functor.{Product,Sum} functions In-Reply-To: References: Message-ID: This |||| is the sum eliminator. We can't call it `sum`, but maybe `sumE`? I do think it should be included with some name. Another option might be to drag Data.Bifoldable into base from bifunctors; (||||) = bifoldMap, but I think the case for a specialized name is still pretty good. &&&& is definitely a nice thing to have. However, (&&&&) = liftA2 Pair, so I'm not convinced we need to give it its own name. On Fri, Dec 23, 2016 at 7:02 PM, Baldur Blöndal wrote: > Let's see if any of these are useful (a lot more at > https://ghc.haskell.org/trac/ghc/ticket/13026) > > (||||) :: (f a -> b) -> (g a -> b) -> ((Sum f g) a -> b) > f |||| g = \case > InL fa -> f fa > InR ga -> g ga > > (&&&&) :: (a -> f b) -> (a -> g b) -> (a -> (Product f g) b) > (f &&&& g) a = f a `Pair` g a > > I couldn't think of any for Data.Functor.Compose, names are up for > bikeshedding > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > From yom at artyom.me Sat Dec 24 13:24:42 2016 From: yom at artyom.me (Artyom) Date: Sat, 24 Dec 2016 16:24:42 +0300 Subject: Data.Functor.{Product,Sum} functions In-Reply-To: References: Message-ID: Data.Bifoldable has already been dragged into base: https://ghc.haskell.org/trac/ghc/ticket/9682 On 12/24/2016 03:43 PM, David Feuer wrote: > This |||| is the sum eliminator. We can't call it `sum`, but maybe > `sumE`? I do think it should be included with some name. Another > option might be to drag Data.Bifoldable into base from bifunctors; > (||||) = bifoldMap, but I think the case for a specialized name is > still pretty good. > > &&&& is definitely a nice thing to have. However, (&&&&) = liftA2 > Pair, so I'm not convinced we need to give it its own name. > > On Fri, Dec 23, 2016 at 7:02 PM, Baldur Blöndal wrote: >> Let's see if any of these are useful (a lot more at >> https://ghc.haskell.org/trac/ghc/ticket/13026) >> >> (||||) :: (f a -> b) -> (g a -> b) -> ((Sum f g) a -> b) >> f |||| g = \case >> InL fa -> f fa >> InR ga -> g ga >> >> (&&&&) :: (a -> f b) -> (a -> g b) -> (a -> (Product f g) b) >> (f &&&& g) a = f a `Pair` g a >> >> I couldn't think of any for Data.Functor.Compose, names are up for >> bikeshedding >> >> _______________________________________________ >> 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 From blamario at ciktel.net Sat Dec 24 17:19:47 2016 From: blamario at ciktel.net (=?UTF-8?Q?Mario_Bla=c5=beevi=c4=87?=) Date: Sat, 24 Dec 2016 12:19:47 -0500 Subject: Data.Functor.{Product,Sum} functions In-Reply-To: References: Message-ID: On 2016-12-23 07:02 PM, Baldur Blöndal wrote: > Let's see if any of these are useful (a lot more at > https://ghc.haskell.org/trac/ghc/ticket/13026) > > (||||) :: (f a -> b) -> (g a -> b) -> ((Sum f g) a -> b) > f |||| g = \case > InL fa -> f fa > InR ga -> g ga The corresponding destructor function in Data.Either is called either: either :: (a -> c) -> (b -> c) -> Either a b -> c Thus the most logical name for the Sum destructor would be sum. You can always import Data.Functor.Product qualified as Product to avoid clashes. In the same vein, I propose adding uncurry :: (f a -> g a -> b) -> Product f g a -> b uncurry f (Pair a b) = f a b > (&&&&) :: (a -> f b) -> (a -> g b) -> (a -> (Product f g) b) > (f &&&& g) a = f a `Pair` g a I'm not fond of that name. Also, f &&&& g == uncurry Pair . (f &&& g) From david.feuer at gmail.com Sat Dec 24 21:49:32 2016 From: david.feuer at gmail.com (David Feuer) Date: Sat, 24 Dec 2016 16:49:32 -0500 Subject: Data.Functor.{Product,Sum} functions In-Reply-To: References: Message-ID: Er ... that was silly. I guess bifoldMap isn't really (||||), exactly. It's pretty much `either`, but needs to have a Monoid wrapper. The generalization I was roughly imagining would be a sort of higher-kinded Bifoldable1: class Bifoldable1' p where bifoldMap1' :: Semigroup m => (f a -> m) -> (g a -> m) -> p f g a -> m which would then get the job done with Data.Semigroup.First. But that's getting pretty far from the point, so, we need `||||` or `sum` or whatever. On Sat, Dec 24, 2016 at 7:43 AM, David Feuer wrote: > This |||| is the sum eliminator. We can't call it `sum`, but maybe > `sumE`? I do think it should be included with some name. Another > option might be to drag Data.Bifoldable into base from bifunctors; > (||||) = bifoldMap, but I think the case for a specialized name is > still pretty good. > > &&&& is definitely a nice thing to have. However, (&&&&) = liftA2 > Pair, so I'm not convinced we need to give it its own name. > > On Fri, Dec 23, 2016 at 7:02 PM, Baldur Blöndal wrote: >> Let's see if any of these are useful (a lot more at >> https://ghc.haskell.org/trac/ghc/ticket/13026) >> >> (||||) :: (f a -> b) -> (g a -> b) -> ((Sum f g) a -> b) >> f |||| g = \case >> InL fa -> f fa >> InR ga -> g ga >> >> (&&&&) :: (a -> f b) -> (a -> g b) -> (a -> (Product f g) b) >> (f &&&& g) a = f a `Pair` g a >> >> I couldn't think of any for Data.Functor.Compose, names are up for >> bikeshedding >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> From baldurpet at gmail.com Tue Dec 27 05:08:54 2016 From: baldurpet at gmail.com (=?UTF-8?Q?Baldur_Bl=C3=B6ndal?=) Date: Tue, 27 Dec 2016 05:08:54 +0000 Subject: Data.Functor.{Product,Sum} functions In-Reply-To: References: Message-ID: I updated the proposal with (again more information in https://ghc.haskell.org/trac/ghc/ticket/13026#comment:5) runSum :: Sum f g a -> Either (f a) (g a)runSum = Left |||| Right runProduct :: Product f g a -> (f a, g a)runProduct (Pair fa ga) = (fa, ga) I found one for ‘Data.Functor.Compose’ o :: Functor m => (b -> n c) -> (a -> m b) -> (a -> Compose m n c)o f g = Compose . fmap f . g -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon.jakobi at googlemail.com Wed Dec 28 03:58:38 2016 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Wed, 28 Dec 2016 04:58:38 +0100 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary Message-ID: read [1] is an easy way to introduce runtime exceptions into programs, but its documentation doesn't sufficiently warn of this danger. read's safe alternatives, Text.Read.readMaybe [2] and Text.Read.readEither [3], are relatively unknown and too hard to find. To guide users (particularly newcomers) away from read and towards readMaybe and readEither, I propose to 1. Add readMaybe to the Prelude 2. Add readEither to the Prelude 3. Change the documentation for read to point out the partiality and to recommend the above alternatives: The haddocks for read currently read: > The read function reads input from a string, which must be completely consumed by the input process. I propose to add a paragraph roughly like this: > Note: read will throw an error if the parse fails. If there's any uncertainty w.r.t. the shape of the input, readMaybe or readEither should be used instead. Name clashes: A cursory code search on Github for readMaybe [4] reveals many existing definitions, mostly with the same type (Read a => String -> Maybe a) and definition. The same search for readEither [5] shows mostly GHC forks. Design issues: I am somewhat doubtful about the benefit of readEither over readMaybe: While readEither does give additional info on the kind of parse failures, that information is encoded in a String error message, from which it must be parsed if it is needed in the program. As the different parts of the proposal can be implemented independently of each other, please vote separately on each part of the proposal. Discussion period: 4 weeks. Cheers, Simon [1] http://hackage.haskell.org/package/base-4.9.0.0/docs/Prelude.html#v:read [2] http://hackage.haskell.org/package/base-4.9.0.0/docs/Text-Read.html#v:readMaybe [3] http://hackage.haskell.org/package/base-4.9.0.0/docs/Text-Read.html#v:readEither [4] https://github.com/search?l=Haskell&q=readMaybe&type=Code [5] https://github.com/search?l=Haskell&q=readEither&type=Code From ivan.miljenovic at gmail.com Wed Dec 28 04:09:25 2016 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Wed, 28 Dec 2016 15:09:25 +1100 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: Message-ID: On 28 December 2016 at 14:58, Simon Jakobi via Libraries wrote: > read [1] is an easy way to introduce runtime exceptions into programs, > but its documentation doesn't sufficiently warn of this danger. read's > safe alternatives, Text.Read.readMaybe [2] and Text.Read.readEither > [3], are relatively unknown and too hard to find. > > To guide users (particularly newcomers) away from read and towards > readMaybe and readEither, I propose to > > 1. Add readMaybe to the Prelude +1 > 2. Add readEither to the Prelude -0.1 (because as you stated in your "Design Issues" section, I doubt its usefulness). > 3. Change the documentation for read to point out the partiality and > to recommend the above alternatives: > > The haddocks for read currently read: > > > The read function reads input from a string, which must be > completely consumed by the input process. > > I propose to add a paragraph roughly like this: > > > Note: read will throw an error if the parse fails. If there's > any uncertainty w.r.t. the shape of the input, readMaybe or readEither > should be used instead. +1 > > > Name clashes: > > A cursory code search on Github for readMaybe [4] reveals many > existing definitions, mostly with the same type (Read a => String -> > Maybe a) and definition. The same search for readEither [5] shows > mostly GHC forks. > > Design issues: > > I am somewhat doubtful about the benefit of readEither over readMaybe: > While readEither does give additional info on the kind of parse > failures, that information is encoded in a String error message, from > which it must be parsed if it is needed in the program. > > > As the different parts of the proposal can be implemented > independently of each other, please vote separately on each part of > the proposal. > > Discussion period: 4 weeks. > > Cheers, > Simon > > [1] http://hackage.haskell.org/package/base-4.9.0.0/docs/Prelude.html#v:read > [2] http://hackage.haskell.org/package/base-4.9.0.0/docs/Text-Read.html#v:readMaybe > [3] http://hackage.haskell.org/package/base-4.9.0.0/docs/Text-Read.html#v:readEither > [4] https://github.com/search?l=Haskell&q=readMaybe&type=Code > [5] https://github.com/search?l=Haskell&q=readEither&type=Code > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From david.feuer at gmail.com Wed Dec 28 04:46:46 2016 From: david.feuer at gmail.com (David Feuer) Date: Tue, 27 Dec 2016 23:46:46 -0500 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: Message-ID: On Dec 27, 2016 10:59 PM, "Simon Jakobi via Libraries" < libraries at haskell.org> wrote: read [1] is an easy way to introduce runtime exceptions into programs, but its documentation doesn't sufficiently warn of this danger. read's safe alternatives, Text.Read.readMaybe [2] and Text.Read.readEither [3], are relatively unknown and too hard to find. A while back I brought up the idea of adding custom warning "classes", allowing such functions to be tagged partial. I should probably put together a proper proposal now that we have that process. Personally, I'd love to remove read from the Prelude, but that would be hard. 1. Add readMaybe to the Prelude +1 2. Add readEither to the Prelude +1 3. Change the documentation for read to point out the partiality and to recommend the above alternatives: +1 > If there's any uncertainty w.r.t. the shape of the input, readMaybe or readEither should be used instead. I would put it more strongly: read should be applied only to strings that are known to have been produced by methods of the Show class. Design issues: I am somewhat doubtful about the benefit of readEither over readMaybe: While readEither does give additional info on the kind of parse failures, that information is encoded in a String error message, from which it must be parsed if it is needed in the program. It's still the right way to handle error reporting for Read. Very wrong: do x <- read <$> getInput use x Correct, in some contexts, but extremely lousy: do x <- read <$> getInput evaluate (force x) use x Correct, but uninformative: do Just x <- readMaybe <$> getInput use x Correct and informative: do ip <- readEither <$> getInput either (throwIO . parseError) use ip (For some value of parseError) Or, when reasonable, do ip <- readEither <$> getInput either (\m -> displayMessage m *> tryAgain) ip -------------- next part -------------- An HTML attachment was scrubbed... URL: From ivan.miljenovic at gmail.com Wed Dec 28 04:56:57 2016 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Wed, 28 Dec 2016 15:56:57 +1100 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: Message-ID: On 28 December 2016 at 15:46, David Feuer wrote: > On Dec 27, 2016 10:59 PM, "Simon Jakobi via Libraries" > wrote: > > read [1] is an easy way to introduce runtime exceptions into programs, > but its documentation doesn't sufficiently warn of this danger. read's > safe alternatives, Text.Read.readMaybe [2] and Text.Read.readEither > [3], are relatively unknown and too hard to find. > > > A while back I brought up the idea of adding custom warning "classes", > allowing such functions to be tagged partial. I should probably put together > a proper proposal now that we have that process. Personally, I'd love to > remove read from the Prelude, but that would be hard. > > > 1. Add readMaybe to the Prelude > > > +1 > > 2. Add readEither to the Prelude > > > +1 > > 3. Change the documentation for read to point out the partiality and > to recommend the above alternatives: > > > +1 > > > > If there's > any uncertainty w.r.t. the shape of the input, readMaybe or readEither > should be used instead. > > > I would put it more strongly: > > read should be applied only to strings that are known to have been produced > by methods of the Show class. More so than that: you know that it's for this exact type. (Though I have [ab]used `read` to convert a String value consisting solely of digits to an `Int` within a parsing library.) > > > > Design issues: > > I am somewhat doubtful about the benefit of readEither over readMaybe: > While readEither does give additional info on the kind of parse > failures, that information is encoded in a String error message, from > which it must be parsed if it is needed in the program. > > > It's still the right way to handle error reporting for Read. > > Very wrong: > > do > x <- read <$> getInput > use x > > Correct, in some contexts, but extremely lousy: > > do > x <- read <$> getInput > evaluate (force x) > use x > > Correct, but uninformative: > > do > Just x <- readMaybe <$> getInput > use x > > Correct and informative: > > do > ip <- readEither <$> getInput > either (throwIO . parseError) use ip > (For some value of parseError) > > Or, when reasonable, > > do > ip <- readEither <$> getInput > either (\m -> displayMessage m *> tryAgain) ip I would argue that if you're doing something like this then you should really be using a proper combinator parsing library. -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From simon.jakobi at googlemail.com Wed Dec 28 07:47:03 2016 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Wed, 28 Dec 2016 08:47:03 +0100 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: Message-ID: 2016-12-28 5:46 GMT+01:00 David Feuer : > > > If there's > > any uncertainty w.r.t. the shape of the input, readMaybe or readEither > > should be used instead. > > > I would put it more strongly: > > read should be applied only to strings that are known to have been produced > by methods of the Show class. I agree, that's more clear. From andrew.thaddeus at gmail.com Wed Dec 28 14:40:25 2016 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Wed, 28 Dec 2016 09:40:25 -0500 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: Message-ID: 1. +1 2. ambivalent, I've never actually seen anyone use readEither, but it doesn't really hurt for it to be there since it isn't stealing anything valuable from the namespace. 3. +1 In my mind, the single most important part of this is part (3), improving the docs. All partial functions defined in base should come with warnings about this in the docs, along with hyperlinks to total functions for accomplishing the same thing. -Andrew Martin On Tue, Dec 27, 2016 at 10:58 PM, Simon Jakobi via Libraries < libraries at haskell.org> wrote: > read [1] is an easy way to introduce runtime exceptions into programs, > but its documentation doesn't sufficiently warn of this danger. read's > safe alternatives, Text.Read.readMaybe [2] and Text.Read.readEither > [3], are relatively unknown and too hard to find. > > To guide users (particularly newcomers) away from read and towards > readMaybe and readEither, I propose to > > 1. Add readMaybe to the Prelude > 2. Add readEither to the Prelude > 3. Change the documentation for read to point out the partiality and > to recommend the above alternatives: > > The haddocks for read currently read: > > > The read function reads input from a string, which must be > completely consumed by the input process. > > I propose to add a paragraph roughly like this: > > > Note: read will throw an error if the parse fails. If there's > any uncertainty w.r.t. the shape of the input, readMaybe or readEither > should be used instead. > > > Name clashes: > > A cursory code search on Github for readMaybe [4] reveals many > existing definitions, mostly with the same type (Read a => String -> > Maybe a) and definition. The same search for readEither [5] shows > mostly GHC forks. > > Design issues: > > I am somewhat doubtful about the benefit of readEither over readMaybe: > While readEither does give additional info on the kind of parse > failures, that information is encoded in a String error message, from > which it must be parsed if it is needed in the program. > > > As the different parts of the proposal can be implemented > independently of each other, please vote separately on each part of > the proposal. > > Discussion period: 4 weeks. > > Cheers, > Simon > > [1] http://hackage.haskell.org/package/base-4.9.0.0/docs/ > Prelude.html#v:read > [2] http://hackage.haskell.org/package/base-4.9.0.0/docs/ > Text-Read.html#v:readMaybe > [3] http://hackage.haskell.org/package/base-4.9.0.0/docs/ > Text-Read.html#v:readEither > [4] https://github.com/search?l=Haskell&q=readMaybe&type=Code > [5] https://github.com/search?l=Haskell&q=readEither&type=Code > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -- -Andrew Thaddeus Martin -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.thaddeus at gmail.com Wed Dec 28 14:44:39 2016 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Wed, 28 Dec 2016 09:44:39 -0500 Subject: Data.Functor.{Product,Sum} functions In-Reply-To: References: Message-ID: I do not like using infix operators as names. Similar to others, I like the Sum eliminator and am skeptical of the value that the &&&& operator provides. On Fri, Dec 23, 2016 at 7:02 PM, Baldur Blöndal wrote: > Let's see if any of these are useful (a lot more at > https://ghc.haskell.org/trac/ghc/ticket/13026) > > (||||) :: (f a -> b) -> (g a -> b) -> ((Sum f g) a -> b) > f |||| g = \case > InL fa -> f fa > InR ga -> g ga > > (&&&&) :: (a -> f b) -> (a -> g b) -> (a -> (Product f g) b) > (f &&&& g) a = f a `Pair` g a > > I couldn't think of any for Data.Functor.Compose, names are up for > bikeshedding > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > -- -Andrew Thaddeus Martin -------------- next part -------------- An HTML attachment was scrubbed... URL: From amindfv at gmail.com Wed Dec 28 16:36:25 2016 From: amindfv at gmail.com (amindfv at gmail.com) Date: Wed, 28 Dec 2016 10:36:25 -0600 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: Message-ID: What about other functions from 'safe', eg headMay, atMay, readNote, etc? Tom > El 28 dic 2016, a las 08:40, Andrew Martin escribió: > > 1. +1 > 2. ambivalent, I've never actually seen anyone use readEither, but it doesn't really hurt for it to be there since it isn't stealing anything valuable from the namespace. > 3. +1 > > In my mind, the single most important part of this is part (3), improving the docs. All partial functions defined in base should come with warnings about this in the docs, along with hyperlinks to total functions for accomplishing the same thing. > > -Andrew Martin > >> On Tue, Dec 27, 2016 at 10:58 PM, Simon Jakobi via Libraries wrote: >> read [1] is an easy way to introduce runtime exceptions into programs, >> but its documentation doesn't sufficiently warn of this danger. read's >> safe alternatives, Text.Read.readMaybe [2] and Text.Read.readEither >> [3], are relatively unknown and too hard to find. >> >> To guide users (particularly newcomers) away from read and towards >> readMaybe and readEither, I propose to >> >> 1. Add readMaybe to the Prelude >> 2. Add readEither to the Prelude >> 3. Change the documentation for read to point out the partiality and >> to recommend the above alternatives: >> >> The haddocks for read currently read: >> >> > The read function reads input from a string, which must be >> completely consumed by the input process. >> >> I propose to add a paragraph roughly like this: >> >> > Note: read will throw an error if the parse fails. If there's >> any uncertainty w.r.t. the shape of the input, readMaybe or readEither >> should be used instead. >> >> >> Name clashes: >> >> A cursory code search on Github for readMaybe [4] reveals many >> existing definitions, mostly with the same type (Read a => String -> >> Maybe a) and definition. The same search for readEither [5] shows >> mostly GHC forks. >> >> Design issues: >> >> I am somewhat doubtful about the benefit of readEither over readMaybe: >> While readEither does give additional info on the kind of parse >> failures, that information is encoded in a String error message, from >> which it must be parsed if it is needed in the program. >> >> >> As the different parts of the proposal can be implemented >> independently of each other, please vote separately on each part of >> the proposal. >> >> Discussion period: 4 weeks. >> >> Cheers, >> Simon >> >> [1] http://hackage.haskell.org/package/base-4.9.0.0/docs/Prelude.html#v:read >> [2] http://hackage.haskell.org/package/base-4.9.0.0/docs/Text-Read.html#v:readMaybe >> [3] http://hackage.haskell.org/package/base-4.9.0.0/docs/Text-Read.html#v:readEither >> [4] https://github.com/search?l=Haskell&q=readMaybe&type=Code >> [5] https://github.com/search?l=Haskell&q=readEither&type=Code >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > > > -- > -Andrew Thaddeus Martin > _______________________________________________ > 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 lemming at henning-thielemann.de Wed Dec 28 16:12:44 2016 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Wed, 28 Dec 2016 17:12:44 +0100 (CET) Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: Message-ID: On Wed, 28 Dec 2016, Simon Jakobi via Libraries wrote: > read [1] is an easy way to introduce runtime exceptions into programs, > but its documentation doesn't sufficiently warn of this danger. read's > safe alternatives, Text.Read.readMaybe [2] and Text.Read.readEither > [3], are relatively unknown and too hard to find. > > To guide users (particularly newcomers) away from read and towards > readMaybe and readEither, I propose to > > 1. Add readMaybe to the Prelude > 2. Add readEither to the Prelude I do not like to add more stuff to Prelude. It is pretty cumbersome to write packages that equally work for Prelude versions before and after this change. In order to avoid preprocessor clutter I tend to import explicitly from Prelude or other 'base' modules. You can easily import these functions from Text.Read. I would be ok with deprecating 'read'. Generally I think that the Read class is overused. Strictly spoken, it would be only sensible to parse Haskell expressions with it, but actually it is mostly used for parsing user input like numbers. But why should a user enter a number in a Haskell compatible way or even the way, the current 'show' implementation does? > 3. Change the documentation for read to point out the partiality and > to recommend the above alternatives: I prefer that. From gale at sefer.org Wed Dec 28 19:29:37 2016 From: gale at sefer.org (Yitzchak Gale) Date: Wed, 28 Dec 2016 21:29:37 +0200 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: Message-ID: Henning Thielemann wrote: > I do not like to add more stuff to Prelude. It is pretty cumbersome to write > packages that equally work for Prelude versions before and after this > change. In order to avoid preprocessor clutter I tend to import explicitly > from Prelude or other 'base' modules. You can easily import these functions > from Text.Read. That's all true. After an earlier period of continual change to the Prelude, we have had a period where the Prelude was effectively frozen, for this reason. But after some years of a frozen Prelude, many people feel that we have accumulated cruft, and that now the Prelude needs to be updated again to match modern practice. A sudden upheaval doesn't seem prudent, but incremental changes like this one that give a lot of benefit for little cost seem worthwhile. > Generally I think that the Read class is overused. Strictly spoken, it would > be only sensible to parse Haskell expressions with it, but actually it is > mostly used for parsing user input like numbers. Nowadays parsing numbers can use the more efficient and correct combinators in places like Data.Text.Read and Data.Attoparsec. But there are other common uses of Read (when performance does not matter), such as: o Debugging and test suites o Easy serialization o An input data file format that parses for free Regards, Yitz From gale at sefer.org Wed Dec 28 19:29:46 2016 From: gale at sefer.org (Yitzchak Gale) Date: Wed, 28 Dec 2016 21:29:46 +0200 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: Message-ID: Tom wrote: > What about other functions from 'safe', > eg headMay, atMay, readNote, etc? The standard spelling of "headMay", already included in base, is "listToMaybe". In general, once you have readMaybe, NonEmpty, and the rich set of combinators and instances we have today for Maybe and Either, the safe library really isn't needed anymore. It was a great innovation at the time - it brought the problem of partial functions to the forefront. But I prefer using the standard names we have for those functions nowadays, or occasionally using a simple combination of two of them. The function names in the safe library always seemed a bit awkward to me. YItz From gale at sefer.org Wed Dec 28 19:39:29 2016 From: gale at sefer.org (Yitzchak Gale) Date: Wed, 28 Dec 2016 21:39:29 +0200 Subject: Proposal: Add NonEmpty constructors to the Prelude Message-ID: In continuation of Simon Jakobi's proposal for a small incremental change to the Prelude to make it more conducive to partial-function-free programming, https://mail.haskell.org/pipermail/libraries/2016-December/027496.html and after some encouragement from the community on reddit, I propose adding the basic constructors of NonEmpty to the Prelude: nonEmpty, (:|), and the type constructor NonEmpty. In practice, users of NonEmpty will often still need a qualified import of Data.List.NonEmpty. But having the constructors available in the Prelude will make the use of NonEmpty more common, and will make programming without partial functions feel more natural and standard. Note: This proposal is separate from Simon's and should not interfere with the acceptance of Simon's. But it is related in that it attempts to achieve the same goals. Discussion period: Until the end of the discussion period of Simon's proposal. Thanks, Yitz From lemming at henning-thielemann.de Wed Dec 28 19:41:53 2016 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Wed, 28 Dec 2016 20:41:53 +0100 (CET) Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: Message-ID: On Wed, 28 Dec 2016, Yitzchak Gale wrote: > But after some years of a frozen Prelude, many people feel that > we have accumulated cruft, and that now the Prelude needs to > be updated again to match modern practice. A sudden upheaval > doesn't seem prudent, but incremental changes like this one that > give a lot of benefit for little cost seem worthwhile. What precisely is the problem of importing readMaybe and readEither from Text.Read? The current state means you have to import them, that is, you have to add one import line and this solution works back to GHC-7.6. If we add readMaybe and readEither to Prelude, you may be happy to not add a new import line but you force your library users to the newest version of GHC and you risk to make his programs uncompilable because it may depend on other packages that are not (yet) updated to the newest GHC. If you care for multiple versions of GHC you have to make much more cumbersome import statements or add multiple lines of preprocessor. This seems to be too much effort if 'read' calls should be replaced by other functions anyway. From simon.jakobi at googlemail.com Wed Dec 28 22:22:09 2016 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Wed, 28 Dec 2016 23:22:09 +0100 Subject: Proposal: Add NonEmpty constructors to the Prelude In-Reply-To: References: Message-ID: 2016-12-28 20:39 GMT+01:00 Yitzchak Gale : > I propose adding the basic constructors of NonEmpty to > the Prelude: nonEmpty, (:|), and the type constructor NonEmpty. +1 I'd still like to point out that all three names are exposed by several other packages, mostly with different types: * nonEmpty: https://www.stackage.org/lts-7.14/hoogle?q=nonEmpty&exact=on * (:|): https://www.stackage.org/lts-7.14/hoogle?q=%3A%7C&exact=on * NonEmpty: https://www.stackage.org/lts-7.14/hoogle?q=NonEmpty&exact=on From simon.jakobi at googlemail.com Thu Dec 29 01:39:39 2016 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Thu, 29 Dec 2016 02:39:39 +0100 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: Message-ID: 2016-12-28 17:12 GMT+01:00 Henning Thielemann : > I would be ok with deprecating 'read'. That seems like a reasonable idea but I would prefer to discuss it in a separate thread. From simon.jakobi at googlemail.com Thu Dec 29 02:42:30 2016 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Thu, 29 Dec 2016 03:42:30 +0100 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: Message-ID: 2016-12-28 20:41 GMT+01:00 Henning Thielemann : > What precisely is the problem of importing readMaybe and readEither from > Text.Read? Those who are aware that these functions reside in Text.Read can of course import them with little effort. The point of exporting these functions from the Prelude is to present them to everyone else, particularly newcomers who might otherwise use read without being aware of its partiality. > The current state means you have to import them, that is, you > have to add one import line and this solution works back to GHC-7.6. If we > add readMaybe and readEither to Prelude, you may be happy to not add a new > import line but you force your library users to the newest version of GHC > and you risk to make his programs uncompilable because it may depend on > other packages that are not (yet) updated to the newest GHC. If you care for > multiple versions of GHC you have to make much more cumbersome import > statements or add multiple lines of preprocessor. These concerns apply to any change to the Prelude. > This seems to be too much effort if 'read' calls should be replaced by other > functions anyway. I disagree. While Read may not be the right way (TM) to parse numbers, it currently is the standard way presented to newcomers. I invite you to google for "haskell parse int string"! I don't want to discourage anyone from bringing a better solution into base, but at this point I would like to incrementally improve the status quo. I think the cost that we impose on package maintainers by introducing readMaybe (and possibly readEither) into Prelude is reasonable. Cheers, Simon From shumovichy at gmail.com Thu Dec 29 11:32:48 2016 From: shumovichy at gmail.com (Yuras Shumovich) Date: Thu, 29 Dec 2016 14:32:48 +0300 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: Message-ID: <1483011168.4381.1.camel@gmail.com> On Thu, 2016-12-29 at 03:42 +0100, Simon Jakobi via Libraries wrote: > 2016-12-28 20:41 GMT+01:00 Henning Thielemann mann.de>: > > What precisely is the problem of importing readMaybe and readEither > > from > > Text.Read? > > Those who are aware that these functions reside in Text.Read can of > course import them with little effort. > > The point of exporting these functions from the Prelude is to present > them to everyone else, particularly newcomers who might otherwise use > read without being aware of its partiality. Documenting partiality of `read` should be enough IMO. > > > The current state means you have to import them, that is, you > > have to add one import line and this solution works back to GHC- > > 7.6. If we > > add readMaybe and readEither to Prelude, you may be happy to not > > add a new > > import line but you force your library users to the newest version > > of GHC > > and you risk to make his programs uncompilable because it may > > depend on > > other packages that are not (yet) updated to the newest GHC. If you > > care for > > multiple versions of GHC you have to make much more cumbersome > > import > > statements or add multiple lines of preprocessor. > > These concerns apply to any change to the Prelude. Yet it is a valid argument. We should be careful with Prelude. > > > This seems to be too much effort if 'read' calls should be replaced > > by other > > functions anyway. > > I disagree. While Read may not be the right way (TM) to parse > numbers, > it currently is the standard way presented to newcomers. I invite you > to google for "haskell parse int string"! > > I don't want to discourage anyone from bringing a better solution > into > base, but at this point I would like to incrementally improve the > status quo. I think the cost that we impose on package maintainers by > introducing readMaybe (and possibly readEither) into Prelude is > reasonable. Incremental improvements should go in some specific direction, otherwise they are random steps in the design space. I'm not sure optimizing for newcomers is a good direction. If the goal is to remove partial functions from Prelude, then there should be a clear plan where adding `readMaybe` is just the first step. Without the plan we'll never do the next step or we'll do it in the opposite direction. Adding `readMaybe` to Prelude makes it discoverable, but we can't add every useful function into Prelude. IMO fat Prelude in the reason for bad discoverability -- if something is not in Prelude, then it doesn't exist, because Prelude already contains (worse) alternative. To solve that, we can move everything related to `Read` type class into one module, e.g. Data.Read, and then `read` and `readMaybe` will have the same discoverability. If it is the goal, then adding `readMaybe` to Prelude is a step in wrong direction. I'm against the proposal (except the documentation part) until it is presented in wider context. > > Cheers, > Simon > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From andreas.abel at ifi.lmu.de Thu Dec 29 12:48:48 2016 From: andreas.abel at ifi.lmu.de (Andreas Abel) Date: Thu, 29 Dec 2016 13:48:48 +0100 Subject: Proposal: Add NonEmpty constructors to the Prelude In-Reply-To: References: Message-ID: What are the types and definitions of > nonEmpty, (:|), and the type constructor NonEmpty. ? Must be something generic, overloaded, given the name... On 28.12.2016 20:39, Yitzchak Gale wrote: > In continuation of Simon Jakobi's proposal for a small > incremental change to the Prelude to make it more > conducive to partial-function-free programming, > > https://mail.haskell.org/pipermail/libraries/2016-December/027496.html > > and after some encouragement from the community on reddit, > I propose adding the basic constructors of NonEmpty to > the Prelude: nonEmpty, (:|), and the type constructor NonEmpty. > > In practice, users of NonEmpty will often still need a qualified > import of Data.List.NonEmpty. But having the constructors > available in the Prelude will make the use of NonEmpty more > common, and will make programming without partial functions > feel more natural and standard. > > Note: This proposal is separate from Simon's and should not > interfere with the acceptance of Simon's. But it is related in > that it attempts to achieve the same goals. > > Discussion period: Until the end of the discussion period of > Simon's proposal. > > Thanks, > Yitz > _______________________________________________ > 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 simon.jakobi at googlemail.com Thu Dec 29 12:52:19 2016 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Thu, 29 Dec 2016 13:52:19 +0100 Subject: Proposal: Add NonEmpty constructors to the Prelude In-Reply-To: References: Message-ID: 2016-12-29 13:48 GMT+01:00 Andreas Abel : > What are the types and definitions of > >> nonEmpty, (:|), and the type constructor NonEmpty. > > ? See http://hackage.haskell.org/package/base-4.9.0.0/docs/Data-List-NonEmpty.html From Henrik.Nilsson at nottingham.ac.uk Thu Dec 29 13:34:45 2016 From: Henrik.Nilsson at nottingham.ac.uk (Henrik Nilsson) Date: Thu, 29 Dec 2016 13:34:45 +0000 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: <1483011168.4381.1.camel@gmail.com> References: <1483011168.4381.1.camel@gmail.com> Message-ID: <586510F5.6080108@exmail.nottingham.ac.uk> Hi, Yuras Shumovich said: > >> you may be happy to not > >> add a new > >> import line but you force your library users to the newest version > >> of GHC > >> and you risk to make his programs uncompilable because it may > >> depend on > >> other packages that are not (yet) updated to the newest GHC. If you > >> care for > >> multiple versions of GHC you have to make much more cumbersome > >> import > >> statements or add multiple lines of preprocessor. > >> > > These concerns apply to any change to the Prelude. > Yet it is a valid argument. We should be careful with Prelude. I can only second this. It is *very* frustrating when code fails to compile with an slightly out-of-date version of GHC just because someone, perhaps a beginner, perhaps mostly by accident, use a new "nifty" add on to the prelude just because it happens to be there. I recently had this experience with code written for a recent version of GHC I needed to make work with GHC 7.8. I had to make rather a lot of edits that ultimately turned out to be entirely trivial, in many cases because new, alternative names had been added for existing features. When I compared the "before" and "after" versions of the code, I didn't find the new version an iota more readable or elegant than the old one on balance because the number of affected lines in relative terms was small so the only real effect of the additions I had to get rid of was to increase the cognitive burden of the reader in terms of a larger "Prelude vocabulary". I wouldn't have minded half as much if the new features had been signalled by explicit imports. And most likely, in many cases, the new features would not have been used at all as they were not particularly important for this particular piece of code (in terms of increasing readability etc). Which is not to at all to say that these features might not be very useful for other pieces of code. In which case they could just have just be imported explicitly. So indeed, as Yuras said: "We should be careful with the Prelude". /Henrik This message and any attachment are intended solely for the addressee and may contain confidential information. If you have received this message in error, please send it back to me, and immediately delete it. Please do not use, copy or disclose the information contained in this message or in any attachment. Any views or opinions expressed by the author of this email do not necessarily reflect the views of the University of Nottingham. This message has been checked for viruses but the contents of an attachment may still contain software viruses which could damage your computer system, you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation. From Henrik.Nilsson at nottingham.ac.uk Thu Dec 29 14:26:54 2016 From: Henrik.Nilsson at nottingham.ac.uk (Henrik Nilsson) Date: Thu, 29 Dec 2016 14:26:54 +0000 Subject: Proposal: Add NonEmpty constructors to the Prelude In-Reply-To: References: Message-ID: <58651D2E.5010504@exmail.nottingham.ac.uk> Hi, On 12/29/2016 12:48 PM, Andreas Abel wrote: > What are the types and definitions of > > > nonEmpty, (:|), and the type constructor NonEmpty. > > ? > > Must be something generic, overloaded, given the name... Indeed, one would assume so, given the names. But: > > What are the types and definitions of > > > >> nonEmpty, (:|), and the type constructor NonEmpty. > > > > ? > > See http://hackage.haskell.org/package/base-4.9.0.0/docs/ > Data-List-NonEmpty.html there is nothing generic at all about these: I am assuming that the idea is that these three definitions will be made available for unqualified use (while all other library functions for programming with non-empty lists would have to be imported explicitly from Data.List.NonEmpty, as currently is the case). But these are really poor names for something this specific being made available unqualified everywhere: there are lots of things that could be called "NonEmpty" or "nonEmpty", and ":|" is a perfectly good combinator name for other purposes. So this addition would do little beside increasing the footprint of the Prelude and causing issues clashes with code that happens to use these names already. To quote Yuras Shumovich from a related thread (Add readMaybe (and possibly readEither) to Prelude): "We should be careful with Prelude." Additionally, as is evidenced by the type signatures of the module NonEmpty, the utility of keeping track of non-empty lists at the type level in a language like Haskell is in general limited (which is not to say that it cannot be very useful sometimes). Even in a language with dependent types the approach (of integrating properties with data types) is not always smooth as it may lead to a proliferation of different related but distinct types which quickly becomes clunky. As far as I am aware, solving this conundrum is still an open research problem. (And nothing new under the sun, either: people familiar with Pascal or Ada will have had similar experiences with a proliferation of integral types of various ranges. In simple cases, very useful to ensure e.g. an array index is not out of bounds, but does not go very far.) Finally, why single out "non-empty" specifically as a property worthy to keep track at the type level in the prelude? Why not lists of finite length as well, for example? That could help ensuring termination. (Just to be clear: I am not proposing this. I am just saying that I can't see how adding variations of existing types with specific properties to the prelude possibly can result in a principled design for a language like Haskell as it currently stands.) /Henrik This message and any attachment are intended solely for the addressee and may contain confidential information. If you have received this message in error, please send it back to me, and immediately delete it. Please do not use, copy or disclose the information contained in this message or in any attachment. Any views or opinions expressed by the author of this email do not necessarily reflect the views of the University of Nottingham. This message has been checked for viruses but the contents of an attachment may still contain software viruses which could damage your computer system, you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation. From ekmett at gmail.com Thu Dec 29 15:33:01 2016 From: ekmett at gmail.com (Edward Kmett) Date: Thu, 29 Dec 2016 10:33:01 -0500 Subject: Proposal: Add NonEmpty constructors to the Prelude In-Reply-To: References: Message-ID: I'm personally -1 on this proposal *at this time*. Adding these to the footprint of Prelude means everybody who has written any data type with a data constructor named :| breaks, every combinator named nonEmpty, NonEmpty type or class... so we shouldn't do this lightly. That said, Semigroup is slated to become a superclass of Monoid in 8.6 and move into Prelude as part of the timeline on https://prime.haskell.org/wiki/Libraries/Proposals and Semigroup has sconcat as a member, which references NonEmpty. At that point the case becomes much stronger, and the need to decide how to handle sconcat for the Prelude acts as a forcing function for this decision. On the other hand, we don't have many classes exported from Prelude partially, but we do have them: Functor (<$), Read (readPrec, readListPrec), Floating (log1p, expm1, etc.) come to mind as members we avoid exporting from Prelude. So while there is precedent for continuing to hide "messy" implementation details, at that point the weight of simplicity of explanation may come down on the other side of the argument. With all that in mind I'm -1 if we're talking about adding this in 8.4, but I'm largely neutral and maybe even weakly positive about it for 8.6 as part of the larger Semigroup migration and would be happy to accept either the hidden detail solution or a solution that dragged NonEmpty into base based on community feedback. -Edward On Wed, Dec 28, 2016 at 2:39 PM, Yitzchak Gale wrote: > In continuation of Simon Jakobi's proposal for a small > incremental change to the Prelude to make it more > conducive to partial-function-free programming, > > https://mail.haskell.org/pipermail/libraries/2016-December/027496.html > > and after some encouragement from the community on reddit, > I propose adding the basic constructors of NonEmpty to > the Prelude: nonEmpty, (:|), and the type constructor NonEmpty. > > In practice, users of NonEmpty will often still need a qualified > import of Data.List.NonEmpty. But having the constructors > available in the Prelude will make the use of NonEmpty more > common, and will make programming without partial functions > feel more natural and standard. > > Note: This proposal is separate from Simon's and should not > interfere with the acceptance of Simon's. But it is related in > that it attempts to achieve the same goals. > > Discussion period: Until the end of the discussion period of > Simon's proposal. > > Thanks, > Yitz > _______________________________________________ > 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 Thu Dec 29 17:57:14 2016 From: andreas.abel at ifi.lmu.de (Andreas Abel) Date: Thu, 29 Dec 2016 18:57:14 +0100 Subject: Proposal: Add NonEmpty constructors to the Prelude In-Reply-To: <58651D2E.5010504@exmail.nottingham.ac.uk> References: <58651D2E.5010504@exmail.nottingham.ac.uk> Message-ID: <72213f32-b053-d15e-c3fb-65d8d7e61879@ifi.lmu.de> Since "nonEmpty" is a predicate that could apply any kind of collection, not just lists, I am strongly -1 on such a proposal. Similarly, "NonEmpty" misses a "List", it should be called "NonEmptyList". --Andreas On 29.12.2016 15:26, Henrik Nilsson wrote: > Hi, > > On 12/29/2016 12:48 PM, Andreas Abel wrote: >> What are the types and definitions of >> >> > nonEmpty, (:|), and the type constructor NonEmpty. >> >> ? >> >> Must be something generic, overloaded, given the name... > > Indeed, one would assume so, given the names. > > But: > >> > What are the types and definitions of >> > >> >> nonEmpty, (:|), and the type constructor NonEmpty. >> > >> > ? >> >> See http://hackage.haskell.org/package/base-4.9.0.0/docs/ >> Data-List-NonEmpty.html > > there is nothing generic at all about these: > > I am assuming that the idea is that these three definitions > will be made available for unqualified use (while all other > library functions for programming with non-empty lists would > have to be imported explicitly from Data.List.NonEmpty, as > currently is the case). > > But these are really poor names for something this specific being made > available unqualified everywhere: there are lots of things that could > be called "NonEmpty" or "nonEmpty", and ":|" is a perfectly good > combinator name for other purposes. > > So this addition would do little beside increasing the footprint of the > Prelude and causing issues clashes with code that happens to use these > names already. > > To quote Yuras Shumovich from a related thread (Add readMaybe (and > possibly readEither) to Prelude): "We should be careful with Prelude." > > Additionally, as is evidenced by the type signatures of the > module NonEmpty, the utility of keeping track of non-empty lists at > the type level in a language like Haskell is in general limited > (which is not to say that it cannot be very useful sometimes). > Even in a language with dependent types the approach (of integrating > properties with data types) is not always smooth as it may lead to > a proliferation of different related but distinct types which quickly > becomes clunky. As far as I am aware, solving this conundrum is > still an open research problem. > > (And nothing new under the sun, either: people familiar > with Pascal or Ada will have had similar experiences with a > proliferation of integral types of various ranges. In simple cases, > very useful to ensure e.g. an array index is not out of bounds, but > does not go very far.) > > Finally, why single out "non-empty" specifically as a > property worthy to keep track at the type level in the prelude? > Why not lists of finite length as well, for example? > That could help ensuring termination. > > (Just to be clear: I am not proposing this. I am just saying > that I can't see how adding variations of existing types with > specific properties to the prelude possibly can result in > a principled design for a language like Haskell as it currently > stands.) > > /Henrik > > > > > > This message and any attachment are intended solely for the addressee > and may contain confidential information. If you have received this > message in error, please send it back to me, and immediately delete it. > Please do not use, copy or disclose the information contained in this > message or in any attachment. Any views or opinions expressed by the > author of this email do not necessarily reflect the views of the > University of Nottingham. > > This message has been checked for viruses but the contents of an > attachment may still contain software viruses which could damage your > computer system, you are advised to perform your own checks. Email > communications with the University of Nottingham may be monitored as > permitted by UK legislation. > > _______________________________________________ > 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 amindfv at gmail.com Thu Dec 29 20:17:13 2016 From: amindfv at gmail.com (amindfv at gmail.com) Date: Thu, 29 Dec 2016 14:17:13 -0600 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: <586510F5.6080108@exmail.nottingham.ac.uk> References: <1483011168.4381.1.camel@gmail.com> <586510F5.6080108@exmail.nottingham.ac.uk> Message-ID: <36DCAF4A-4590-44AB-BED3-EC1B9D7338F8@gmail.com> I don't think there actually will be any need for CPP if we add this to the Prelude. I'm +1 on adding it, either as 'readMay' or 'readMaybe' Tom > El 29 dic 2016, a las 07:34, Henrik Nilsson escribió: > > Hi, > > Yuras Shumovich said: > > > >> you may be happy to not > > >> add a new > > >> import line but you force your library users to the newest version > > >> of GHC > > >> and you risk to make his programs uncompilable because it may > > >> depend on > > >> other packages that are not (yet) updated to the newest GHC. If you > > >> care for > > >> multiple versions of GHC you have to make much more cumbersome > > >> import > > >> statements or add multiple lines of preprocessor. > > >> > > > These concerns apply to any change to the Prelude. > > > Yet it is a valid argument. We should be careful with Prelude. > > I can only second this. It is *very* frustrating when code fails > to compile with an slightly out-of-date version of GHC just because > someone, perhaps a beginner, perhaps mostly by accident, use a new > "nifty" add on to the prelude just because it happens to be there. > > I recently had this experience with code written for a recent version > of GHC I needed to make work with GHC 7.8. I had to make rather a lot > of edits that ultimately turned out to be entirely trivial, in many cases because new, alternative names had been added for existing > features. When I compared the "before" and "after" versions of the > code, I didn't find the new version an iota more readable or elegant > than the old one on balance because the number of affected lines in > relative terms was small so the only real effect of the additions I had > to get rid of was to increase the cognitive burden of the reader in terms of a larger "Prelude vocabulary". > > I wouldn't have minded half as much if the new features had been > signalled by explicit imports. > > And most likely, in many cases, the new features would not have been > used at all as they were not particularly important for this particular > piece of code (in terms of increasing readability etc). Which > is not to at all to say that these features might not be very > useful for other pieces of code. In which case they could just have > just be imported explicitly. > > So indeed, as Yuras said: "We should be careful with the Prelude". > > /Henrik > > > > > > This message and any attachment are intended solely for the addressee > and may contain confidential information. If you have received this > message in error, please send it back to me, and immediately delete it. > Please do not use, copy or disclose the information contained in this > message or in any attachment. Any views or opinions expressed by the > author of this email do not necessarily reflect the views of the > University of Nottingham. > > This message has been checked for viruses but the contents of an > attachment may still contain software viruses which could damage your > computer system, you are advised to perform your own checks. Email > communications with the University of Nottingham may be monitored as > permitted by UK legislation. > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From andreas.abel at ifi.lmu.de Thu Dec 29 20:12:35 2016 From: andreas.abel at ifi.lmu.de (Andreas Abel) Date: Thu, 29 Dec 2016 21:12:35 +0100 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: <36DCAF4A-4590-44AB-BED3-EC1B9D7338F8@gmail.com> References: <1483011168.4381.1.camel@gmail.com> <586510F5.6080108@exmail.nottingham.ac.uk> <36DCAF4A-4590-44AB-BED3-EC1B9D7338F8@gmail.com> Message-ID: I am in favor of deprecating "read" and pointing to a total version in a library. Otherwise, I'd leave the Prelude unchanged. --Andreas On 29.12.2016 21:17, amindfv at gmail.com wrote: > I don't think there actually will be any need for CPP if we add this to the Prelude. I'm +1 on adding it, either as 'readMay' or 'readMaybe' > > Tom > > >> El 29 dic 2016, a las 07:34, Henrik Nilsson escribió: >> >> Hi, >> >> Yuras Shumovich said: >> >>>>> you may be happy to not >>>>> add a new >>>>> import line but you force your library users to the newest version >>>>> of GHC >>>>> and you risk to make his programs uncompilable because it may >>>>> depend on >>>>> other packages that are not (yet) updated to the newest GHC. If you >>>>> care for >>>>> multiple versions of GHC you have to make much more cumbersome >>>>> import >>>>> statements or add multiple lines of preprocessor. >>>>> >>>> These concerns apply to any change to the Prelude. >> >>> Yet it is a valid argument. We should be careful with Prelude. >> >> I can only second this. It is *very* frustrating when code fails >> to compile with an slightly out-of-date version of GHC just because >> someone, perhaps a beginner, perhaps mostly by accident, use a new >> "nifty" add on to the prelude just because it happens to be there. >> >> I recently had this experience with code written for a recent version >> of GHC I needed to make work with GHC 7.8. I had to make rather a lot >> of edits that ultimately turned out to be entirely trivial, in many cases because new, alternative names had been added for existing >> features. When I compared the "before" and "after" versions of the >> code, I didn't find the new version an iota more readable or elegant >> than the old one on balance because the number of affected lines in >> relative terms was small so the only real effect of the additions I had >> to get rid of was to increase the cognitive burden of the reader in terms of a larger "Prelude vocabulary". >> >> I wouldn't have minded half as much if the new features had been >> signalled by explicit imports. >> >> And most likely, in many cases, the new features would not have been >> used at all as they were not particularly important for this particular >> piece of code (in terms of increasing readability etc). Which >> is not to at all to say that these features might not be very >> useful for other pieces of code. In which case they could just have >> just be imported explicitly. >> >> So indeed, as Yuras said: "We should be careful with the Prelude". >> >> /Henrik >> >> >> >> >> >> This message and any attachment are intended solely for the addressee >> and may contain confidential information. If you have received this >> message in error, please send it back to me, and immediately delete it. >> Please do not use, copy or disclose the information contained in this >> message or in any attachment. Any views or opinions expressed by the >> author of this email do not necessarily reflect the views of the >> University of Nottingham. >> >> This message has been checked for viruses but the contents of an >> attachment may still contain software viruses which could damage your >> computer system, you are advised to perform your own checks. Email >> communications with the University of Nottingham may be monitored as >> permitted by UK legislation. >> >> _______________________________________________ >> 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 spam at scientician.net Thu Dec 29 21:47:18 2016 From: spam at scientician.net (Bardur Arantsson) Date: Thu, 29 Dec 2016 22:47:18 +0100 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: <1483011168.4381.1.camel@gmail.com> <586510F5.6080108@exmail.nottingham.ac.uk> <36DCAF4A-4590-44AB-BED3-EC1B9D7338F8@gmail.com> Message-ID: On 2016-12-29 21:12, Andreas Abel wrote: > > I am in favor of deprecating "read" and pointing to a total version in a > library. Otherwise, I'd leave the Prelude unchanged. > But that throws a wrench in the works of people who want to be "-Wall" clean... unless you mean "deprecated" in the sense of being *documented* as deprecated rather than actually marked as such (causing deprecation warnings during compilation). I'm not sure actually... do we have fine-grained deprecation warnings yet?[1] I.e. can we turn on/off individual deprecation warnings with compiler switches? If so, then just deprecating read and pointing to a readMaybe in some module might be the optimal solution here. Regards, [1] If we don't then I honestly think that this may be the single most important feature to be able to move forward wrt. the Prelude. (Well, a "go fix" type tool might be even better, but that's not likely to happen any time soon.) From david.feuer at gmail.com Thu Dec 29 21:54:59 2016 From: david.feuer at gmail.com (David Feuer) Date: Thu, 29 Dec 2016 16:54:59 -0500 Subject: MonadZip for Data.Tree Message-ID: MonadZip doesn't really explain how strict mzipWith and (especially) munzip should be. For example, we could have munzip (Node (a, b) ts) = (Node a as, Node b bs) where (as, bs) = Data.List.unzip (map munzip ts) or we could make some or all of the pattern matches lazy, or we could use something lazier than Data.List.unzip, or we could make everything completely spine-strict (surely unwise). Does anyone have a particular preference, or a particular reason to prefer one choice over others? If not, I think we should go with the simple version above. David Feuer From ekmett at gmail.com Fri Dec 30 04:22:15 2016 From: ekmett at gmail.com (Edward Kmett) Date: Thu, 29 Dec 2016 23:22:15 -0500 Subject: MonadZip for Data.Tree In-Reply-To: References: Message-ID: No real preference, but this does remind me that MonadZip probably should have the following extra law: uncurry mzip . munzip = id This law is passed by all current instances and fits the intent of much harder to state opposite facing information preservation law. Since we continue to insist on this class containing the annoying munzip operation, this law is actually far easier to demonstrate than the existing law. We can also restate the other information preservation law now that Functor is a superclass of Monad to the rather more succinct () <$ ma = () <$ mb ==> munzip (mzip ma mb) = (ma, mb) -Edward On Thu, Dec 29, 2016 at 4:54 PM, David Feuer wrote: > MonadZip doesn't really explain how strict mzipWith and (especially) > munzip should be. For example, we could have > > munzip (Node (a, b) ts) = (Node a as, Node b bs) > where (as, bs) = Data.List.unzip (map munzip ts) > > or we could make some or all of the pattern matches lazy, or we could > use something lazier than Data.List.unzip, or we could make everything > completely spine-strict (surely unwise). > > Does anyone have a particular preference, or a particular reason to > prefer one choice over others? If not, I think we should go with the > simple version above. > > David Feuer > _______________________________________________ > 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 dave at zednenem.com Fri Dec 30 04:50:02 2016 From: dave at zednenem.com (David Menendez) Date: Thu, 29 Dec 2016 23:50:02 -0500 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: <1483011168.4381.1.camel@gmail.com> <586510F5.6080108@exmail.nottingham.ac.uk> <36DCAF4A-4590-44AB-BED3-EC1B9D7338F8@gmail.com> Message-ID: On Thu, Dec 29, 2016 at 4:47 PM, Bardur Arantsson wrote: > On 2016-12-29 21:12, Andreas Abel wrote: > > > > I am in favor of deprecating "read" and pointing to a total version in a > > library. Otherwise, I'd leave the Prelude unchanged. > This is also my preference. If we *have* to change the Prelude, I’d prefer moving Read out entirely. But that throws a wrench in the works of people who want to be "-Wall" > clean... unless you mean "deprecated" in the sense of being *documented* > as deprecated rather than actually marked as such (causing deprecation > warnings during compilation). > I don't think making life easy for -Wall clean people should be a goal. The whole point of warnings is that they indicate things that might not be a problem. Otherwise, they’d be errors. This is especially true for warnings that only show up if you use -Wall instead of -W. -- Dave Menendez -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Fri Dec 30 04:51:16 2016 From: ekmett at gmail.com (Edward Kmett) Date: Thu, 29 Dec 2016 23:51:16 -0500 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: <1483011168.4381.1.camel@gmail.com> <586510F5.6080108@exmail.nottingham.ac.uk> <36DCAF4A-4590-44AB-BED3-EC1B9D7338F8@gmail.com> Message-ID: On Thu, Dec 29, 2016 at 4:47 PM, Bardur Arantsson wrote: > On 2016-12-29 21:12, Andreas Abel wrote: > > > > I am in favor of deprecating "read" and pointing to a total version in a > > library. Otherwise, I'd leave the Prelude unchanged. > > > > But that throws a wrench in the works of people who want to be "-Wall" > clean... unless you mean "deprecated" in the sense of being *documented* > as deprecated rather than actually marked as such (causing deprecation > warnings during compilation). > Indeed. I'm not sure actually... do we have fine-grained deprecation warnings > yet?[1] We do not. There has been some work on breaking up the monolithic set of warnings and being a bit more regular about how we handle them, but not individual groups of deprecations. > I.e. can we turn on/off individual deprecation warnings with > compiler switches? If so, then just deprecating read and pointing to a > readMaybe in some module might be the optimal solution here. > I'm strongly -1 on adding a full-fledged DEPRECATED flag to read. The amount of noise that would generate would dwarf anything else under discussion by multiple orders of magnitude. It is in the Haskell Report and it has been used a lot for a couple of decades now. On the other hand, whether or not anything changes in Prelude, I'm a strong +1 on adding documentation to it that mentions these safer alternatives, and where to get them if necessary. [1] If we don't then I honestly think that this may be the single most > important feature to be able to move forward wrt. the Prelude. (Well, a > "go fix" type tool might be even better, but that's not likely to happen > any time soon.) The amount of CPP running around in Haskell with any sort of long support window makes 'go fix' tools quite shockingly difficult for us to get right. I'm a weak +1 on adding re-export of the existing readMaybe and readEither to the Prelude, possibly after a warning period. They are sufficiently obscure names that I'm personally not expecting many name conflicts at all and the changes in base are minimal as the classes and 'read' are already re-exports from the same place, so there isn't much of an engineering challenge. I do think if we're going to include readMaybe there isn't much point in not including the slightly more powerful readEither. -Edward > _______________________________________________ > 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 Fri Dec 30 04:56:30 2016 From: ekmett at gmail.com (Edward Kmett) Date: Thu, 29 Dec 2016 23:56:30 -0500 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: <1483011168.4381.1.camel@gmail.com> <586510F5.6080108@exmail.nottingham.ac.uk> <36DCAF4A-4590-44AB-BED3-EC1B9D7338F8@gmail.com> Message-ID: Read is one of very few classes with stated a deriving technique in the Haskell Report. Moving it out of the Prelude would break a ridiculous amount of code and involve adding import Text.Read as boilerplate to the top of every single module of Haskell source code out there that deigned to include deriving (Read,....) among the list of instances derived for their data types. The cure feels a lot worse than any disease. Heck, read isn't even a member of the class, so this would just spite users and not even address the symptom raised by this thread. -Edward On Thu, Dec 29, 2016 at 11:50 PM, David Menendez wrote: > On Thu, Dec 29, 2016 at 4:47 PM, Bardur Arantsson > wrote: > >> On 2016-12-29 21:12, Andreas Abel wrote: >> > >> > I am in favor of deprecating "read" and pointing to a total version in a >> > library. Otherwise, I'd leave the Prelude unchanged. >> > > This is also my preference. If we *have* to change the Prelude, I’d prefer > moving Read out entirely. > > But that throws a wrench in the works of people who want to be "-Wall" >> clean... unless you mean "deprecated" in the sense of being *documented* >> as deprecated rather than actually marked as such (causing deprecation >> warnings during compilation). >> > > I don't think making life easy for -Wall clean people should be a goal. > The whole point of warnings is that they indicate things that might not be > a problem. Otherwise, they’d be errors. This is especially true for > warnings that only show up if you use -Wall instead of -W. > > -- > Dave Menendez > > > _______________________________________________ > 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 Fri Dec 30 05:08:46 2016 From: ekmett at gmail.com (Edward Kmett) Date: Fri, 30 Dec 2016 00:08:46 -0500 Subject: Proposal: Add NonEmpty constructors to the Prelude In-Reply-To: <72213f32-b053-d15e-c3fb-65d8d7e61879@ifi.lmu.de> References: <58651D2E.5010504@exmail.nottingham.ac.uk> <72213f32-b053-d15e-c3fb-65d8d7e61879@ifi.lmu.de> Message-ID: Regardless of if NonEmpty should have been called NonEmptyList years ago when it was designed years ago (It was modeled on two existing libraries that took the NonEmpty name and at least one of those authors was vocally against the longer name, so we might never have been able to consolidate the implementation at all) and before it was brought into base, randomly recoloring the bikeshed at this point basically would just guarantee that all existing users are left with no migration path. But your point on how annoyingly common the names are does make me shift to weakly -1 as to including them as part of an 8.6 migration story. Leaving them where they are in Data.List.NonEmpty and not exporting sconcat in the Prelude as an implementation detail for Semigroup like (<$), readPrec, readListPrec, log1p, etc. avoids clutter and breakage. Heck, that way if you really want List somewhere in the name you can personally import Data.List.NonEmpty qualified or ignore it and sconcat entirely. -Edward On Thu, Dec 29, 2016 at 12:57 PM, Andreas Abel wrote: > Since "nonEmpty" is a predicate that could apply any kind of collection, > not just lists, I am strongly -1 on such a proposal. > > Similarly, "NonEmpty" misses a "List", it should be called "NonEmptyList". > > --Andreas > > > On 29.12.2016 15:26, Henrik Nilsson wrote: > >> Hi, >> >> On 12/29/2016 12:48 PM, Andreas Abel wrote: >> >>> What are the types and definitions of >>> >>> > nonEmpty, (:|), and the type constructor NonEmpty. >>> >>> ? >>> >>> Must be something generic, overloaded, given the name... >>> >> >> Indeed, one would assume so, given the names. >> >> But: >> >> > What are the types and definitions of >>> > >>> >> nonEmpty, (:|), and the type constructor NonEmpty. >>> > >>> > ? >>> >>> See http://hackage.haskell.org/package/base-4.9.0.0/docs/ >>> Data-List-NonEmpty.html >>> >> >> there is nothing generic at all about these: >> >> I am assuming that the idea is that these three definitions >> will be made available for unqualified use (while all other >> library functions for programming with non-empty lists would >> have to be imported explicitly from Data.List.NonEmpty, as >> currently is the case). >> >> But these are really poor names for something this specific being made >> available unqualified everywhere: there are lots of things that could >> be called "NonEmpty" or "nonEmpty", and ":|" is a perfectly good >> combinator name for other purposes. >> >> So this addition would do little beside increasing the footprint of the >> Prelude and causing issues clashes with code that happens to use these >> names already. >> >> To quote Yuras Shumovich from a related thread (Add readMaybe (and >> possibly readEither) to Prelude): "We should be careful with Prelude." >> >> Additionally, as is evidenced by the type signatures of the >> module NonEmpty, the utility of keeping track of non-empty lists at >> the type level in a language like Haskell is in general limited >> (which is not to say that it cannot be very useful sometimes). >> Even in a language with dependent types the approach (of integrating >> properties with data types) is not always smooth as it may lead to >> a proliferation of different related but distinct types which quickly >> becomes clunky. As far as I am aware, solving this conundrum is >> still an open research problem. >> >> (And nothing new under the sun, either: people familiar >> with Pascal or Ada will have had similar experiences with a >> proliferation of integral types of various ranges. In simple cases, >> very useful to ensure e.g. an array index is not out of bounds, but >> does not go very far.) >> >> Finally, why single out "non-empty" specifically as a >> property worthy to keep track at the type level in the prelude? >> Why not lists of finite length as well, for example? >> That could help ensuring termination. >> >> (Just to be clear: I am not proposing this. I am just saying >> that I can't see how adding variations of existing types with >> specific properties to the prelude possibly can result in >> a principled design for a language like Haskell as it currently >> stands.) >> >> /Henrik >> >> >> >> >> >> This message and any attachment are intended solely for the addressee >> and may contain confidential information. If you have received this >> message in error, please send it back to me, and immediately delete it. >> Please do not use, copy or disclose the information contained in this >> message or in any attachment. Any views or opinions expressed by the >> author of this email do not necessarily reflect the views of the >> University of Nottingham. >> >> This message has been checked for viruses but the contents of an >> attachment may still contain software viruses which could damage your >> computer system, you are advised to perform your own checks. Email >> communications with the University of Nottingham may be monitored as >> permitted by UK legislation. >> >> _______________________________________________ >> 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: From david.feuer at gmail.com Fri Dec 30 05:22:56 2016 From: david.feuer at gmail.com (David Feuer) Date: Fri, 30 Dec 2016 00:22:56 -0500 Subject: MonadZip for Data.Tree In-Reply-To: References: Message-ID: The class is altogether annoying because it has a Monad superclass instead of a Functor one, excluding perfectly good zippable functors like Map k, IntMap k, and even, ironically, ZipList. What do you mean by the opposite facing information preservation law? And what do you have against munzip, aside from the fact that it looks like it wants to be in the too-lofty-for-its-like circle of Functor? On Dec 29, 2016 11:22 PM, "Edward Kmett" wrote: No real preference, but this does remind me that MonadZip probably should have the following extra law: uncurry mzip . munzip = id This law is passed by all current instances and fits the intent of much harder to state opposite facing information preservation law. Since we continue to insist on this class containing the annoying munzip operation, this law is actually far easier to demonstrate than the existing law. We can also restate the other information preservation law now that Functor is a superclass of Monad to the rather more succinct () <$ ma = () <$ mb ==> munzip (mzip ma mb) = (ma, mb) -Edward On Thu, Dec 29, 2016 at 4:54 PM, David Feuer wrote: > MonadZip doesn't really explain how strict mzipWith and (especially) > munzip should be. For example, we could have > > munzip (Node (a, b) ts) = (Node a as, Node b bs) > where (as, bs) = Data.List.unzip (map munzip ts) > > or we could make some or all of the pattern matches lazy, or we could > use something lazier than Data.List.unzip, or we could make everything > completely spine-strict (surely unwise). > > Does anyone have a particular preference, or a particular reason to > prefer one choice over others? If not, I think we should go with the > simple version above. > > David Feuer > _______________________________________________ > 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 Fri Dec 30 06:54:29 2016 From: ekmett at gmail.com (Edward Kmett) Date: Fri, 30 Dec 2016 01:54:29 -0500 Subject: MonadZip for Data.Tree In-Reply-To: References: Message-ID: By opposite facing information preservation law, I mean there is a law right now called Information Preservation in the haddocks for the class. It only supplies half the story about how uncurry mzip and munzip are "almost inverses", but the law given in the haddocks is actually pretty weird. The nice law I mentioned 'uncurry mzip . munzip = id' says uncurry mzip 'retracts' munzip in category theoretic terms. The existing law is kind of abomination that tries to imply that if you have the same shape on both sides they should zip together in a way that unzips without destroying or creating any weird new shapes, but without the retraction law I don't think you can prove that you've ruled out all the wonky instances. As for what I have against munzip as a member, it is a boring, unnecessary member with no interesting definitions. It has to be equivalent to fmap fst &&& fmap snd to pass the laws and free theorems involved. The *only* interesting instance I've ever derived is one I came up with for a memoizing variant of Lindsey Kuper's idempotent Par monad that admits pure LVar reads, and lacks region parameters. There you could exploit idempotence to reuse the results and share *some* computation effort in case you use <*> to glue the parts you munzipped back together, but I don't exactly see people lining up to use it. ;) As a pure computation you need to make a new promise/IVar, fill it with the computation that will produce the (a,b) pair. Then return two computations that each demand the result of the promise when run and fmap fst or fmap snd the result appropriately. But building that one interesting monad requires embracing at least unsafeInterleaveST levels of evil, and the instance requires upgrading that to unsafePerformST levels of messiness. -Edward On Fri, Dec 30, 2016 at 12:22 AM, David Feuer wrote: > The class is altogether annoying because it has a Monad superclass instead > of a Functor one, excluding perfectly good zippable functors like Map k, > IntMap k, and even, ironically, ZipList. What do you mean by the opposite > facing information preservation law? And what do you have against munzip, > aside from the fact that it looks like it wants to be in the > too-lofty-for-its-like circle of Functor? > > On Dec 29, 2016 11:22 PM, "Edward Kmett" wrote: > > No real preference, but this does remind me that MonadZip probably should > have the following extra law: > > uncurry mzip . munzip = id > > This law is passed by all current instances and fits the intent of much > harder to state opposite facing information preservation law. > > Since we continue to insist on this class containing the annoying munzip > operation, this law is actually far easier to demonstrate than the existing > law. > > We can also restate the other information preservation law now that > Functor is a superclass of Monad to the rather more succinct > > () <$ ma = () <$ mb ==> munzip (mzip ma mb) = (ma, mb) > > -Edward > > On Thu, Dec 29, 2016 at 4:54 PM, David Feuer > wrote: > >> MonadZip doesn't really explain how strict mzipWith and (especially) >> munzip should be. For example, we could have >> >> munzip (Node (a, b) ts) = (Node a as, Node b bs) >> where (as, bs) = Data.List.unzip (map munzip ts) >> >> or we could make some or all of the pattern matches lazy, or we could >> use something lazier than Data.List.unzip, or we could make everything >> completely spine-strict (surely unwise). >> >> Does anyone have a particular preference, or a particular reason to >> prefer one choice over others? If not, I think we should go with the >> simple version above. >> >> David Feuer >> _______________________________________________ >> 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 svenpanne at gmail.com Fri Dec 30 07:13:15 2016 From: svenpanne at gmail.com (Sven Panne) Date: Fri, 30 Dec 2016 08:13:15 +0100 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: <1483011168.4381.1.camel@gmail.com> <586510F5.6080108@exmail.nottingham.ac.uk> <36DCAF4A-4590-44AB-BED3-EC1B9D7338F8@gmail.com> Message-ID: 2016-12-30 5:50 GMT+01:00 David Menendez : > [...] I don't think making life easy for -Wall clean people should be a > goal. The whole point of warnings is that they indicate things that might > not be a problem. Otherwise, they’d be errors. This is especially true for > warnings that only show up if you use -Wall instead of -W. > This is largely a matter of personal preference, and this is probably even changing over time: 10-20 years ago, I didn't care much about -Wall (in various languages/compilers) too much, but this has changed with experience in tons of projects: Basically each and every warning turned into a bug sooner or later, with very, very few exceptions. So I'm basically a hardcore -Wall-clean-fanatic nowaydays. :-) Not using -Wall doesn't make the problems go away, you only discover them much, much later, probably when your SW is shipped to your client. So whatever is done, it should be easily be possible to be -Wall-clean, which basically means more control over warnings. Especially important are one-shot things like the usual C/C++'s NOLINT ("I know what I'm doing here, really!") comments, which make it possible to be extremely fine-grained about warnings. Warnings from compilers are just like people crying for help: If you see them too often, you get used to them and ignore them, which in the long run is bad for all parties involved... -------------- next part -------------- An HTML attachment was scrubbed... URL: From dave at zednenem.com Fri Dec 30 07:48:41 2016 From: dave at zednenem.com (David Menendez) Date: Fri, 30 Dec 2016 02:48:41 -0500 Subject: Fwd: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: <1483011168.4381.1.camel@gmail.com> <586510F5.6080108@exmail.nottingham.ac.uk> <36DCAF4A-4590-44AB-BED3-EC1B9D7338F8@gmail.com> Message-ID: On Thu, Dec 29, 2016 at 11:56 PM, Edward Kmett wrote: > Read is one of very few classes with stated a deriving technique in the > Haskell Report. > ... > The cure feels a lot worse than any disease. Heck, read isn't even a > member of the class, so this would just spite users and not even address > the symptom raised by this thread. > I may have been unclear. My (weak) preference is to leave things as they are, from an API standpoint, and mention that read is partial in its documentation. I am neutral on deprecation. If at some point the Haskell community decides to refactor the Prelude, it should figure out what Read is for and whether that functionality is essential enough to be in the Prelude. > > -Edward > > > On Thu, Dec 29, 2016 at 11:50 PM, David Menendez > wrote: > >> On Thu, Dec 29, 2016 at 4:47 PM, Bardur Arantsson >> wrote: >> >>> On 2016-12-29 21:12, Andreas Abel wrote: >>> > >>> > I am in favor of deprecating "read" and pointing to a total version in >>> a >>> > library. Otherwise, I'd leave the Prelude unchanged. >>> >> >> This is also my preference. If we *have* to change the Prelude, I’d >> prefer moving Read out entirely. >> >> But that throws a wrench in the works of people who want to be "-Wall" >>> clean... unless you mean "deprecated" in the sense of being *documented* >>> as deprecated rather than actually marked as such (causing deprecation >>> warnings during compilation). >>> >> >> I don't think making life easy for -Wall clean people should be a goal. >> The whole point of warnings is that they indicate things that might not be >> a problem. Otherwise, they’d be errors. This is especially true for >> warnings that only show up if you use -Wall instead of -W. >> >> -- >> Dave Menendez >> >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> > -- Dave Menendez -- Dave Menendez -------------- next part -------------- An HTML attachment was scrubbed... URL: From dave at zednenem.com Fri Dec 30 08:43:04 2016 From: dave at zednenem.com (David Menendez) Date: Fri, 30 Dec 2016 03:43:04 -0500 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: <1483011168.4381.1.camel@gmail.com> <586510F5.6080108@exmail.nottingham.ac.uk> <36DCAF4A-4590-44AB-BED3-EC1B9D7338F8@gmail.com> Message-ID: On Fri, Dec 30, 2016 at 2:13 AM, Sven Panne wrote: > 2016-12-30 5:50 GMT+01:00 David Menendez : > >> [...] I don't think making life easy for -Wall clean people should be a >> goal. The whole point of warnings is that they indicate things that might >> not be a problem. Otherwise, they’d be errors. This is especially true for >> warnings that only show up if you use -Wall instead of -W. >> > > This is largely a matter of personal preference, and this is probably even > changing over time: 10-20 years ago, I didn't care much about -Wall (in > various languages/compilers) too much, but this has changed with experience > in tons of projects: Basically each and every warning turned into a bug > sooner or later, with very, very few exceptions. So I'm basically a > hardcore -Wall-clean-fanatic nowaydays. :-) Not using -Wall doesn't make > the problems go away, you only discover them much, much later, probably > when your SW is shipped to your client. > > So whatever is done, it should be easily be possible to be -Wall-clean, > which basically means more control over warnings. Especially important are > one-shot things like the usual C/C++'s NOLINT ("I know what I'm doing here, > really!") comments, which make it possible to be extremely fine-grained > about warnings. > > Warnings from compilers are just like people crying for help: If you see > them too often, you get used to them and ignore them, which in the long run > is bad for all parties involved… > Why -Wall and not -W? If something is almost always an issue, shouldn’t it be in -W? The point I was trying to make is that we don’t want to prevent compiler developers from adding warnings (or library developers from deprecating things) merely to make life easier for people who want to be -Wall clean. Having a syntax to disable a warning is not a bad idea, even though it brings to mind the “please” keyword from Intercal. -- Dave Menendez -------------- next part -------------- An HTML attachment was scrubbed... URL: From andreas.abel at ifi.lmu.de Fri Dec 30 08:55:38 2016 From: andreas.abel at ifi.lmu.de (Andreas Abel) Date: Fri, 30 Dec 2016 09:55:38 +0100 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: <1483011168.4381.1.camel@gmail.com> <586510F5.6080108@exmail.nottingham.ac.uk> <36DCAF4A-4590-44AB-BED3-EC1B9D7338F8@gmail.com> Message-ID: When updating the documentation for Read, one can at the same time stress that this class is for parsing values in *Haskell* syntax. Same for Show, it should be stressed that it is for printing values into their *Haskell* linearization. I'd guess "Show" is the most abused type class. (Our own code base, Agda, is a prime example for this.) Currently we have: https://hackage.haskell.org/package/base-4.9.0.0/docs/Text-Show.html Converting values to readable strings: the Show class and associated functions. https://hackage.haskell.org/package/base-4.9.0.0/docs/Text-Read.html Converting strings to values. This description is way too generic/generous... Cheers (and a happy 2017), Andreas On 30.12.2016 09:43, David Menendez wrote: > On Fri, Dec 30, 2016 at 2:13 AM, Sven Panne > wrote: > > 2016-12-30 5:50 GMT+01:00 David Menendez >: > > [...] I don't think making life easy for -Wall clean people > should be a goal. The whole point of warnings is that they > indicate things that might not be a problem. Otherwise, they’d > be errors. This is especially true for warnings that only show > up if you use -Wall instead of -W. > > > This is largely a matter of personal preference, and this is > probably even changing over time: 10-20 years ago, I didn't care > much about -Wall (in various languages/compilers) too much, but this > has changed with experience in tons of projects: Basically each and > every warning turned into a bug sooner or later, with very, very few > exceptions. So I'm basically a hardcore -Wall-clean-fanatic > nowaydays. :-) Not using -Wall doesn't make the problems go away, > you only discover them much, much later, probably when your SW is > shipped to your client. > > So whatever is done, it should be easily be possible to be > -Wall-clean, which basically means more control over warnings. > Especially important are one-shot things like the usual C/C++'s > NOLINT ("I know what I'm doing here, really!") comments, which make > it possible to be extremely fine-grained about warnings. > > Warnings from compilers are just like people crying for help: If you > see them too often, you get used to them and ignore them, which in > the long run is bad for all parties involved… > > > Why -Wall and not -W? If something is almost always an issue, shouldn’t > it be in -W? > > The point I was trying to make is that we don’t want to prevent compiler > developers from adding warnings (or library developers from deprecating > things) merely to make life easier for people who want to be -Wall clean. > > Having a syntax to disable a warning is not a bad idea, even though it > brings to mind the “please” keyword from Intercal. > > -- > Dave Menendez > > > > > _______________________________________________ > 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 svenpanne at gmail.com Fri Dec 30 09:01:03 2016 From: svenpanne at gmail.com (Sven Panne) Date: Fri, 30 Dec 2016 10:01:03 +0100 Subject: Proposal: Add readMaybe (and possibly readEither) to Prelude, make Haddocks for read more cautionary In-Reply-To: References: <1483011168.4381.1.camel@gmail.com> <586510F5.6080108@exmail.nottingham.ac.uk> <36DCAF4A-4590-44AB-BED3-EC1B9D7338F8@gmail.com> Message-ID: 2016-12-30 9:43 GMT+01:00 David Menendez : > Why -Wall and not -W? If something is almost always an issue, shouldn’t it > be in -W? > My point basically is: The distinction between -Wall and -W is an illusion. > The point I was trying to make is that we don’t want to prevent compiler > developers from adding warnings (or library developers from deprecating > things) merely to make life easier for people who want to be -Wall clean. > Who is "we"? :-) Adding a new sensible warning to the compiler is completely OK, if it breaks some projects, these should be fixed. Deprecating things is OK, too, at least if there is a sane migration path. But of course in both cases, the potential benefits should outweigh the induced costs. > Having a syntax to disable a warning is not a bad idea, even though it > brings to mind the “please” keyword from Intercal. > :-D The point about such syntax is: Tools almost always give some false positives, so there must be some kind of escape hatch for the programmer to shut them up locally. People who have tried e.g. include-what-you-use, clang-tidy or cppcheck on larger projects probably know what I mean: You can't wait months or even years until a tool is fixed, but you don't want to use a big hammer to silence them, either. -------------- next part -------------- An HTML attachment was scrubbed... URL: