Haskell mini-idiom: constraining coerce

I really like using coerce. It allows you to skip tedious manual wrapping and unwrapping of newtypes. The instance for functions is especially useful, avoiding you the drudgery of going through all the positional parameters before reaching the result that you want to change.

Yet sometimes coerce is a bit too powerful. When using it with complex types, I start to second-guess myself, hoping that I’m not mistakenly plugging some value which happens to fit because some newtype I hadn’t considered is unexpectedly unwrapped.

For example, recently I had the need to work with deeply nested compositions of functors. Something like:

import Data.Functor.Compose
type Phases = IO `Compose` IO `Compose` IO `Compose` IO

defining values of this type is very tedious because of the Compose spam:

value :: Phases Int
value = Compose (pure (Compose (pure (Compose (pure (pure 5))))))
-- in the real case, each applicative layer performs actual effects

It’s simpler to define a newtype-less value, and then coerce it:

bareValue :: IO (IO (IO (IO Int)))
bareValue = pure $ pure $ pure $ pure 5
-- in the real case, each applicative layer performs actual effects

value2 :: Phases Int 
value2 = coerce bareValue

Alas, suppose we had some other value like this lying around:

-- We don't want this newtype to be coerced, but we might do it by accident.
newtype DoNotUnwrap = DoNotUnwrap Int

dangerousBareValue :: IO (IO (IO (IO DoNotUnwrap)))
dangerousBareValue = pure $ pure $ pure $ pure (DoNotUnwrap 5)

coerce works fine with it:

-- bad!
value3 :: Phases Int 
value3 = coerce dangerousBareValue

What we need is a restricted form of coerce which only removes the Compose newtypes, and nothing more. To express "only removes the Compose" we can use a type family:

type family Bare x where
  Bare (Compose outer inner x) = Bare (outer (Bare (inner x)))
  Bare other = other

With Bare, we can define a restricted coerce and use it like this:

fromBare :: Coercible x (Bare x) => Bare x -> x
fromBare = coerce

value4 :: Phases Int
value4 = fromBare bareValue

-- doesn't compile (good!)
-- value5 :: Phases Int
-- value5 = fromBare dangerousBareValue

Another example. The Servant library expects its handlers to work in ExceptT. But suppose that all your candidate handlers work by returning an Either :

type Handler = Int -> String -> ExceptT String IO Int

eitherHandler :: Int -> String -> IO (Either String Int)
eitherHandler = undefined

-- ugh! tedious to write
manuallyAdaptedHandler :: Handler
manuallyAdaptedHandler i s = ExceptT (eitherHandler i s)

As before, we can use coerce directly:

handler2 :: Handler
handler2 = coerce eitherHandler

but again we have problematic cases:

dangerousEitherHandler :: Int -> String -> IO (Either String DoNotUnwrap)
dangerousEitherHandler = undefined

-- bad!
handler3 :: Handler
handler3 = coerce dangerousEitherHandler

We can play the same type family trick:

type family BareH x where
  BareH (ExceptT e IO r) = IO (Either e r)
  BareH (input -> output) = input -> BareH output
  BareH other = TypeError (Text "unexpedted value at the tip: " 
                            :<>: ShowType other)

fromBareH :: Coercible x (BareH x) => BareH x -> x
fromBareH = coerce

handler4 :: Handler 
handler4 = fromBareH eitherHandler

-- doesn't compile (good!)
-- handler5 :: Handler 
-- handler5 = fromBareH dangerousEitherHandler

The full gist is here.

So, how do you restrain the unbridled power of coerce?

1 Like

I can’t say I ever had this problem, but could you not use type roles instead?

Yes, one solution would be to ensure that no types are unintentionally coercibe. But I still like the idea of constraining coerce itself, making it say “only these specific newtypes will change here”.

Any reason why

  BareH (input -> output) = input -> BareH output

isn’t

  BareH (input -> output) = BareH input -> BareH output

besides that you didn’t need it in your code yet?

In that case I was only interested in changing the monadic action at the “tip” of the handler, so I didn’t touch the argument.

I’ll try it here:

There is one type annotation I can remove this way :smiley:

1 Like
-- We don't want this newtype to be coerced, but we might do it by accident.
newtype DoNotUnwrap = DoNotUnwrap Int

GHC does not support coercion through a newtype unless its data constructor is in scope. So to prevent “doing it by accident”, just don’t export the data constructor DoNotUnwrap.

That seems simple enough. But maybe I’m missing the point.

It would be odd to use DoNotUnwrap in public APIs…

Here is an example:

module NonEmpty (NE, singleton, (++), length) where
import qualified Data.List
import Data.Monoid
import Data.Coerce
newtype NE a = NE [a]
singleton :: a -> NE a
singleton = wombaz singleton
(++) :: NE a -> NE a -> NE a
(++) = wombaz (Data.List.++)
length :: NE a -> Int
length = wombaz Data.List.length

-- This function doesn't make much sense, but it uses another newtype in its signature
sequenceIdentity :: NE (Identity a) -> Identity (NE a)
sequenceIdentity = wombaz sequence

The idea behind wombaz is that it takes the internal implementation, with [a], and adds the NE newtype wrappers as needed. So it should work at these types:

wombaz :: (a -> [a]) -> (a -> NE a)
wombaz :: ([a] -> [a] -> [a]) -> (NE a -> NE a -> NE a)
wombaz :: ([a] -> Int) ->  (NE a -> Int)
wombaz :: ([Identity a] -> Identity [a]) ->  (NE (Identity a) -> Identity (NE a))

Indeed, coerce can be instantiated to all these types! But

  • it does too much. It can replace Identity a with a, that would miss the point of “open up the abstraction introduced by NE”.
  • because it does too much, it has bad type inference; in sequenceIdentity we’d have to give the argument an explicit type.

With @danidiaz’s idiom, we can write

wombaz :: Coercible a (UnNE a) => UnNE a -> a
wombaz = coerce

with a suitable type class UnNE, and solve both problems: Given the external type signature (involving NE), GHC can infer the exact type of the argument to wombaz, and only the NE newtype is unwrapped.

The annoying this that I have to write UnNE by hand, and I’d prefer to have declarative way to say “In type a, replace all UnNE with [], even under type constructed (as permitted by the roles)”. But writing it out isn’t too bad for a first approximation.

(This post was merged from another thread, the conversation joins a few comments below.)

The classic way of creating abstractions in Haskell is using a newtype, and then pattern-matching or constructing the newtype at the boundary of your code:

module NonEmpty (NE, singleton, (++), length) where
import qualified Data.List
newtype NE a = NE [a]
singleton :: a -> NE a
singleton x = NE $ Data.List.singleton x
(++) :: NE a -> NE a -> NE a
(++) (NE xs) (NE ys) = NE $ (Data.List.++) xs ys
length :: NE a -> Int
length (NE xs) = length xs

Recently, I have adopted a less noisy style of simply using coerce instead of manually finding the right places to project out or into my newtype

module NonEmpty (NE, singleton, (++), length) where
import qualified Data.List
import Data.Coerce
newtype NE a = NE [a]
singleton :: a -> NE a
singleton = coerce singleton
(++) :: NE a -> NE a -> NE a
(++) = coerce (Data.List.++)
length :: NE a -> Int
length = coerce Data.List.length

This is neat, but only works well if the compiler can infer the type of the thing passed to coerce, but will fail if there is too much polymorphism around.

Also, I kinda want to say “resolve just NE, but nothing else”.

So would it not be nice to have a function

open :: Newtype tc a b => a -> b

that allows me to write

module NonEmpty (NE, singleton, (++), length) where
import qualified Data.List
import Data.Coerce
newtype NE a = NE [a]
singleton :: a -> NE a
singleton = open @NE singleton
(++) :: NE a -> NE a -> NE a
(++) = open @NE (Data.List.++)
length :: NE a -> Int
length = open @NE Data.List.length

and where this Newtype tc a b constraint

  • behaves like Coercible a b, but
  • only looks through the newtype mentioned in tc (if the constructor is in scope)
  • does so in a directed way (of course reversing the direction in negative position)
  • and thus can have better type inference. In particular, if b is known, a can be inferred.

(The tc parameter is probably polykinded.)

Just throwing this out there. Might be a nice little exercise in writing a typechecker plugin.

3 Likes

I like that this would solve a practical problem which I’ve also encountered before.

However, I can’t help but feeling like this is a band-aid over the problems of Haskell’s default encapsulation and module system. Instead, we could push Backpack as the way forward: just make NE a signature and mix in Data.List as the implementation.

Yes, I agree that this is just an experiment about an idiom that might be prettier if done some other, more integrated way. But a band-aid, if shown to be useful, can mean that something more built in or elegant would be worthwhile pursuing.

I kinda want to say “resolve just NE , but nothing else”.

For simple cases in which the newtype is fixed, I’ve used type families to constrain coerce.

But I haven’t found a way of doing it for arbitrary newtypes.

That’s a neat idiom as well, using a type family as the second argument to Coercible. Maybe I’ll use that!

1 Like

I think you have a typo. I was confused for a second with newtype NE a = NE a and I guess you mean newtype NE a = NE [a].

I haven’t used coerce that much with newtypes, always going the manual route, but I can see how open would be useful (and I need to have a look at Dani Diaz’s trick!)

1 Like

Thanks, fixed!

I suggest to merge the threads, so further comments best at

1 Like

Done. Maybe you want to edit some of your first post to make them fit better in this thread.