[Git][ghc/ghc][wip/kirchner/ast] AST: move conDetailsArity into GHC.Rename.Module

Fabian Kirchner (@kirchner) gitlab at gitlab.haskell.org
Sat Jun 8 16:30:26 UTC 2024



Fabian Kirchner pushed to branch wip/kirchner/ast at Glasgow Haskell Compiler / GHC


Commits:
5c2a4c3e by Fabian Kirchner at 2024-06-08T18:27:23+02:00
AST: move conDetailsArity into GHC.Rename.Module

The function conDetailsArity is only used inside GHC.Rename.Module.  We
therefore move it there from Language.Haskell.Syntax.Lit.

- - - - -


2 changed files:

- compiler/GHC/Rename/Module.hs
- compiler/Language/Haskell/Syntax/Type.hs


Changes:

=====================================
compiler/GHC/Rename/Module.hs
=====================================
@@ -3,6 +3,7 @@
 {-# LANGUAGE NamedFieldPuns      #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeFamilies        #-}
+{-# LANGUAGE LambdaCase          #-}
 
 {-# OPTIONS_GHC -Wno-incomplete-uni-patterns   #-}
 
@@ -54,6 +55,7 @@ import GHC.Types.Name.Set
 import GHC.Types.Name.Env
 import GHC.Utils.Outputable
 import GHC.Data.Bag
+import GHC.Types.Basic (Arity)
 import GHC.Types.Basic  ( TypeOrKind(..) )
 import GHC.Data.FastString
 import GHC.Types.SrcLoc as SrcLoc
@@ -2558,6 +2560,12 @@ extendPatSynEnv dup_fields_ok has_sel val_decls local_fix_env thing = do {
       | otherwise
       = return names
 
+conDetailsArity :: (rec -> Arity) -> HsConDetails tyarg arg rec -> Arity
+conDetailsArity recToArity = \case
+  PrefixCon _ args -> length args
+  RecCon rec -> recToArity rec
+  InfixCon _ _ -> 2
+
 {-
 *********************************************************
 *                                                      *


=====================================
compiler/Language/Haskell/Syntax/Type.hs
=====================================
@@ -48,7 +48,7 @@ module Language.Haskell.Syntax.Type (
 
         ConDeclField(..), LConDeclField,
 
-        HsConDetails(..), noTypeArgs, conDetailsArity,
+        HsConDetails(..), noTypeArgs,
 
         FieldOcc(..), LFieldOcc,
         AmbiguousFieldOcc(..), LAmbiguousFieldOcc,
@@ -66,7 +66,6 @@ import Language.Haskell.Syntax.Extension
 import GHC.Types.Name.Reader ( RdrName )
 import GHC.Core.DataCon( HsSrcBang(..) )
 import GHC.Core.Type (Specificity)
-import GHC.Types.Basic (Arity)
 
 import GHC.Hs.Doc (LHsDoc)
 import GHC.Data.FastString (FastString)
@@ -77,7 +76,7 @@ import Data.Maybe
 import Data.Eq
 import Data.Bool
 import Data.Char
-import Prelude (Integer, length)
+import Prelude (Integer)
 import Data.Ord (Ord)
 
 {-
@@ -1108,12 +1107,6 @@ data HsConDetails tyarg arg rec
 noTypeArgs :: [Void]
 noTypeArgs = []
 
-conDetailsArity :: (rec -> Arity) -> HsConDetails tyarg arg rec -> Arity
-conDetailsArity recToArity = \case
-  PrefixCon _ args -> length args
-  RecCon rec -> recToArity rec
-  InfixCon _ _ -> 2
-
 {-
 Note [ConDeclField pass]
 ~~~~~~~~~~~~~~~~~~~~~~~~~



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5c2a4c3e7d517fd1eb6f7c0fe01cfb2d9e7976a6

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5c2a4c3e7d517fd1eb6f7c0fe01cfb2d9e7976a6
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240608/8875e188/attachment-0001.html>


More information about the ghc-commits mailing list