Using Record Patterns Synonyms to evolve a data type?

I was trying to make a backwards compatible change to a library using a record pattern ( 6.7.4. Pattern synonyms — Glasgow Haskell Compiler 9.15.20251008 User's Guide )

The idea would be to change the underlying data type with forward/backwards compatible options, but expose a record pattern that allows other dependencies to transition using the pattern. After all dependencies have upgraded, then I could remove accessorV1.

This compiles fine:

{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ExplicitNamespaces #-}
module Test (
    TypeA(..),
    pattern TypeA,
    accessor,
    dToB,
    B,
    C,
    D,
    test,
    defaultN
  ) where
import Data.Maybe

newtype B = B Int deriving (Show)
newtype C = C String deriving (Show)
newtype D = D Int deriving (Show)

-- Convert from new -> old
dToB :: D -> B
dToB (D n) = B (n * 2)

-- OLD VERSION
-- data TypeA = TypeA {
--     otherValue :: String,
--     accessor :: B -> C
--  }
data TypeA = TypeANew {
    otherValue :: String,
    accessorV2 :: D -> C,
    accessorV1 :: B -> C
  }

pattern TypeA :: String -> (B -> C) -> TypeA
pattern TypeA {otherValue , accessor} <- TypeANew { otherValue = otherValue, accessorV1 = accessor }
  where
    TypeA v a = let convertDtoC :: D -> C
                    convertDtoC d = a (dToB d)
                in TypeANew v convertDtoC a
{-# DEPRECATED data TypeA, accessor "Use TypeAnew instead" #-}

test a = do
  case a of
    TypeA { otherValue, accessor } -> do
      print (otherValue, accessor $ B 45)

  case a of
    TypeANew { otherValue, accessorV2, accessorV1 } -> do
      print (otherValue, accessorV2 $ D 45)

defaultN = TypeA {
    otherValue = "str 23",
    accessor = \b -> C ("C -> " ++ show b)
  }

Also, this works completely fine (inside the same file):

defaultA = TypeA {
    otherValue = "v23",
    accessor = \b -> C ("C -> " ++ show b)
  }

main = do 
  putStrLn "hello world"
  let btoC (B b) = C ("B_Results: " ++ show b)
  let dtoC (D d) = C ("C_Result: " ++ show d)
  -- use the new constructor
  let defaultA = TypeANew {otherValue = "defaultValue", accessorV2 = dtoC, accessorV1 = btoC}
  putStrLn "---- Case 1: A constructed with btoC"
  -- use the pattern synonym constructor
  let a = TypeA { otherValue = "test", accessor = btoC }
  test a
  putStrLn "---- Case 2: defaultA constructed with nyaa"
  -- pattern match using the pattern synonym
  let a = defaultA { accessor = \b -> C ("nyaaaaa" ++ show b) }
  test a
  putStrLn "---- Case 3: defaultA constructed"
  -- pattern match using the base record
  let a = defaultA { accessorV2 = \d -> C ("Override someAccessor2 " ++ show d) }
  test a
  -- Use old interface via pattern synonym

But now, if I put this code in a new module with import Test, or import Test (pattern TypeA) it fails:

Main.hs:11:5: error: [GHC-53822]
    Constructor ‘TypeA’ does not have field ‘otherValue’
   |
11 |     otherValue = "v23",
   |     ^^^^^^^^^^

Is this a limitation of record patterns, or am I doing something wrong?

1 Like

The otherValue fields of TypeA and TypeANew are not identified; you need to export both of them.

@Leary I don’t think it’s possible (or I don’t know how) to export just the pattern’s otherValue, since when I add otherValue to my module exports, then I get:

Error: Ambiguous occurrence ‘otherValue’.
It could refer to
   either the field ‘otherValue’ of pattern synonym ‘TypeA’,
          defined at /home/ec/Code/Test.hs:33:16,
       or the field ‘otherValue’ of record ‘TypeA’,
          defined at /home/ec/Code/Test.hs:27:5. (typecheck) [GHC-87543]

Remove the export list to export everything, or declare TypeA and TypeANew in separate modules.

1 Like

Thanks, both of those approaches work. Can you explain why this is necessary? It seems odd that this can’t be defined & exported within a single module with an explicit export list.

DuplicateRecordFields and PatternSynonyms are not features designed into Haskell, but ad hoc extensions stapled onto it after the fact. Using them in conjunction exposes this minor incompatibility in their individual designs.

3 Likes

I think this is a really good thing to be bringing up, so let me start with a big thank you!

There are some other things that I think are important in this discussion

  1. The answer of have an open export list, may resolve the immediate issue of the exports for the record and pattern, but could also have negative impacts on the way the optimization of the rest of the code in the module. This can be a pretty important point for a library where the solution to providing backwards compatibility ends up harming performance.
  2. Moving things to another module may also not be a good answer because it does not allow users of a library to have a smooth transition to migrate. Consider if this was in a package like text and in particular the common usage was to import a module Data.Text. Then the choices left would be for the new code to live in Data.Text or the now deprecated code. If you put the new code in Data.Text and move the deprecated one to Data.Text.Foo then you have just broken everyone upgrading that doesn’t have -Wdeprecations turned on. But if you do the opposite, then anyone who wants to use the non-deprecated path is now required to have two imports which would mean a code change for anyone that does have -Wdeprecations turned on.

Both of those points above, really lead me to believe we have a feature in PatternSynonyms that could be very useful for the broader ecosystem in providing a more smooth upgrade path in libraries. But we clearly are there right now.

In the past I have run into something similar with PatternSynonyms where I really desired the ability to use the (..) syntax in the export, but found that does not exist. For that particular case however it wasn’t about providing an evolution path for code. The case outlined here I think points to a much greater need for this functionality.

This thread led me to find at least a few related, open, ghc issues to this:

  1. There is one that is exactly about this disambiguation: Cannot disambiguate duplicate pattern synonym record fields in exports (#23963) · Issues · Glasgow Haskell Compiler / GHC · GitLab
  2. A similar-ish one about when using NoFieldSelectors Name clashes when exporting field labels with -XPatternSynonyms and -XNoFieldSelectors (#25292) · Issues · Glasgow Haskell Compiler / GHC · GitLab
  3. A very recent issue that predates this thread by one day around HasField instances. Add built-in HasField instances for pattern synonym record fields (#26489) · Issues · Glasgow Haskell Compiler / GHC · GitLab

Those issues clearly mean there isn’t a full resolution, but if anyone is curious to see previous discussions. And I think further highlight that we have potential for value here that is waiting to be unlocked.

2 Likes

@adamgundry: I know we need some design work and a proposal to address any of the above issues, and you’ve spoken to me directly about this as well as commented on those issues. It is becoming clearer to me that some work to shore up PatternSynonyms would be a potential big win for the ecosystem for providing exactly the initial issue described above. In terms of making progress on that design work, if we find someone willing to do the work, do you have any suggestions on materials to get started or someone to field questions/mentor?

1 Like

I agree that PatternSynonyms could do with some design attention. It would be much better if we could get to a situation where exporting a complete set of pattern synonyms can entirely replace an exported datatype, such that downstream modules will continue to compile unchanged. That’s at least a clear goal to work towards.

I’m not aware of a resource that synthesizes all the issues involved (producing such a thing could be a good first step?) but there are a bunch of labelled tickets ( Issues · Glasgow Haskell Compiler / GHC · GitLab ) and a couple of GHC proposals that didn’t quite make it over the line ( Allow bundling patterns with type synonyms by int-e · Pull Request #28 · ghc-proposals/ghc-proposals · GitHub , More Symmetrical Pattern Synonyms by howtonotwin · Pull Request #138 · ghc-proposals/ghc-proposals · GitHub ) . There’s also discussion about the interaction with HasField specifically at ghc-proposals/proposals/0583-hasfield-redesign.rst at master · ghc-proposals/ghc-proposals · GitHub . I’m always happy to discuss such things further if anyone is interested to try to make progress on a design here.