2

I was trying to simplify my life with newtype with coerce, but I've encountered a quite painful problem when using it in certain scenario:

import Data.Coerce (coerce)
import Data.Foldable (toList)

-- | newtype instance wrapping foldable type (not necessary [Int])
newtype Foo = Foo [Int]

bar :: [Int]
bar = toList $ coerce $ Foo [1,2,3]

This fails as Haskell is not able to deduce the type correctly.

Is there a way to force this to be correctly resolved? (without directly specifying what coerce should coerce into) Or maybe there is other clean solution? (SO answers suggest mostly the coerce)

majkrzak
  • 1,332
  • 3
  • 14
  • 30

2 Answers2

3

The lens solution you may be looking for is in Control.Lens.Wrapped:

{-# LANGUAGE DeriveGeneric, StandaloneDeriving #-}

import Control.Lens
import Control.Lens.Wrapped
import GHC.Generics
import Data.Foldable (toList)

newtype Foo = Foo [Int] deriving (Generic)
instance Wrapped Foo

bar :: [Int]
bar = toList . view _Wrapped' $ Foo [1,2,3]
K. A. Buhr
  • 45,621
  • 3
  • 45
  • 71
2

The easiest answer is adding a field accessor:

type    Foo :: Type
newtype Foo = Foo { getFoo :: [Int] }

bar :: [Int]
bar = toList $ getFoo $ Foo [1,2,3]

which works even if you parameterise Foo by the Foldable structure:

-- >> toList $ getFoo $ Foo [1,2,3]
-- [1,2,3]
-- >> toList $ getFoo $ Foo Nothing
-- []
type    Foo :: (Type -> Type) -> Type
newtype Foo f = Foo { getFoo :: f Int }

If you do want guided coerce you can imagine a type family that resolves the underlying type. This is a standalone type family, unlike the associated Wrapped from the lens answer. I personally think this type family ought to be included in the standard library with instances magically generated by GHC.

type          Underlying :: Type -> Type
type family   Underlying a
type instance Underlying Foo = [Int]
type instance Underlying Any = Bool
type instance Underlying All = Bool
-- ..

underlying :: Coercible a (Underlying a) => a -> Underlying a
underlying = coerce

bar :: [Int]
bar = toList $ underlying $ Foo [1,2,3]

We don't need to define individual underlying unwrappings, all the definitions are coerce. You can now replace coerce with underlying which gives the compiler some guidance and it replaces getFoo; even in the parameterised case:

type instance Underlying (Foo f) = f Int

-- >> toList $ underlying $ Foo [1,2,3]
-- [1,2,3]
-- >> toList $ underlying $ Foo Nothing
-- []

Without the type family to tell what the target type is coerce is too general. There are arbitrarily many types coercible to/from Foo:

coerce
  :: Foo -> [Int]
  :: Foo -> Identity [Int]
  :: Foo -> Identity (Sum (Product (Alt Identity (Ap [] Int))))
  :: ..

I consider raw coerce appearing in code to be an anti-pattern because of this inference problem, and try to replace it with other abstractions like GeneralizedNewtypeDeriving or DerivingVia when I can.

That being said you are able to hold GHC's hand with TypeApplications where you explicitly specify the return type

>> toList $ coerce @_ @[Int] $ Foo [1,2,3]
[1,2,3]
>> toList $ coerce @_ @(Maybe Int) $ Foo Nothing
[]

or specify the input type of toList

>> toList @[] @Int $ coerce $ Foo [1,2,3]
[1,2,3]
>> toList @Maybe @Int $ coerce $ Foo Nothing
[]
Iceland_jack
  • 6,848
  • 7
  • 37
  • 46