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