From d99a617bf1c104760e53c294cbe0b6ea752cd242 Mon Sep 17 00:00:00 2001
From: Ben Gamari <ben@well-typed.com>
Date: Wed, 23 Apr 2025 08:55:06 -0400
Subject: [PATCH] Move Data ModuleName instance to
 Language.Haskell.Syntax.Module.Name

Fixes #25968.
---
 compiler/GHC/Unit/Types.hs                      | 9 ---------
 compiler/Language/Haskell/Syntax/Module/Name.hs | 9 +++++++++
 2 files changed, 9 insertions(+), 9 deletions(-)

diff --git a/compiler/GHC/Unit/Types.hs b/compiler/GHC/Unit/Types.hs
index 5d3f43063b0..278c9067649 100644
--- a/compiler/GHC/Unit/Types.hs
+++ b/compiler/GHC/Unit/Types.hs
@@ -1,5 +1,3 @@
-{-# OPTIONS_GHC -Wno-orphans #-} -- instance Data ModuleName
-
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveTraversable #-}
@@ -117,13 +115,6 @@ data GenModule unit = Module
    }
    deriving (Eq,Ord,Data,Functor)
 
--- TODO: should be moved back into Language.Haskell.Syntax.Module.Name
-instance Data ModuleName where
-  -- don't traverse?
-  toConstr _   = abstractConstr "ModuleName"
-  gunfold _ _  = error "gunfold"
-  dataTypeOf _ = mkNoRepType "ModuleName"
-
 -- | A Module is a pair of a 'Unit' and a 'ModuleName'.
 type Module = GenModule Unit
 
diff --git a/compiler/Language/Haskell/Syntax/Module/Name.hs b/compiler/Language/Haskell/Syntax/Module/Name.hs
index 632baa61e9c..85d8c687945 100644
--- a/compiler/Language/Haskell/Syntax/Module/Name.hs
+++ b/compiler/Language/Haskell/Syntax/Module/Name.hs
@@ -3,6 +3,7 @@ module Language.Haskell.Syntax.Module.Name where
 import Prelude
 
 import Data.Char (isAlphaNum)
+import Data.Data
 import Control.DeepSeq
 import qualified Text.ParserCombinators.ReadP as Parse
 import System.FilePath
@@ -12,6 +13,14 @@ import GHC.Data.FastString
 -- | A ModuleName is essentially a simple string, e.g. @Data.List@.
 newtype ModuleName = ModuleName FastString deriving (Show, Eq)
 
+instance Data ModuleName where
+  -- don't traverse?
+  toConstr x   = constr
+    where
+      constr = mkConstr (dataTypeOf x) "{abstract:ModuleName}" [] Prefix
+  gunfold _ _  = error "gunfold"
+  dataTypeOf _ = mkNoRepType "ModuleName"
+
 instance Ord ModuleName where
   nm1 `compare` nm2 = stableModuleNameCmp nm1 nm2
 
-- 
GitLab