[Git][ghc/ghc][wip/js-staging] Minor refactoring

Sylvain Henry (@hsyl20) gitlab at gitlab.haskell.org
Tue Sep 27 14:35:36 UTC 2022



Sylvain Henry pushed to branch wip/js-staging at Glasgow Haskell Compiler / GHC


Commits:
a86cc1d4 by Sylvain Henry at 2022-09-27T15:13:31+02:00
Minor refactoring

- - - - -


1 changed file:

- compiler/GHC/Driver/Pipeline/Execute.hs


Changes:

=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -4,6 +4,7 @@
 {-# LANGUAGE NamedFieldPuns #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE GADTs #-}
+{-# LANGUAGE LambdaCase #-}
 {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
 #include <ghcplatform.h>
 
@@ -355,34 +356,38 @@ runJsPhase pipe_env hsc_env input_fn = do
         let unit_env   = hsc_unit_env hsc_env
 
         output_fn <- phaseOutputFilenameNew StopLn pipe_env hsc_env Nothing
-        need_cpp <- jsFileNeedsCpp input_fn
-        tmp_fn <- newTempName logger tmpfs (tmpDir dflags) TFL_CurrentModule "js"
-
-        -- the header lets the linker recognize processed JavaScript files
-        -- But don't add JavaScript header to object files!
-        is_js_obj <- isJsObjectFile input_fn
-        let header
-              | is_js_obj = ""
-              | otherwise = "//JavaScript\n"
 
         -- if the input filename is the same as the output, then we've probably
         -- generated the object ourselves, we leave the file alone
         when (input_fn /= output_fn) $ do
-          if need_cpp
-          then do
-            doCpp logger
-                    tmpfs
-                    dflags
-                    unit_env
-                    (CppOpts
-                        { cppUseCc = True
-                        , cppLinePragmas = False
-                        })
-                    []
-                    input_fn
-                    tmp_fn
-            copyWithHeader header tmp_fn output_fn
-          else copyWithHeader header input_fn output_fn
+
+          -- the header lets the linker recognize processed JavaScript files
+          -- But don't add JavaScript header to object files!
+          is_js_obj <- isJsObjectFile input_fn
+
+          if is_js_obj
+            then copyWithHeader "" input_fn output_fn
+            else do
+              -- header appended to JS files stored as .o to recognize them.
+              let header = "//JavaScript\n"
+              jsFileNeedsCpp input_fn >>= \case
+                False -> copyWithHeader header input_fn output_fn
+                True  -> do
+                  -- run CPP on the input JS file
+                  tmp_fn <- newTempName logger tmpfs (tmpDir dflags) TFL_CurrentModule "js"
+                  doCpp logger
+                          tmpfs
+                          dflags
+                          unit_env
+                          (CppOpts
+                              { cppUseCc = True
+                              , cppLinePragmas = False
+                              })
+                          []
+                          input_fn
+                          tmp_fn
+                  copyWithHeader header tmp_fn output_fn
+
         return output_fn
 
 jsFileNeedsCpp :: FilePath -> IO Bool



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a86cc1d4cc7bedf8650e8ddcad536d834655be7a
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/20220927/f4bfd47c/attachment-0001.html>


More information about the ghc-commits mailing list