Hassan Al-Awwadi pushed to branch wip/haanss/depdir at Glasgow Haskell Compiler / GHC

Commits:

5 changed files:

Changes:

  • compiler/GHC/Tc/Gen/Splice.hs
    ... ... @@ -1528,13 +1528,6 @@ instance TH.Quasi TcM where
    1528 1528
         ref <- fmap tcg_dependent_dirs getGblEnv
    
    1529 1529
         dep_dirs <- readTcRef ref
    
    1530 1530
         writeTcRef ref (dp:dep_dirs)
    
    1531
    -    -- listDirectory does not return an absolute path, so
    
    1532
    -    -- we need to prepend the directory path to make the
    
    1533
    -    -- the contents absolute.
    
    1534
    -    contents <- liftIO $ listDirectory dp
    
    1535
    -    let path_prefix = dp ++ "\\"
    
    1536
    -    let abs_contents = map (path_prefix ++) contents
    
    1537
    -    return abs_contents
    
    1538 1531
     
    
    1539 1532
       qAddTempFile suffix = do
    
    1540 1533
         dflags <- getDynFlags
    

  • libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
    ... ... @@ -136,7 +136,7 @@ class (MonadIO m, MonadFail m) => Quasi m where
    136 136
       qAddDependentFile :: FilePath -> m ()
    
    137 137
     
    
    138 138
       -- | See 'addDependentDirectory'.
    
    139
    -  qAddDependentDirectory :: FilePath -> m [FilePath]
    
    139
    +  qAddDependentDirectory :: FilePath -> m ()
    
    140 140
     
    
    141 141
       -- | See 'addTempFile'.
    
    142 142
       qAddTempFile :: String -> m FilePath
    
    ... ... @@ -839,23 +839,9 @@ getPackageRoot = Q qGetPackageRoot
    839 839
     --   * The dependency is shallow, just a hash of its direct contents. It returns
    
    840 840
     --     a list of the contents (absolute paths), files and subdirectories both, so
    
    841 841
     --     you can manually depend on (a subset of) those, if you wish.
    
    842
    -addDependentDirectory :: FilePath -> Q [FilePath]
    
    842
    +addDependentDirectory :: FilePath -> Q ()
    
    843 843
     addDependentDirectory dp = Q (qAddDependentDirectory dp)
    
    844 844
     
    
    845
    --- | Record external directories that runIO is using (dependent upon).
    
    846
    --- The compiler can then recognize that it should re-compile the Haskell file
    
    847
    --- when a directory changes.
    
    848
    ---
    
    849
    --- Expects an absolute directory path.
    
    850
    ---
    
    851
    --- Notes:
    
    852
    ---
    
    853
    ---   * ghc -M does not know about these dependencies - it does not execute TH.
    
    854
    ---
    
    855
    ---   * The dependency is shallow, just a hash of its direct contents.
    
    856
    ---     See 'addDependentDirectory' for a version that returns the contents.
    
    857
    -addDependentDirectory_ :: FilePath -> Q ()
    
    858
    -addDependentDirectory_ dp = addDependentDirectory dp >> pure ()
    
    859 845
     
    
    860 846
     -- | Record external files that runIO is using (dependent upon).
    
    861 847
     -- The compiler can then recognize that it should re-compile the Haskell file
    

  • libraries/ghci/GHCi/Message.hs
    ... ... @@ -291,7 +291,7 @@ data THMessage a where
    291 291
     
    
    292 292
       GetPackageRoot :: THMessage (THResult FilePath)
    
    293 293
       AddDependentFile :: FilePath -> THMessage (THResult ())
    
    294
    -  AddDependentDirectory :: FilePath -> THMessage (THResult [FilePath])
    
    294
    +  AddDependentDirectory :: FilePath -> THMessage (THResult ())
    
    295 295
       AddTempFile :: String -> THMessage (THResult FilePath)
    
    296 296
       AddModFinalizer :: RemoteRef (TH.Q ()) -> THMessage (THResult ())
    
    297 297
       AddCorePlugin :: String -> THMessage (THResult ())
    

  • libraries/template-haskell/Language/Haskell/TH/Syntax.hs
    ... ... @@ -33,7 +33,6 @@ module Language.Haskell.TH.Syntax (
    33 33
         addCorePlugin,
    
    34 34
         addDependentFile,
    
    35 35
         addDependentDirectory,
    
    36
    -    addDependentDirectory_,
    
    37 36
         addForeignFile,
    
    38 37
         addForeignFilePath,
    
    39 38
         addForeignSource,
    

  • testsuite/tests/interface-stability/template-haskell-exports.stdout
    ... ... @@ -1715,7 +1715,7 @@ module Language.Haskell.TH.Syntax where
    1715 1715
         qRunIO :: forall a. GHC.Internal.Types.IO a -> m a
    
    1716 1716
         qGetPackageRoot :: m GHC.Internal.IO.FilePath
    
    1717 1717
         qAddDependentFile :: GHC.Internal.IO.FilePath -> m ()
    
    1718
    -    qAddDependentDirectory :: GHC.Internal.IO.FilePath -> m [GHC.Internal.IO.FilePath]
    
    1718
    +    qAddDependentDirectory :: GHC.Internal.IO.FilePath -> m ()
    
    1719 1719
         qAddTempFile :: GHC.Internal.Base.String -> m GHC.Internal.IO.FilePath
    
    1720 1720
         qAddTopDecls :: [Dec] -> m ()
    
    1721 1721
         qAddForeignFilePath :: ForeignSrcLang -> GHC.Internal.Base.String -> m ()
    
    ... ... @@ -1780,8 +1780,7 @@ module Language.Haskell.TH.Syntax where
    1780 1780
       type VarStrictType :: *
    
    1781 1781
       type VarStrictType = VarBangType
    
    1782 1782
       addCorePlugin :: GHC.Internal.Base.String -> Q ()
    
    1783
    -  addDependentDirectory :: GHC.Internal.IO.FilePath -> Q [GHC.Internal.IO.FilePath]
    
    1784
    -  addDependentDirectory_ :: GHC.Internal.IO.FilePath -> Q ()
    
    1783
    +  addDependentDirectory :: GHC.Internal.IO.FilePath -> Q ()
    
    1785 1784
       addDependentFile :: GHC.Internal.IO.FilePath -> Q ()
    
    1786 1785
       addForeignFile :: ForeignSrcLang -> GHC.Internal.Base.String -> Q ()
    
    1787 1786
       addForeignFilePath :: ForeignSrcLang -> GHC.Internal.IO.FilePath -> Q ()