[Git][ghc/ghc][wip/kirchner/ast] 4 commits: ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var

Fabian Kirchner (@kirchner) gitlab at gitlab.haskell.org
Sun Jun 9 13:18:34 UTC 2024



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


Commits:
12c61144 by Fabian Kirchner at 2024-06-09T15:18:23+02:00
ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var

Progress towards #21592

Specificity, ForAllTyFlag and its' helper functions are extracted from
GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity.

Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on
GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls.
At this point, this would cause cyclic dependencies.

- - - - -
1dfd165e by Fabian Kirchner at 2024-06-09T15:18:23+02:00
ttg: move TopLevelFlag into Language.Haskell.Syntax.Basic

Progress towards #21592

- - - - -
bcd7dc75 by Fabian Kirchner at 2024-06-09T15:18:23+02:00
ttg: move TypeOrData into Language.Haskell.Syntax.Basic

Progress towards #21592

- - - - -
2959c9ad by Fabian Kirchner at 2024-06-09T15:18:23+02:00
ttg: move TyConFlavour into Language.Haskell.Syntax.Basic

Progress towards #21592

- - - - -


8 changed files:

- compiler/GHC/Core/TyCo/Rep.hs-boot
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/Var.hs
- compiler/GHC/Types/Var.hs-boot
- compiler/Language/Haskell/Syntax/Basic.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- + compiler/Language/Haskell/Syntax/Specificity.hs
- compiler/ghc.cabal.in


Changes:

=====================================
compiler/GHC/Core/TyCo/Rep.hs-boot
=====================================
@@ -3,8 +3,9 @@ module GHC.Core.TyCo.Rep where
 
 import GHC.Utils.Outputable ( Outputable )
 import Data.Data  ( Data )
-import {-# SOURCE #-} GHC.Types.Var( Var, VarBndr, ForAllTyFlag, FunTyFlag )
+import {-# SOURCE #-} GHC.Types.Var( Var, VarBndr, FunTyFlag )
 import {-# SOURCE #-} GHC.Core.TyCon ( TyCon )
+import Language.Haskell.Syntax.Specificity (ForAllTyFlag)
 
 data Type
 data Coercion


=====================================
compiler/GHC/Types/Basic.hs
=====================================
@@ -132,7 +132,7 @@ import GHC.Utils.Binary
 import GHC.Types.SourceText
 import qualified GHC.LanguageExtensions as LangExt
 import {-# SOURCE #-} Language.Haskell.Syntax.Type (PromotionFlag(..), isPromoted)
-import Language.Haskell.Syntax.Basic (Boxity(..), isBoxed, ConTag)
+import Language.Haskell.Syntax.Basic (Boxity(..), isBoxed, ConTag, TopLevelFlag(..), isTopLevel, isNotTopLevel, TypeOrData(..), TyConFlavour(..))
 import {-# SOURCE #-} Language.Haskell.Syntax.Expr (HsDoFlavour)
 
 import Control.DeepSeq ( NFData(..) )
@@ -542,19 +542,6 @@ pprRuleName rn = doubleQuotes (ftext rn)
 ************************************************************************
 -}
 
-data TopLevelFlag
-  = TopLevel
-  | NotTopLevel
-  deriving Data
-
-isTopLevel, isNotTopLevel :: TopLevelFlag -> Bool
-
-isNotTopLevel NotTopLevel = True
-isNotTopLevel TopLevel    = False
-
-isTopLevel TopLevel     = True
-isTopLevel NotTopLevel  = False
-
 instance Outputable TopLevelFlag where
   ppr TopLevel    = text "<TopLevel>"
   ppr NotTopLevel = text "<NotTopLevel>"
@@ -2166,22 +2153,6 @@ data TypeOrConstraint
 *                                                                      *
 ********************************************************************* -}
 
--- | Paints a picture of what a 'TyCon' represents, in broad strokes.
--- This is used towards more informative error messages.
-data TyConFlavour tc
-  = ClassFlavour
-  | TupleFlavour Boxity
-  | SumFlavour
-  | DataTypeFlavour
-  | NewtypeFlavour
-  | AbstractTypeFlavour
-  | OpenFamilyFlavour TypeOrData (Maybe tc) -- Just tc <=> (tc == associated class)
-  | ClosedTypeFamilyFlavour
-  | TypeSynonymFlavour
-  | BuiltInTypeFlavour -- ^ e.g., the @(->)@ 'TyCon'.
-  | PromotedDataConFlavour
-  deriving (Eq, Data, Functor)
-
 instance Outputable (TyConFlavour tc) where
   ppr = text . go
     where
@@ -2220,13 +2191,6 @@ tyConFlavourAssoc_maybe :: TyConFlavour tc -> Maybe tc
 tyConFlavourAssoc_maybe (OpenFamilyFlavour _ mb_parent) = mb_parent
 tyConFlavourAssoc_maybe _                               = Nothing
 
--- | Whether something is a type or a data declaration,
--- e.g. a type family or a data family.
-data TypeOrData
-  = IAmData
-  | IAmType
-  deriving (Eq, Data)
-
 instance Outputable TypeOrData where
   ppr IAmData = text "data"
   ppr IAmType = text "type"


=====================================
compiler/GHC/Types/Var.hs
=====================================
@@ -129,6 +129,8 @@ import GHC.Utils.Binary
 import GHC.Utils.Outputable
 import GHC.Utils.Panic
 
+import Language.Haskell.Syntax.Specificity
+
 import Data.Data
 import Control.DeepSeq
 
@@ -455,57 +457,6 @@ updateVarTypeM upd var
 *                                                                      *
 ********************************************************************* -}
 
--- | ForAllTyFlag
---
--- Is something required to appear in source Haskell ('Required'),
--- permitted by request ('Specified') (visible type application), or
--- prohibited entirely from appearing in source Haskell ('Inferred')?
--- See Note [VarBndrs, ForAllTyBinders, TyConBinders, and visibility] in "GHC.Core.TyCo.Rep"
-data ForAllTyFlag = Invisible !Specificity
-                  | Required
-  deriving (Eq, Ord, Data)
-  -- (<) on ForAllTyFlag means "is less visible than"
-
--- | Whether an 'Invisible' argument may appear in source Haskell.
-data Specificity = InferredSpec
-                   -- ^ the argument may not appear in source Haskell, it is
-                   -- only inferred.
-                 | SpecifiedSpec
-                   -- ^ the argument may appear in source Haskell, but isn't
-                   -- required.
-  deriving (Eq, Ord, Data)
-
-pattern Inferred, Specified :: ForAllTyFlag
-pattern Inferred  = Invisible InferredSpec
-pattern Specified = Invisible SpecifiedSpec
-
-{-# COMPLETE Required, Specified, Inferred #-}
-
--- | Does this 'ForAllTyFlag' classify an argument that is written in Haskell?
-isVisibleForAllTyFlag :: ForAllTyFlag -> Bool
-isVisibleForAllTyFlag af = not (isInvisibleForAllTyFlag af)
-
--- | Does this 'ForAllTyFlag' classify an argument that is not written in Haskell?
-isInvisibleForAllTyFlag :: ForAllTyFlag -> Bool
-isInvisibleForAllTyFlag (Invisible {}) = True
-isInvisibleForAllTyFlag Required       = False
-
-isInferredForAllTyFlag :: ForAllTyFlag -> Bool
--- More restrictive than isInvisibleForAllTyFlag
-isInferredForAllTyFlag (Invisible InferredSpec) = True
-isInferredForAllTyFlag _                        = False
-
-isSpecifiedForAllTyFlag :: ForAllTyFlag -> Bool
--- More restrictive than isInvisibleForAllTyFlag
-isSpecifiedForAllTyFlag (Invisible SpecifiedSpec) = True
-isSpecifiedForAllTyFlag _                         = False
-
-coreTyLamForAllTyFlag :: ForAllTyFlag
--- ^ The ForAllTyFlag on a (Lam a e) term, where `a` is a type variable.
--- If you want other ForAllTyFlag, use a cast.
--- See Note [Required foralls in Core] in GHC.Core.TyCo.Rep
-coreTyLamForAllTyFlag = Specified
-
 instance Outputable ForAllTyFlag where
   ppr Required  = text "[req]"
   ppr Specified = text "[spec]"


=====================================
compiler/GHC/Types/Var.hs-boot
=====================================
@@ -2,13 +2,12 @@
 module GHC.Types.Var where
 
 import {-# SOURCE #-} GHC.Types.Name
+import Language.Haskell.Syntax.Specificity (Specificity, ForAllTyFlag)
 
-data ForAllTyFlag
 data FunTyFlag
 data Var
 instance NamedThing Var
 data VarBndr var argf
-data Specificity
 type TyVar = Var
 type Id    = Var
 type TyCoVar = Id


=====================================
compiler/Language/Haskell/Syntax/Basic.hs
=====================================
@@ -2,6 +2,8 @@
 {-# LANGUAGE GeneralisedNewtypeDeriving #-}
 module Language.Haskell.Syntax.Basic where
 
+import Prelude
+
 import Data.Data
 import Data.Eq
 import Data.Ord
@@ -96,3 +98,48 @@ data SrcUnpackedness = SrcUnpack -- ^ {-# UNPACK #-} specified
                      | SrcNoUnpack -- ^ {-# NOUNPACK #-} specified
                      | NoSrcUnpack -- ^ no unpack pragma
      deriving (Eq, Data)
+
+
+{-
+************************************************************************
+*                                                                      *
+Top-level/not-top level flag
+*                                                                      *
+************************************************************************
+-}
+
+data TopLevelFlag
+  = TopLevel
+  | NotTopLevel
+  deriving Data
+
+isTopLevel, isNotTopLevel :: TopLevelFlag -> Bool
+
+isNotTopLevel NotTopLevel = True
+isNotTopLevel TopLevel    = False
+
+isTopLevel TopLevel     = True
+isTopLevel NotTopLevel  = False
+
+-- | Whether something is a type or a data declaration,
+-- e.g. a type family or a data family.
+data TypeOrData
+  = IAmData
+  | IAmType
+  deriving (Eq, Data)
+
+-- | Paints a picture of what a 'TyCon' represents, in broad strokes.
+-- This is used towards more informative error messages.
+data TyConFlavour tc
+  = ClassFlavour
+  | TupleFlavour Boxity
+  | SumFlavour
+  | DataTypeFlavour
+  | NewtypeFlavour
+  | AbstractTypeFlavour
+  | OpenFamilyFlavour TypeOrData (Maybe tc) -- Just tc <=> (tc == associated class)
+  | ClosedTypeFamilyFlavour
+  | TypeSynonymFlavour
+  | BuiltInTypeFlavour -- ^ e.g., the @(->)@ 'TyCon'.
+  | PromotedDataConFlavour
+  deriving (Eq, Data, Functor)


=====================================
compiler/Language/Haskell/Syntax/Decls.hs
=====================================
@@ -97,14 +97,13 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr
 import Language.Haskell.Syntax.Binds
 import Language.Haskell.Syntax.Extension
 import Language.Haskell.Syntax.Type
-import Language.Haskell.Syntax.Basic (Role)
+import Language.Haskell.Syntax.Basic (Role, TopLevelFlag, TypeOrData(..), TyConFlavour(..))
+import Language.Haskell.Syntax.Specificity (Specificity)
 
-import GHC.Types.Basic (TopLevelFlag, OverlapMode, RuleName, Activation
-                       ,TyConFlavour(..), TypeOrData(..))
+import GHC.Types.Basic (OverlapMode, RuleName, Activation)
 import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CCallTarget, CExportSpec)
 import GHC.Types.Fixity (LexicalFixity)
 
-import GHC.Core.Type (Specificity)
 import GHC.Unit.Module.Warnings (WarningTxt)
 import GHC.Utils.Panic.Plain ( assert )
 


=====================================
compiler/Language/Haskell/Syntax/Specificity.hs
=====================================
@@ -0,0 +1,68 @@
+{-# LANGUAGE MultiWayIf, PatternSynonyms #-}
+
+-- TODO Everthing in this module should be moved to
+-- Language.Haskell.Syntax.Decls
+
+module Language.Haskell.Syntax.Specificity (
+        -- * ForAllTyFlags
+        ForAllTyFlag(Invisible,Required,Specified,Inferred),
+        Specificity(..),
+        isVisibleForAllTyFlag, isInvisibleForAllTyFlag, isInferredForAllTyFlag,
+        isSpecifiedForAllTyFlag,
+        coreTyLamForAllTyFlag,
+        ) where
+
+import Prelude
+
+import Data.Data
+
+-- | ForAllTyFlag
+--
+-- Is something required to appear in source Haskell ('Required'),
+-- permitted by request ('Specified') (visible type application), or
+-- prohibited entirely from appearing in source Haskell ('Inferred')?
+-- See Note [VarBndrs, ForAllTyBinders, TyConBinders, and visibility] in "GHC.Core.TyCo.Rep"
+data ForAllTyFlag = Invisible !Specificity
+                  | Required
+  deriving (Eq, Ord, Data)
+  -- (<) on ForAllTyFlag means "is less visible than"
+
+-- | Whether an 'Invisible' argument may appear in source Haskell.
+data Specificity = InferredSpec
+                   -- ^ the argument may not appear in source Haskell, it is
+                   -- only inferred.
+                 | SpecifiedSpec
+                   -- ^ the argument may appear in source Haskell, but isn't
+                   -- required.
+  deriving (Eq, Ord, Data)
+
+pattern Inferred, Specified :: ForAllTyFlag
+pattern Inferred  = Invisible InferredSpec
+pattern Specified = Invisible SpecifiedSpec
+
+{-# COMPLETE Required, Specified, Inferred #-}
+
+-- | Does this 'ForAllTyFlag' classify an argument that is written in Haskell?
+isVisibleForAllTyFlag :: ForAllTyFlag -> Bool
+isVisibleForAllTyFlag af = not (isInvisibleForAllTyFlag af)
+
+-- | Does this 'ForAllTyFlag' classify an argument that is not written in Haskell?
+isInvisibleForAllTyFlag :: ForAllTyFlag -> Bool
+isInvisibleForAllTyFlag (Invisible {}) = True
+isInvisibleForAllTyFlag Required       = False
+
+isInferredForAllTyFlag :: ForAllTyFlag -> Bool
+-- More restrictive than isInvisibleForAllTyFlag
+isInferredForAllTyFlag (Invisible InferredSpec) = True
+isInferredForAllTyFlag _                        = False
+
+isSpecifiedForAllTyFlag :: ForAllTyFlag -> Bool
+-- More restrictive than isInvisibleForAllTyFlag
+isSpecifiedForAllTyFlag (Invisible SpecifiedSpec) = True
+isSpecifiedForAllTyFlag _                         = False
+
+coreTyLamForAllTyFlag :: ForAllTyFlag
+-- ^ The ForAllTyFlag on a (Lam a e) term, where `a` is a type variable.
+-- If you want other ForAllTyFlag, use a cast.
+-- See Note [Required foralls in Core] in GHC.Core.TyCo.Rep
+coreTyLamForAllTyFlag = Specified


=====================================
compiler/ghc.cabal.in
=====================================
@@ -976,6 +976,7 @@ Library
         Language.Haskell.Syntax.Lit
         Language.Haskell.Syntax.Module.Name
         Language.Haskell.Syntax.Pat
+        Language.Haskell.Syntax.Specificity
         Language.Haskell.Syntax.Type
 
     autogen-modules: GHC.Platform.Constants



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f3573f65620b17534170bf01136eec1a8f1ef2f6...2959c9ad201f867c11793da4845afdbcb78c7097

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f3573f65620b17534170bf01136eec1a8f1ef2f6...2959c9ad201f867c11793da4845afdbcb78c7097
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/20240609/02bc9180/attachment-0001.html>


More information about the ghc-commits mailing list