/src/Language/PureScript/Ide/Rebuild.hs

https://github.com/purerl/purescript · Haskell · 199 lines · 143 code · 19 blank · 37 comment · 6 complexity · a9810daa364018b404b3ff4ce9a6dc67 MD5 · raw file

  1. {-# LANGUAGE PackageImports #-}
  2. {-# LANGUAGE TemplateHaskell #-}
  3. module Language.PureScript.Ide.Rebuild
  4. ( rebuildFileSync
  5. , rebuildFileAsync
  6. , rebuildFile
  7. ) where
  8. import Protolude
  9. import "monad-logger" Control.Monad.Logger
  10. import qualified Data.List as List
  11. import qualified Data.Map.Lazy as M
  12. import Data.Maybe (fromJust)
  13. import qualified Data.Set as S
  14. import qualified Language.PureScript as P
  15. import qualified Language.PureScript.CST as CST
  16. import Language.PureScript.Ide.Error
  17. import Language.PureScript.Ide.Logging
  18. import Language.PureScript.Ide.State
  19. import Language.PureScript.Ide.Types
  20. import Language.PureScript.Ide.Util
  21. -- | Given a filepath performs the following steps:
  22. --
  23. -- * Reads and parses a PureScript module from the filepath.
  24. --
  25. -- * Builds a dependency graph for the parsed module from the already loaded
  26. -- ExternsFiles.
  27. --
  28. -- * Attempts to find an FFI definition file for the module by looking
  29. -- for a file with the same filepath except for a .js extension.
  30. --
  31. -- * Passes all the created artifacts to @rebuildModule@.
  32. --
  33. -- * If the rebuilding succeeds, returns a @RebuildSuccess@ with the generated
  34. -- warnings, and if rebuilding fails, returns a @RebuildError@ with the
  35. -- generated errors.
  36. rebuildFile
  37. :: (Ide m, MonadLogger m, MonadError IdeError m)
  38. => FilePath
  39. -- ^ The file to rebuild
  40. -> Maybe FilePath
  41. -- ^ The file to use as the location for parsing and errors
  42. -> Set P.CodegenTarget
  43. -- ^ The targets to codegen
  44. -> (ReaderT IdeEnvironment (LoggingT IO) () -> m ())
  45. -- ^ A runner for the second build with open exports
  46. -> m Success
  47. rebuildFile file actualFile codegenTargets runOpenBuild = do
  48. (fp, input) <- ideReadFile file
  49. let fp' = fromMaybe fp actualFile
  50. m <- case CST.parseFromFile fp' input of
  51. Left parseError ->
  52. throwError $ RebuildError $ CST.toMultipleErrors fp' parseError
  53. Right m -> pure m
  54. -- Externs files must be sorted ahead of time, so that they get applied
  55. -- in the right order (bottom up) to the 'Environment'.
  56. externs <- logPerf (labelTimespec "Sorting externs") (sortExterns m =<< getExternFiles)
  57. outputDirectory <- confOutputPath . ideConfiguration <$> ask
  58. -- For rebuilding, we want to 'RebuildAlways', but for inferring foreign
  59. -- modules using their file paths, we need to specify the path in the 'Map'.
  60. let filePathMap = M.singleton (P.getModuleName m) (Left P.RebuildAlways)
  61. foreigns <- P.inferForeignModules codegenTargets (M.singleton (P.getModuleName m) (Right file))
  62. let makeEnv = MakeActionsEnv outputDirectory filePathMap foreigns False
  63. -- Rebuild the single module using the cached externs
  64. (result, warnings) <- logPerf (labelTimespec "Rebuilding Module") $
  65. liftIO
  66. . P.runMake (P.defaultOptions { P.optionsCodegenTargets = codegenTargets })
  67. . P.rebuildModule (buildMakeActions
  68. >>= shushProgress $ makeEnv) externs $ m
  69. case result of
  70. Left errors -> throwError (RebuildError errors)
  71. Right newExterns -> do
  72. whenM isEditorMode $ do
  73. insertModule (fromMaybe file actualFile, m)
  74. insertExterns newExterns
  75. void populateVolatileState
  76. runOpenBuild (rebuildModuleOpen makeEnv externs m)
  77. pure (RebuildSuccess warnings)
  78. isEditorMode :: Ide m => m Bool
  79. isEditorMode = asks (confEditorMode . ideConfiguration)
  80. rebuildFileAsync
  81. :: forall m. (Ide m, MonadLogger m, MonadError IdeError m)
  82. => FilePath -> Maybe FilePath -> Set P.CodegenTarget -> m Success
  83. rebuildFileAsync fp fp' ts = rebuildFile fp fp' ts asyncRun
  84. where
  85. asyncRun :: ReaderT IdeEnvironment (LoggingT IO) () -> m ()
  86. asyncRun action = do
  87. env <- ask
  88. let ll = confLogLevel (ideConfiguration env)
  89. void (liftIO (async (runLogger ll (runReaderT action env))))
  90. rebuildFileSync
  91. :: forall m. (Ide m, MonadLogger m, MonadError IdeError m)
  92. => FilePath -> Maybe FilePath -> Set P.CodegenTarget -> m Success
  93. rebuildFileSync fp fp' ts = rebuildFile fp fp' ts syncRun
  94. where
  95. syncRun :: ReaderT IdeEnvironment (LoggingT IO) () -> m ()
  96. syncRun action = do
  97. env <- ask
  98. let ll = confLogLevel (ideConfiguration env)
  99. void (liftIO (runLogger ll (runReaderT action env)))
  100. -- | Rebuilds a module but opens up its export list first and stores the result
  101. -- inside the rebuild cache
  102. rebuildModuleOpen
  103. :: (Ide m, MonadLogger m)
  104. => MakeActionsEnv
  105. -> [P.ExternsFile]
  106. -> P.Module
  107. -> m ()
  108. rebuildModuleOpen makeEnv externs m = void $ runExceptT $ do
  109. (openResult, _) <- liftIO
  110. . P.runMake P.defaultOptions
  111. . P.rebuildModule (buildMakeActions
  112. >>= shushProgress
  113. >>= shushCodegen
  114. $ makeEnv) externs $ openModuleExports m
  115. case openResult of
  116. Left _ ->
  117. throwError (GeneralError "Failed when rebuilding with open exports")
  118. Right result -> do
  119. $(logDebug)
  120. ("Setting Rebuild cache: " <> P.runModuleName (P.efModuleName result))
  121. cacheRebuild result
  122. -- | Parameters we can access while building our @MakeActions@
  123. data MakeActionsEnv =
  124. MakeActionsEnv
  125. { maeOutputDirectory :: FilePath
  126. , maeFilePathMap :: ModuleMap (Either P.RebuildPolicy FilePath)
  127. , maeForeignPathMap :: ModuleMap FilePath
  128. , maePrefixComment :: Bool
  129. }
  130. -- | Builds the default @MakeActions@ from a @MakeActionsEnv@
  131. buildMakeActions :: MakeActionsEnv -> P.MakeActions P.Make
  132. buildMakeActions MakeActionsEnv{..} =
  133. P.buildMakeActions
  134. maeOutputDirectory
  135. maeFilePathMap
  136. maeForeignPathMap
  137. maePrefixComment
  138. -- | Shuts the compiler up about progress messages
  139. shushProgress :: P.MakeActions P.Make -> MakeActionsEnv -> P.MakeActions P.Make
  140. shushProgress ma _ =
  141. ma { P.progress = \_ -> pure () }
  142. -- | Stops any kind of codegen
  143. shushCodegen :: P.MakeActions P.Make -> MakeActionsEnv -> P.MakeActions P.Make
  144. shushCodegen ma MakeActionsEnv{..} =
  145. ma { P.codegen = \_ _ _ _ _ -> pure ()
  146. , P.ffiCodegen = \_ -> pure ()
  147. }
  148. -- | Returns a topologically sorted list of dependent ExternsFiles for the given
  149. -- module. Throws an error if there is a cyclic dependency within the
  150. -- ExternsFiles
  151. sortExterns
  152. :: (Ide m, MonadError IdeError m)
  153. => P.Module
  154. -> ModuleMap P.ExternsFile
  155. -> m [P.ExternsFile]
  156. sortExterns m ex = do
  157. sorted' <- runExceptT
  158. . P.sortModules P.moduleSignature
  159. . (:) m
  160. . map mkShallowModule
  161. . M.elems
  162. . M.delete (P.getModuleName m) $ ex
  163. case sorted' of
  164. Left err ->
  165. throwError (RebuildError err)
  166. Right (sorted, graph) -> do
  167. let deps = fromJust (List.lookup (P.getModuleName m) graph)
  168. pure $ mapMaybe getExtern (deps `inOrderOf` map P.getModuleName sorted)
  169. where
  170. mkShallowModule P.ExternsFile{..} =
  171. P.Module (P.internalModuleSourceSpan "<rebuild>") [] efModuleName (map mkImport efImports) Nothing
  172. mkImport (P.ExternsImport mn it iq) =
  173. P.ImportDeclaration (P.internalModuleSourceSpan "<rebuild>", []) mn it iq
  174. getExtern mn = M.lookup mn ex
  175. -- Sort a list so its elements appear in the same order as in another list.
  176. inOrderOf :: (Ord a) => [a] -> [a] -> [a]
  177. inOrderOf xs ys = let s = S.fromList xs in filter (`S.member` s) ys
  178. -- | Removes a modules export list.
  179. openModuleExports :: P.Module -> P.Module
  180. openModuleExports (P.Module ss cs mn decls _) = P.Module ss cs mn decls Nothing