[Proposal] Integration of helpers to operate on Newtypes in base

Hello, CLC and haskell-libraries, I am opening a proposal process to consider the integration of several helper functions in `base`, operating on Newtypes, and all based on `coerce`. My motivations are that we ought to provide a minimum set of tools in order to work effectively with one of our most beloved and ubiquitous language features. Now, these functions that I am about to present to you all do not come out of nowhere. They have been integrated to Kowainik's alternative prelude "Relude", and seem to have found their use amongst their users, me included. Their documentation can be found here => https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype... but I am reproducing them below for convenience: --- un :: forall a n. Coercible a n => n -> a Unwraps value from newtype. ```
newtype Size = Size Int deriving Show un @Int (Size 5) 5 un (Size 5) == length ['a', 'x', 'b'] False
---
wrap :: forall n a. Coercible a n => a -> n
Wraps value to newtype. Behaves exactly as 'un' but has more meaningful
name in case you need to convert some value to newtype.
newtype Flag = Flag Bool deriving (Show, Eq) wrap False == Flag True False
---
under :: forall n a. Coercible a n => (n -> n) -> a -> a
Applies function to the content of newtype. This function is not
supposed to be used on newtypes that are created with the help of smart
constructors.
newtype Foo = Foo Bool deriving Show under not (Foo True) Foo False newtype Bar = Bar String deriving Show under (filter (== 'a')) (Bar "abacaba") Bar "aaaa"
As well as the coerced composition operator:
(#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c)
(#.) _f = coerce
{-# INLINE (#.) #-}
Which currently lives in
https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Utils.html#%23
but is not exported.
Regarding the location of these functions, I either see them living in
their own "Data.Newtype", or they could join Data.Coerce.
I would personally create a new module as to avoid "polluting"
Data.Coerce with non-class functions, but this is my personal preference.
Thank you for reading.
--
Hécate ✨
🐦: @TechnoEmpress
IRC: Uniaika
WWW: https://glitchbra.in
RUN: BSD

If you're playing around with these ideas, you may appreciate the
coercible-utils package[*]. I basically rewrote the package last year to
get really good type inference at the cost of some (hard to use)
flexibility.
[*] https://hackage.haskell.org/package/coercible-utils
On Tue, Nov 10, 2020, 8:23 AM Hécate
Hello, CLC and haskell-libraries,
I am opening a proposal process to consider the integration of several helper functions in `base`, operating on Newtypes, and all based on `coerce`.
My motivations are that we ought to provide a minimum set of tools in order to work effectively with one of our most beloved and ubiquitous language features.
Now, these functions that I am about to present to you all do not come out of nowhere. They have been integrated to Kowainik's alternative prelude "Relude", and seem to have found their use amongst their users, me included. Their documentation can be found here => https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype... but I am reproducing them below for convenience:
--- un :: forall a n. Coercible a n => n -> a
Unwraps value from newtype.
```
newtype Size = Size Int deriving Show un @Int (Size 5) 5 un (Size 5) == length ['a', 'x', 'b'] False
--- wrap :: forall n a. Coercible a n => a -> n Wraps value to newtype. Behaves exactly as 'un' but has more meaningful name in case you need to convert some value to newtype.
newtype Flag = Flag Bool deriving (Show, Eq) wrap False == Flag True False
--- under :: forall n a. Coercible a n => (n -> n) -> a -> a Applies function to the content of newtype. This function is not supposed to be used on newtypes that are created with the help of smart constructors.
newtype Foo = Foo Bool deriving Show under not (Foo True) Foo False newtype Bar = Bar String deriving Show under (filter (== 'a')) (Bar "abacaba") Bar "aaaa"
As well as the coerced composition operator: (#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c) (#.) _f = coerce {-# INLINE (#.) #-} Which currently lives in https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Utils.html#%23 but is not exported. Regarding the location of these functions, I either see them living in their own "Data.Newtype", or they could join Data.Coerce. I would personally create a new module as to avoid "polluting" Data.Coerce with non-class functions, but this is my personal preference. Thank you for reading. -- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW: https://glitchbra.in RUN: BSD _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Hi David, thank you very much for pointing its existence! There are indeed very interesting helpers that are available there that could definitely populate an independent Data.Newtype module in base! Cheers! Le 10/11/2020 à 14:36, David Feuer a écrit :
If you're playing around with these ideas, you may appreciate the coercible-utils package[*]. I basically rewrote the package last year to get really good type inference at the cost of some (hard to use) flexibility.
[*] https://hackage.haskell.org/package/coercible-utils https://hackage.haskell.org/package/coercible-utils
On Tue, Nov 10, 2020, 8:23 AM Hécate
mailto:hecate@glitchbra.in> wrote: Hello, CLC and haskell-libraries,
I am opening a proposal process to consider the integration of several helper functions in `base`, operating on Newtypes, and all based on `coerce`.
My motivations are that we ought to provide a minimum set of tools in order to work effectively with one of our most beloved and ubiquitous language features.
Now, these functions that I am about to present to you all do not come out of nowhere. They have been integrated to Kowainik's alternative prelude "Relude", and seem to have found their use amongst their users, me included. Their documentation can be found here => https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype... https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype...
but I am reproducing them below for convenience:
--- un :: forall a n. Coercible a n => n -> a
Unwraps value from newtype.
``` >>> newtype Size = Size Int deriving Show >>> un @Int (Size 5) 5 >>> un (Size 5) == length ['a', 'x', 'b'] False ```
--- wrap :: forall n a. Coercible a n => a -> n
Wraps value to newtype. Behaves exactly as 'un' but has more meaningful name in case you need to convert some value to newtype.
``` >>> newtype Flag = Flag Bool deriving (Show, Eq) >>> wrap False == Flag True False ```
--- under :: forall n a. Coercible a n => (n -> n) -> a -> a
Applies function to the content of newtype. This function is not supposed to be used on newtypes that are created with the help of smart constructors.
``` >>> newtype Foo = Foo Bool deriving Show >>> under not (Foo True) Foo False >>> newtype Bar = Bar String deriving Show >>> under (filter (== 'a')) (Bar "abacaba") Bar "aaaa" ```
As well as the coerced composition operator:
(#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c) (#.) _f = coerce {-# INLINE (#.) #-}
Which currently lives in https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Util... https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Util... but is not exported.
Regarding the location of these functions, I either see them living in their own "Data.Newtype", or they could join Data.Coerce. I would personally create a new module as to avoid "polluting" Data.Coerce with non-class functions, but this is my personal preference.
Thank you for reading.
-- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW:https://glitchbra.in https://glitchbra.in RUN: BSD
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
-- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW: https://glitchbra.in RUN: BSD

For the most part, I oppose adding these to base. I'm most sympathetic to
adding (.#) and (#.), originally from the profunctors package, as they seem
to pop up quite a lot. For the rest, inference can be a real problem.
coercible-utils goes to quite a lot of trouble to make these functions
reasonably usable, but I don't think we want that sort of machinery in
`base`.
On Tue, Nov 10, 2020, 8:23 AM Hécate
Hello, CLC and haskell-libraries,
I am opening a proposal process to consider the integration of several helper functions in `base`, operating on Newtypes, and all based on `coerce`.
My motivations are that we ought to provide a minimum set of tools in order to work effectively with one of our most beloved and ubiquitous language features.
Now, these functions that I am about to present to you all do not come out of nowhere. They have been integrated to Kowainik's alternative prelude "Relude", and seem to have found their use amongst their users, me included. Their documentation can be found here => https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype... but I am reproducing them below for convenience:
--- un :: forall a n. Coercible a n => n -> a
Unwraps value from newtype.
```
newtype Size = Size Int deriving Show un @Int (Size 5) 5 un (Size 5) == length ['a', 'x', 'b'] False
--- wrap :: forall n a. Coercible a n => a -> n Wraps value to newtype. Behaves exactly as 'un' but has more meaningful name in case you need to convert some value to newtype.
newtype Flag = Flag Bool deriving (Show, Eq) wrap False == Flag True False
--- under :: forall n a. Coercible a n => (n -> n) -> a -> a Applies function to the content of newtype. This function is not supposed to be used on newtypes that are created with the help of smart constructors.
newtype Foo = Foo Bool deriving Show under not (Foo True) Foo False newtype Bar = Bar String deriving Show under (filter (== 'a')) (Bar "abacaba") Bar "aaaa"
As well as the coerced composition operator: (#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c) (#.) _f = coerce {-# INLINE (#.) #-} Which currently lives in https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Utils.html#%23 but is not exported. Regarding the location of these functions, I either see them living in their own "Data.Newtype", or they could join Data.Coerce. I would personally create a new module as to avoid "polluting" Data.Coerce with non-class functions, but this is my personal preference. Thank you for reading. -- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW: https://glitchbra.in RUN: BSD _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Do you think that they will produce unwanted inference even with -XTypeApplications? Le 11/11/2020 à 08:42, David Feuer a écrit :
For the most part, I oppose adding these to base. I'm most sympathetic to adding (.#) and (#.), originally from the profunctors package, as they seem to pop up quite a lot. For the rest, inference can be a real problem. coercible-utils goes to quite a lot of trouble to make these functions reasonably usable, but I don't think we want that sort of machinery in `base`.
On Tue, Nov 10, 2020, 8:23 AM Hécate
mailto:hecate@glitchbra.in> wrote: Hello, CLC and haskell-libraries,
I am opening a proposal process to consider the integration of several helper functions in `base`, operating on Newtypes, and all based on `coerce`.
My motivations are that we ought to provide a minimum set of tools in order to work effectively with one of our most beloved and ubiquitous language features.
Now, these functions that I am about to present to you all do not come out of nowhere. They have been integrated to Kowainik's alternative prelude "Relude", and seem to have found their use amongst their users, me included. Their documentation can be found here => https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype... https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype...
but I am reproducing them below for convenience:
--- un :: forall a n. Coercible a n => n -> a
Unwraps value from newtype.
``` >>> newtype Size = Size Int deriving Show >>> un @Int (Size 5) 5 >>> un (Size 5) == length ['a', 'x', 'b'] False ```
--- wrap :: forall n a. Coercible a n => a -> n
Wraps value to newtype. Behaves exactly as 'un' but has more meaningful name in case you need to convert some value to newtype.
``` >>> newtype Flag = Flag Bool deriving (Show, Eq) >>> wrap False == Flag True False ```
--- under :: forall n a. Coercible a n => (n -> n) -> a -> a
Applies function to the content of newtype. This function is not supposed to be used on newtypes that are created with the help of smart constructors.
``` >>> newtype Foo = Foo Bool deriving Show >>> under not (Foo True) Foo False >>> newtype Bar = Bar String deriving Show >>> under (filter (== 'a')) (Bar "abacaba") Bar "aaaa" ```
As well as the coerced composition operator:
(#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c) (#.) _f = coerce {-# INLINE (#.) #-}
Which currently lives in https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Util... https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Util... but is not exported.
Regarding the location of these functions, I either see them living in their own "Data.Newtype", or they could join Data.Coerce. I would personally create a new module as to avoid "polluting" Data.Coerce with non-class functions, but this is my personal preference.
Thank you for reading.
-- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW:https://glitchbra.in https://glitchbra.in RUN: BSD
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
-- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW: https://glitchbra.in RUN: BSD

Hi Hécate and David,
I'm in support of this proposal. And the module name "Data.Newtype" sounds
good to me 👍
I specifically like the "un" function because it helps to reduce
unnecessary boilerplate. If you have a newtype, it's convenient to specify
an unwrapping function, e.g.
newtype Size = Size
{ unSize :: Int
}
But then, it becomes awkward in two scenarios:
1. When newtypes are long, e.g. "PasswordHash".
2. When you rename newtypes, you also need to rename the unwrapping
function. While renaming the constructor makes total sense to me, because
you want to be explicit in what particular newtype you wrap your values,
renaming the unwrapping function looks to me like maintaining the
unnecessary boilerplate.
Type inference is a valid concern, but those functions are opt-in, and if
people are worried about type inference, they can use type applications or
good old record fields. Also, the order of type variables for the
implementations from "Relude" is optimized for usage with
"TypeApplications", so it's quite convenient to wrap and unwrap newtypes.
Best regards,
Dmitrii
On Wed, 11 Nov 2020 at 10:01, Hécate
Do you think that they will produce unwanted inference even with -XTypeApplications? Le 11/11/2020 à 08:42, David Feuer a écrit :
For the most part, I oppose adding these to base. I'm most sympathetic to adding (.#) and (#.), originally from the profunctors package, as they seem to pop up quite a lot. For the rest, inference can be a real problem. coercible-utils goes to quite a lot of trouble to make these functions reasonably usable, but I don't think we want that sort of machinery in `base`.
On Tue, Nov 10, 2020, 8:23 AM Hécate
wrote: Hello, CLC and haskell-libraries,
I am opening a proposal process to consider the integration of several helper functions in `base`, operating on Newtypes, and all based on `coerce`.
My motivations are that we ought to provide a minimum set of tools in order to work effectively with one of our most beloved and ubiquitous language features.
Now, these functions that I am about to present to you all do not come out of nowhere. They have been integrated to Kowainik's alternative prelude "Relude", and seem to have found their use amongst their users, me included. Their documentation can be found here => https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype... but I am reproducing them below for convenience:
--- un :: forall a n. Coercible a n => n -> a
Unwraps value from newtype.
```
newtype Size = Size Int deriving Show un @Int (Size 5) 5 un (Size 5) == length ['a', 'x', 'b'] False
--- wrap :: forall n a. Coercible a n => a -> n Wraps value to newtype. Behaves exactly as 'un' but has more meaningful name in case you need to convert some value to newtype.
newtype Flag = Flag Bool deriving (Show, Eq) wrap False == Flag True False
--- under :: forall n a. Coercible a n => (n -> n) -> a -> a Applies function to the content of newtype. This function is not supposed to be used on newtypes that are created with the help of smart constructors.
newtype Foo = Foo Bool deriving Show under not (Foo True) Foo False newtype Bar = Bar String deriving Show under (filter (== 'a')) (Bar "abacaba") Bar "aaaa"
As well as the coerced composition operator: (#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c) (#.) _f = coerce {-# INLINE (#.) #-} Which currently lives in https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Utils.html#%23 but is not exported. Regarding the location of these functions, I either see them living in their own "Data.Newtype", or they could join Data.Coerce. I would personally create a new module as to avoid "polluting" Data.Coerce with non-class functions, but this is my personal preference. Thank you for reading. -- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW: https://glitchbra.in RUN: BSD _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
-- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW: https://glitchbra.in RUN: BSD
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Certainly you can work around not having good inference. But at what point
are you better off just using `coerce` directly?
On Wed, Nov 11, 2020, 5:01 AM Hécate
Do you think that they will produce unwanted inference even with -XTypeApplications? Le 11/11/2020 à 08:42, David Feuer a écrit :
For the most part, I oppose adding these to base. I'm most sympathetic to adding (.#) and (#.), originally from the profunctors package, as they seem to pop up quite a lot. For the rest, inference can be a real problem. coercible-utils goes to quite a lot of trouble to make these functions reasonably usable, but I don't think we want that sort of machinery in `base`.
On Tue, Nov 10, 2020, 8:23 AM Hécate
wrote: Hello, CLC and haskell-libraries,
I am opening a proposal process to consider the integration of several helper functions in `base`, operating on Newtypes, and all based on `coerce`.
My motivations are that we ought to provide a minimum set of tools in order to work effectively with one of our most beloved and ubiquitous language features.
Now, these functions that I am about to present to you all do not come out of nowhere. They have been integrated to Kowainik's alternative prelude "Relude", and seem to have found their use amongst their users, me included. Their documentation can be found here => https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype... but I am reproducing them below for convenience:
--- un :: forall a n. Coercible a n => n -> a
Unwraps value from newtype.
```
newtype Size = Size Int deriving Show un @Int (Size 5) 5 un (Size 5) == length ['a', 'x', 'b'] False
--- wrap :: forall n a. Coercible a n => a -> n Wraps value to newtype. Behaves exactly as 'un' but has more meaningful name in case you need to convert some value to newtype.
newtype Flag = Flag Bool deriving (Show, Eq) wrap False == Flag True False
--- under :: forall n a. Coercible a n => (n -> n) -> a -> a Applies function to the content of newtype. This function is not supposed to be used on newtypes that are created with the help of smart constructors.
newtype Foo = Foo Bool deriving Show under not (Foo True) Foo False newtype Bar = Bar String deriving Show under (filter (== 'a')) (Bar "abacaba") Bar "aaaa"
As well as the coerced composition operator: (#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c) (#.) _f = coerce {-# INLINE (#.) #-} Which currently lives in https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Utils.html#%23 but is not exported. Regarding the location of these functions, I either see them living in their own "Data.Newtype", or they could join Data.Coerce. I would personally create a new module as to avoid "polluting" Data.Coerce with non-class functions, but this is my personal preference. Thank you for reading. -- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW: https://glitchbra.in RUN: BSD _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
-- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW: https://glitchbra.in RUN: BSD

Thank you for suggesting these, Hécate.
I personally don't see much benefit in `un` and `wrap` functions, since it is quite straightforward to use coerce directly:
un @Int = coerce @_ @Int
and wrap is the same way:
wrap @SIze = coerce @_ @Size
At what point do we stop creating synonyms? Adding these two functions IMHO is a redundant mental overhead.
On the other hand `#.` operator can be quite handy and I'd be totally in favor of exposing it to the world but from a Data.Coerce module instead of a totally new module. However I would also not call it coerced composition operator, because firstly it doesn't really compose functions it just coerces them and secondly it can be made more polymorphic and then it would be useful with other things than just functions:
(#.) :: forall a b c proxy. Coercible b c => proxy b c -> (a -> b) -> (a -> c)
(#.) _proxy = coerce
With regards to `under` I am a somewhat indifferent, but if it was in base I am sure I'd use it. Naming is a bit odd, but I am not the one to bikeshed.
Sincerely,
Alexey.
‐‐‐‐‐‐‐ Original Message ‐‐‐‐‐‐‐
On Tuesday, November 10, 2020 4:23 PM, Hécate
Hello, CLC and haskell-libraries,
I am opening a proposal process to consider the integration of several helper functions in `base`, operating on Newtypes, and all based on `coerce`.
My motivations are that we ought to provide a minimum set of tools in order to work effectively with one of our most beloved and ubiquitous language features.
Now, these functions that I am about to present to you all do not come out of nowhere. They have been integrated to Kowainik's alternative prelude "Relude", and seem to have found their use amongst their users, me included. Their documentation can be found here => https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype... but I am reproducing them below for convenience:
--- un :: forall a n. Coercible a n => n -> a
Unwraps value from newtype.
```
newtype Size = Size Int deriving Show un @Int (Size 5) 5 un (Size 5) == length ['a', 'x', 'b'] False
wrap :: forall n a. Coercible a n => a -> n Wraps value to newtype. Behaves exactly as 'un' but has more meaningful name in case you need to convert some value to newtype.
newtype Flag = Flag Bool deriving (Show, Eq) wrap False == Flag True False
--- under :: forall n a. Coercible a n => (n -> n) -> a -> a Applies function to the content of newtype. This function is not supposed to be used on newtypes that are created with the help of smart constructors.
newtype Foo = Foo Bool deriving Show under not (Foo True) Foo False newtype Bar = Bar String deriving Show under (filter (== 'a')) (Bar "abacaba") Bar "aaaa"
As well as the coerced composition operator: (#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c) (#.) _f = coerce {-# INLINE (#.) #-} Which currently lives in https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Utils.html#%23 but is not exported. Regarding the location of these functions, I either see them living in their own "Data.Newtype", or they could join Data.Coerce. I would personally create a new module as to avoid "polluting" Data.Coerce with non-class functions, but this is my personal preference. Thank you for reading. -- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW: https://glitchbra.in RUN: BSD

If we add (#.), we should surely also add
(.#) :: forall b c a to. Coercible a b => (b -> c) -> (a `to` b) -> (a ->
c)
(.#) f = const (coerce f)
I think the more-constrained version of `under` from coercible-utils is
probably more useful than the wild one you suggest. The former works under
a single newtype wrapper, using generics to infer what's inside.
On Wed, Nov 11, 2020, 9:54 AM Alexey Kuleshevich
Thank you for suggesting these, Hécate.
I personally don't see much benefit in `un` and `wrap` functions, since it is quite straightforward to use coerce directly:
un @Int = coerce @_ @Int
and wrap is the same way:
wrap @SIze = coerce @_ @Size
At what point do we stop creating synonyms? Adding these two functions IMHO is a redundant mental overhead.
On the other hand `#.` operator can be quite handy and I'd be totally in favor of exposing it to the world but from a Data.Coerce module instead of a totally new module. However I would also not call it coerced composition operator, because firstly it doesn't really compose functions it just coerces them and secondly it can be made more polymorphic and then it would be useful with other things than just functions:
(#.) :: forall a b c proxy. Coercible b c => proxy b c -> (a -> b) -> (a -> c) (#.) _proxy = coerce
With regards to `under` I am a somewhat indifferent, but if it was in base I am sure I'd use it. Naming is a bit odd, but I am not the one to bikeshed.
Sincerely, Alexey.
‐‐‐‐‐‐‐ Original Message ‐‐‐‐‐‐‐ On Tuesday, November 10, 2020 4:23 PM, Hécate
wrote: Hello, CLC and haskell-libraries,
I am opening a proposal process to consider the integration of several helper functions in `base`, operating on Newtypes, and all based on `coerce`.
My motivations are that we ought to provide a minimum set of tools in order to work effectively with one of our most beloved and ubiquitous language features.
Now, these functions that I am about to present to you all do not come out of nowhere. They have been integrated to Kowainik's alternative prelude "Relude", and seem to have found their use amongst their users, me included. Their documentation can be found here => https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype... but I am reproducing them below for convenience:
--- un :: forall a n. Coercible a n => n -> a
Unwraps value from newtype.
```
newtype Size = Size Int deriving Show un @Int (Size 5) 5 un (Size 5) == length ['a', 'x', 'b'] False
--- wrap :: forall n a. Coercible a n => a -> n Wraps value to newtype. Behaves exactly as 'un' but has more meaningful name in case you need to convert some value to newtype.
newtype Flag = Flag Bool deriving (Show, Eq) wrap False == Flag True False
--- under :: forall n a. Coercible a n => (n -> n) -> a -> a Applies function to the content of newtype. This function is not supposed to be used on newtypes that are created with the help of smart constructors.
newtype Foo = Foo Bool deriving Show under not (Foo True) Foo False newtype Bar = Bar String deriving Show under (filter (== 'a')) (Bar "abacaba") Bar "aaaa"
As well as the coerced composition operator: (#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c) (#.) _f = coerce {-# INLINE (#.) #-} Which currently lives in https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Utils.html#%23 but is not exported. Regarding the location of these functions, I either see them living in their own "Data.Newtype", or they could join Data.Coerce. I would personally create a new module as to avoid "polluting" Data.Coerce with non-class functions, but this is my personal preference. Thank you for reading. -- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW: https://glitchbra.in RUN: BSD _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

and/or a new Functor method :: (Coercible a b, Functor m) => (b -> c) -> m b -> m c, which includes the (b -> c) -> (a -> b) -> (a -> c) instance.
Sent from my phone with K-9 Mail.
On November 11, 2020 3:22:00 PM UTC, David Feuer
If we add (#.), we should surely also add
(.#) :: forall b c a to. Coercible a b => (b -> c) -> (a `to` b) -> (a -> c) (.#) f = const (coerce f)
I think the more-constrained version of `under` from coercible-utils is probably more useful than the wild one you suggest. The former works under a single newtype wrapper, using generics to infer what's inside.
On Wed, Nov 11, 2020, 9:54 AM Alexey Kuleshevich
wrote: Thank you for suggesting these, Hécate.
I personally don't see much benefit in `un` and `wrap` functions, since it is quite straightforward to use coerce directly:
un @Int = coerce @_ @Int
and wrap is the same way:
wrap @SIze = coerce @_ @Size
At what point do we stop creating synonyms? Adding these two functions IMHO is a redundant mental overhead.
On the other hand `#.` operator can be quite handy and I'd be totally in favor of exposing it to the world but from a Data.Coerce module instead of a totally new module. However I would also not call it coerced composition operator, because firstly it doesn't really compose functions it just coerces them and secondly it can be made more polymorphic and then it would be useful with other things than just functions:
(#.) :: forall a b c proxy. Coercible b c => proxy b c -> (a -> b) -> (a -> c) (#.) _proxy = coerce
With regards to `under` I am a somewhat indifferent, but if it was in base I am sure I'd use it. Naming is a bit odd, but I am not the one to bikeshed.
Sincerely, Alexey.
‐‐‐‐‐‐‐ Original Message ‐‐‐‐‐‐‐ On Tuesday, November 10, 2020 4:23 PM, Hécate
wrote: Hello, CLC and haskell-libraries,
I am opening a proposal process to consider the integration of several helper functions in `base`, operating on Newtypes, and all based on `coerce`.
My motivations are that we ought to provide a minimum set of tools in order to work effectively with one of our most beloved and ubiquitous language features.
Now, these functions that I am about to present to you all do not come out of nowhere. They have been integrated to Kowainik's alternative prelude "Relude", and seem to have found their use amongst their users, me included. Their documentation can be found here => https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype... but I am reproducing them below for convenience:
--- un :: forall a n. Coercible a n => n -> a
Unwraps value from newtype.
```
newtype Size = Size Int deriving Show un @Int (Size 5) 5 un (Size 5) == length ['a', 'x', 'b'] False
--- wrap :: forall n a. Coercible a n => a -> n Wraps value to newtype. Behaves exactly as 'un' but has more meaningful name in case you need to convert some value to newtype.
newtype Flag = Flag Bool deriving (Show, Eq) wrap False == Flag True False
--- under :: forall n a. Coercible a n => (n -> n) -> a -> a Applies function to the content of newtype. This function is not supposed to be used on newtypes that are created with the help of smart constructors.
newtype Foo = Foo Bool deriving Show under not (Foo True) Foo False newtype Bar = Bar String deriving Show under (filter (== 'a')) (Bar "abacaba") Bar "aaaa"
As well as the coerced composition operator: (#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c) (#.) _f = coerce {-# INLINE (#.) #-} Which currently lives in https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Utils.html#%23 but is not exported. Regarding the location of these functions, I either see them living in their own "Data.Newtype", or they could join Data.Coerce. I would personally create a new module as to avoid "polluting" Data.Coerce with non-class functions, but this is my personal preference. Thank you for reading. -- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW: https://glitchbra.in RUN: BSD _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Hi Alexey, thanks for this feedback. My reason (but it's also been adopted by other library authors) to adopt different names for these variations on `coerce` is that it guides the hand of the developer. That is also why the documentation of these functions have an example with Type Applications. Of course, one can use bare "coerce" in a code-base, but I would be fairly bothered by it if the intention of the original author was not better expressed.
At what point do we stop creating synonyms? Adding these two functions IMHO is a redundant mental overhead.
With regards to `under` I am a somewhat indifferent, but if it was in
This is not a proposal to open the valve on synonyms creation. I am proposing a closed set of helpers to give an API for newtypes. If other people want to add more of those, they will start a CLC process like I did and be submitted to peer review on this mailing-list. base I am sure I'd use it. Naming is a bit odd, but I am not the one to bikeshed. || I have been told on Reddit that 'inside' would be a more explicit name, which I do not disagree with. On 11/11/2020 15:53, Alexey Kuleshevich wrote:
Thank you for suggesting these, Hécate.
I personally don't see much benefit in `un` and `wrap` functions, since it is quite straightforward to use coerce directly:
un @Int = coerce @_ @Int
and wrap is the same way:
wrap @SIze = coerce @_ @Size
At what point do we stop creating synonyms? Adding these two functions IMHO is a redundant mental overhead.
On the other hand `#.` operator can be quite handy and I'd be totally in favor of exposing it to the world but from a Data.Coerce module instead of a totally new module. However I would also not call it coerced composition operator, because firstly it doesn't really compose functions it just coerces them and secondly it can be made more polymorphic and then it would be useful with other things than just functions:
(#.) :: forall a b c proxy. Coercible b c => proxy b c -> (a -> b) -> (a -> c) (#.) _proxy = coerce
With regards to `under` I am a somewhat indifferent, but if it was in base I am sure I'd use it. Naming is a bit odd, but I am not the one to bikeshed.
Sincerely, Alexey.
‐‐‐‐‐‐‐ Original Message ‐‐‐‐‐‐‐ On Tuesday, November 10, 2020 4:23 PM, Hécate
wrote: Hello, CLC and haskell-libraries,
I am opening a proposal process to consider the integration of several helper functions in `base`, operating on Newtypes, and all based on `coerce`.
My motivations are that we ought to provide a minimum set of tools in order to work effectively with one of our most beloved and ubiquitous language features.
Now, these functions that I am about to present to you all do not come out of nowhere. They have been integrated to Kowainik's alternative prelude "Relude", and seem to have found their use amongst their users, me included. Their documentation can be found here => https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype... https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype...
but I am reproducing them below for convenience:
--- un :: forall a n. Coercible a n => n -> a
Unwraps value from newtype.
```
newtype Size = Size Int deriving Show un @Int (Size 5) 5 un (Size 5) == length ['a', 'x', 'b'] False
--- wrap :: forall n a. Coercible a n => a -> n Wraps value to newtype. Behaves exactly as 'un' but has more meaningful name in case you need to convert some value to newtype.
newtype Flag = Flag Bool deriving (Show, Eq) wrap False == Flag True False
--- under :: forall n a. Coercible a n => (n -> n) -> a -> a Applies function to the content of newtype. This function is not supposed to be used on newtypes that are created with the help of smart constructors.
newtype Foo = Foo Bool deriving Show under not (Foo True) Foo False newtype Bar = Bar String deriving Show under (filter (== 'a')) (Bar "abacaba") Bar "aaaa"
As well as the coerced composition operator: (#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c) (#.) _f = coerce {-# INLINE (#.) #-} Which currently lives in https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Utils.html#%23 <https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Utils.html#%23> but is not exported. Regarding the location of these functions, I either see them living in their own "Data.Newtype", or they could join Data.Coerce. I would personally create a new module as to avoid "polluting" Data.Coerce with non-class functions, but this is my personal preference. Thank you for reading. -- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW:https://glitchbra.in <https://glitchbra.in> RUN: BSD
-- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW: https://glitchbra.in RUN: BSD

Probaly this is obvious, but the provided 'un' and 'wrap' don't actually unwrap and wrap newtypes. They each coerce between any Coercible types (which includes wrapping and unwrapping newtypes). It looks like you can use 'un' to turn a 'Sum Word32' into a newtype BitMask :: Word32 -> BitMask.
So it would be totally on the user to guarantee that such use is safe and idiomatic.
Sent from my phone with K-9 Mail.
On November 11, 2020 9:19:38 PM UTC, "Hécate"
Hi Alexey, thanks for this feedback.
My reason (but it's also been adopted by other library authors) to adopt different names for these variations on `coerce` is that it guides the hand of the developer. That is also why the documentation of these functions have an example with Type Applications. Of course, one can use bare "coerce" in a code-base, but I would be fairly bothered by it if the intention of the original author was not better expressed.
At what point do we stop creating synonyms? Adding these two functions IMHO is a redundant mental overhead.
This is not a proposal to open the valve on synonyms creation. I am proposing a closed set of helpers to give an API for newtypes. If other people want to add more of those, they will start a CLC process like I did and be submitted to peer review on this mailing-list.
With regards to `under` I am a somewhat indifferent, but if it was in base I am sure I'd use it. Naming is a bit odd, but I am not the one to bikeshed. || I have been told on Reddit that 'inside' would be a more explicit name, which I do not disagree with.
On 11/11/2020 15:53, Alexey Kuleshevich wrote:
Thank you for suggesting these, Hécate.
I personally don't see much benefit in `un` and `wrap` functions, since it is quite straightforward to use coerce directly:
un @Int = coerce @_ @Int
and wrap is the same way:
wrap @SIze = coerce @_ @Size
At what point do we stop creating synonyms? Adding these two functions IMHO is a redundant mental overhead.
On the other hand `#.` operator can be quite handy and I'd be totally in favor of exposing it to the world but from a Data.Coerce module instead of a totally new module. However I would also not call it coerced composition operator, because firstly it doesn't really compose functions it just coerces them and secondly it can be made more polymorphic and then it would be useful with other things than just functions:
(#.) :: forall a b c proxy. Coercible b c => proxy b c -> (a -> b) -> (a -> c) (#.) _proxy = coerce
With regards to `under` I am a somewhat indifferent, but if it was in base I am sure I'd use it. Naming is a bit odd, but I am not the one to bikeshed.
Sincerely, Alexey.
‐‐‐‐‐‐‐ Original Message ‐‐‐‐‐‐‐ On Tuesday, November 10, 2020 4:23 PM, Hécate
wrote: Hello, CLC and haskell-libraries,
I am opening a proposal process to consider the integration of several helper functions in `base`, operating on Newtypes, and all based on `coerce`.
My motivations are that we ought to provide a minimum set of tools in order to work effectively with one of our most beloved and ubiquitous language features.
Now, these functions that I am about to present to you all do not come out of nowhere. They have been integrated to Kowainik's alternative prelude "Relude", and seem to have found their use amongst their users, me included. Their documentation can be found here => https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype... https://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Newtype...
but I am reproducing them below for convenience:
--- un :: forall a n. Coercible a n => n -> a
Unwraps value from newtype.
```
newtype Size = Size Int deriving Show un @Int (Size 5) 5 un (Size 5) == length ['a', 'x', 'b'] False
--- wrap :: forall n a. Coercible a n => a -> n Wraps value to newtype. Behaves exactly as 'un' but has more meaningful name in case you need to convert some value to newtype.
newtype Flag = Flag Bool deriving (Show, Eq) wrap False == Flag True False
--- under :: forall n a. Coercible a n => (n -> n) -> a -> a Applies function to the content of newtype. This function is not supposed to be used on newtypes that are created with the help of smart constructors.
newtype Foo = Foo Bool deriving Show under not (Foo True) Foo False newtype Bar = Bar String deriving Show under (filter (== 'a')) (Bar "abacaba") Bar "aaaa"
As well as the coerced composition operator: (#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c) (#.) _f = coerce {-# INLINE (#.) #-} Which currently lives in https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Utils.html#%23 <https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Functor.Utils.html#%23> but is not exported. Regarding the location of these functions, I either see them living in their own "Data.Newtype", or they could join Data.Coerce. I would personally create a new module as to avoid "polluting" Data.Coerce with non-class functions, but this is my personal preference. Thank you for reading. -- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW:https://glitchbra.in <https://glitchbra.in> RUN: BSD
-- Hécate ✨ 🐦: @TechnoEmpress IRC: Uniaika WWW: https://glitchbra.in RUN: BSD

Am Do., 12. Nov. 2020 um 01:31 Uhr schrieb Keith
[...] So it would be totally on the user to guarantee that such use is safe and idiomatic.
Slightly changing an old saying about programming languages (from Jon Fairbarin on a Haskell mailing list? Can't remember...): "A good API doesn't make it easy to write correct code, it makes it hard to write incorrect code." Because of this and the arguably poor names, a -1 for this proposal from my side. Cheers, S.
participants (6)
-
Alexey Kuleshevich
-
David Feuer
-
Dmitrii Kovanikov
-
Hécate
-
Keith
-
Sven Panne