[Git][ghc/ghc][master] Parser: move parser utils into their own module

Marge Bot gitlab at gitlab.haskell.org
Sat Dec 12 03:42:20 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
690c8946 by Sylvain Henry at 2020-12-11T22:42:09-05:00
Parser: move parser utils into their own module

Move code unrelated to runtime evaluation out of GHC.Runtime.Eval

- - - - -


4 changed files:

- compiler/GHC.hs
- + compiler/GHC/Parser/Utils.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/ghc.cabal.in


Changes:

=====================================
compiler/GHC.hs
=====================================
@@ -325,6 +325,7 @@ import qualified GHC.Parser as Parser
 import GHC.Parser.Lexer
 import GHC.Parser.Annotation
 import GHC.Parser.Errors.Ppr
+import GHC.Parser.Utils
 
 import GHC.Iface.Load        ( loadSysInterface )
 import GHC.Hs
@@ -1347,6 +1348,18 @@ getPackageModuleInfo hsc_env mdl
                         minf_modBreaks = emptyModBreaks
                 }))
 
+availsToGlobalRdrEnv :: ModuleName -> [AvailInfo] -> GlobalRdrEnv
+availsToGlobalRdrEnv mod_name avails
+  = mkGlobalRdrEnv (gresFromAvails (Just imp_spec) avails)
+  where
+      -- We're building a GlobalRdrEnv as if the user imported
+      -- all the specified modules into the global interactive module
+    imp_spec = ImpSpec { is_decl = decl, is_item = ImpAll}
+    decl = ImpDeclSpec { is_mod = mod_name, is_as = mod_name,
+                         is_qual = False,
+                         is_dloc = srcLocSpan interactiveSrcLoc }
+
+
 getHomeModuleInfo :: HscEnv -> Module -> IO (Maybe ModuleInfo)
 getHomeModuleInfo hsc_env mdl =
   case lookupHpt (hsc_HPT hsc_env) (moduleName mdl) of


=====================================
compiler/GHC/Parser/Utils.hs
=====================================
@@ -0,0 +1,58 @@
+module GHC.Parser.Utils
+    ( isStmt
+    , hasImport
+    , isImport
+    , isDecl
+    )
+where
+
+import GHC.Prelude
+import GHC.Hs
+import GHC.Data.StringBuffer
+import GHC.Data.FastString
+import GHC.Types.SrcLoc
+
+import qualified GHC.Parser.Lexer as Lexer (P (..), ParseResult(..), unP, initParserState)
+import GHC.Parser.Lexer (ParserOpts)
+import qualified GHC.Parser       as Parser (parseStmt, parseModule, parseDeclaration, parseImport)
+
+
+-- | Returns @True@ if passed string is a statement.
+isStmt :: ParserOpts -> String -> Bool
+isStmt pflags stmt =
+  case parseThing Parser.parseStmt pflags stmt of
+    Lexer.POk _ _ -> True
+    Lexer.PFailed _ -> False
+
+-- | Returns @True@ if passed string has an import declaration.
+hasImport :: ParserOpts -> String -> Bool
+hasImport pflags stmt =
+  case parseThing Parser.parseModule pflags stmt of
+    Lexer.POk _ thing -> hasImports thing
+    Lexer.PFailed _ -> False
+  where
+    hasImports = not . null . hsmodImports . unLoc
+
+-- | Returns @True@ if passed string is an import declaration.
+isImport :: ParserOpts -> String -> Bool
+isImport pflags stmt =
+  case parseThing Parser.parseImport pflags stmt of
+    Lexer.POk _ _ -> True
+    Lexer.PFailed _ -> False
+
+-- | Returns @True@ if passed string is a declaration but __/not a splice/__.
+isDecl :: ParserOpts -> String -> Bool
+isDecl pflags stmt =
+  case parseThing Parser.parseDeclaration pflags stmt of
+    Lexer.POk _ thing ->
+      case unLoc thing of
+        SpliceD _ _ -> False
+        _ -> True
+    Lexer.PFailed _ -> False
+
+parseThing :: Lexer.P thing -> ParserOpts -> String -> Lexer.ParseResult thing
+parseThing parser opts stmt = do
+  let buf = stringToStringBuffer stmt
+      loc = mkRealSrcLoc (fsLit "<interactive>") 1 1
+
+  Lexer.unP parser (Lexer.initParserState opts buf loc)


=====================================
compiler/GHC/Runtime/Eval.hs
=====================================
@@ -17,7 +17,6 @@ module GHC.Runtime.Eval (
         Resume(..), History(..),
         execStmt, execStmt', ExecOptions(..), execOptions, ExecResult(..), resumeExec,
         runDecls, runDeclsWithLocation, runParsedDecls,
-        isStmt, hasImport, isImport, isDecl,
         parseImportDecl, SingleStep(..),
         abandon, abandonAll,
         getResumeContext,
@@ -26,7 +25,6 @@ module GHC.Runtime.Eval (
         getHistoryModule,
         back, forward,
         setContext, getContext,
-        availsToGlobalRdrEnv,
         getNamesInScope,
         getRdrNamesInScope,
         moduleIsInterpreted,
@@ -96,17 +94,12 @@ import GHC.Utils.Error
 import GHC.Utils.Outputable
 import GHC.Utils.Misc
 
-import qualified GHC.Parser.Lexer as Lexer (P (..), ParseResult(..), unP, initParserState)
-import GHC.Parser.Lexer (ParserOpts)
-import qualified GHC.Parser       as Parser (parseStmt, parseModule, parseDeclaration, parseImport)
-
 import GHC.Types.RepType
 import GHC.Types.Fixity.Env
 import GHC.Types.Var
 import GHC.Types.Id as Id
 import GHC.Types.Name      hiding ( varName )
 import GHC.Types.Name.Set
-import GHC.Types.Avail
 import GHC.Types.Name.Reader
 import GHC.Types.Var.Env
 import GHC.Types.SrcLoc
@@ -126,7 +119,6 @@ import qualified Data.IntMap as IntMap
 import Data.List (find,intercalate)
 import Data.Map (Map)
 import qualified Data.Map as Map
-import GHC.Data.StringBuffer (stringToStringBuffer)
 import Control.Monad
 import Control.Monad.Catch as MC
 import Data.Array
@@ -796,17 +788,6 @@ findGlobalRdrEnv hsc_env imports
       Left err -> Left (mod, err)
       Right env -> Right env
 
-availsToGlobalRdrEnv :: ModuleName -> [AvailInfo] -> GlobalRdrEnv
-availsToGlobalRdrEnv mod_name avails
-  = mkGlobalRdrEnv (gresFromAvails (Just imp_spec) avails)
-  where
-      -- We're building a GlobalRdrEnv as if the user imported
-      -- all the specified modules into the global interactive module
-    imp_spec = ImpSpec { is_decl = decl, is_item = ImpAll}
-    decl = ImpDeclSpec { is_mod = mod_name, is_as = mod_name,
-                         is_qual = False,
-                         is_dloc = srcLocSpan interactiveSrcLoc }
-
 mkTopLevEnv :: HomePackageTable -> ModuleName -> Either String GlobalRdrEnv
 mkTopLevEnv hpt modl
   = case lookupHpt hpt modl of
@@ -892,45 +873,6 @@ parseName str = withSession $ \hsc_env -> liftIO $
    do { lrdr_name <- hscParseIdentifier hsc_env str
       ; hscTcRnLookupRdrName hsc_env lrdr_name }
 
--- | Returns @True@ if passed string is a statement.
-isStmt :: ParserOpts -> String -> Bool
-isStmt pflags stmt =
-  case parseThing Parser.parseStmt pflags stmt of
-    Lexer.POk _ _ -> True
-    Lexer.PFailed _ -> False
-
--- | Returns @True@ if passed string has an import declaration.
-hasImport :: ParserOpts -> String -> Bool
-hasImport pflags stmt =
-  case parseThing Parser.parseModule pflags stmt of
-    Lexer.POk _ thing -> hasImports thing
-    Lexer.PFailed _ -> False
-  where
-    hasImports = not . null . hsmodImports . unLoc
-
--- | Returns @True@ if passed string is an import declaration.
-isImport :: ParserOpts -> String -> Bool
-isImport pflags stmt =
-  case parseThing Parser.parseImport pflags stmt of
-    Lexer.POk _ _ -> True
-    Lexer.PFailed _ -> False
-
--- | Returns @True@ if passed string is a declaration but __/not a splice/__.
-isDecl :: ParserOpts -> String -> Bool
-isDecl pflags stmt =
-  case parseThing Parser.parseDeclaration pflags stmt of
-    Lexer.POk _ thing ->
-      case unLoc thing of
-        SpliceD _ _ -> False
-        _ -> True
-    Lexer.PFailed _ -> False
-
-parseThing :: Lexer.P thing -> ParserOpts -> String -> Lexer.ParseResult thing
-parseThing parser opts stmt = do
-  let buf = stringToStringBuffer stmt
-      loc = mkRealSrcLoc (fsLit "<interactive>") 1 1
-
-  Lexer.unP parser (Lexer.initParserState opts buf loc)
 
 getDocs :: GhcMonad m
         => Name


=====================================
compiler/ghc.cabal.in
=====================================
@@ -480,6 +480,7 @@ Library
         GHC.Parser.PostProcess
         GHC.Parser.PostProcess.Haddock
         GHC.Parser.Types
+        GHC.Parser.Utils
         GHC.Platform
         GHC.Platform.ARM
         GHC.Platform.AArch64



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/690c894616a539c59cb8e58d2bba8b9c02c5ad4c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/690c894616a539c59cb8e58d2bba8b9c02c5ad4c
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/20201211/93e2991d/attachment-0001.html>


More information about the ghc-commits mailing list