@@ -399,7 +399,7 @@ runGhci GhciOpts{..} targets mainIsTargets pkgs extraFiles exposePackages = do
399
399
scriptPath <- writeGhciScript tmpDirectory (renderScript isIntero pkgs mainFile ghciOnlyMain extraFiles)
400
400
execGhci (macrosOptions ++ [" -ghci-script=" <> toFilePath scriptPath])
401
401
402
- writeMacrosFile :: ( MonadIO m ) => Path Abs Dir -> [GhciPkgInfo ] -> m [String ]
402
+ writeMacrosFile :: HasRunner env => Path Abs Dir -> [GhciPkgInfo ] -> RIO env [String ]
403
403
writeMacrosFile tmpDirectory packages = do
404
404
preprocessCabalMacros packages macrosFile
405
405
where
@@ -808,12 +808,21 @@ getExtraLoadDeps loadAllDeps sourceMap targets =
808
808
(_, Just PSIndex {}) -> return loadAllDeps
809
809
(_, _) -> return False
810
810
811
- preprocessCabalMacros :: MonadIO m => [GhciPkgInfo ] -> Path Abs File -> m [String ]
812
- preprocessCabalMacros pkgs out = liftIO $ do
813
- let fps = nubOrd (concatMap (mapMaybe (bioCabalMacros . snd ) . ghciPkgOpts) pkgs)
814
- files <- mapM (S8. readFile . toFilePath) fps
811
+ preprocessCabalMacros :: HasRunner env => [GhciPkgInfo ] -> Path Abs File -> RIO env [String ]
812
+ preprocessCabalMacros pkgs out = do
813
+ fps <- fmap (nubOrd . catMaybes . concat ) $
814
+ forM pkgs $ \ pkg -> forM (ghciPkgOpts pkg) $ \ (_, bio) -> do
815
+ let cabalMacros = bioCabalMacros bio
816
+ exists <- liftIO $ doesFileExist cabalMacros
817
+ if exists
818
+ then return $ Just cabalMacros
819
+ else do
820
+ prettyWarnL [" Didn't find expected autogen file:" , display cabalMacros]
821
+ return Nothing
822
+ files <- liftIO $ mapM (S8. readFile . toFilePath) fps
815
823
if null files then return [] else do
816
- S8. writeFile (toFilePath out) $ S8. concat $ map (<> " \n #undef CURRENT_PACKAGE_KEY\n #undef CURRENT_COMPONENT_ID\n " ) files
824
+ liftIO $ S8. writeFile (toFilePath out) $ S8. concat $
825
+ map (<> " \n #undef CURRENT_PACKAGE_KEY\n #undef CURRENT_COMPONENT_ID\n " ) files
817
826
return [" -optP-include" , " -optP" <> toFilePath out]
818
827
819
828
setScriptPerms :: MonadIO m => FilePath -> m ()
@@ -846,50 +855,6 @@ hasLocalComp p t =
846
855
TargetAll ProjectPackage -> True
847
856
_ -> False
848
857
849
-
850
- {- Copied from Stack.Ide, may be useful in the future
851
-
852
- -- | Get options and target files for the given package info.
853
- getPackageOptsAndTargetFiles
854
- :: (MonadThrow m, MonadIO m, MonadReader env m, HasEnvConfig env)
855
- => Path Abs Dir -> GhciPkgInfo -> m ([FilePath], [FilePath])
856
- getPackageOptsAndTargetFiles pwd pkg = do
857
- dist <- distDirFromDir (ghciPkgDir pkg)
858
- let autogen = autogenDir dist
859
- paths_foo <-
860
- liftM
861
- (autogen </>)
862
- (parseRelFile
863
- ("Paths_" ++ packageNameString (ghciPkgName pkg) ++ ".hs"))
864
- paths_foo_exists <- doesFileExist paths_foo
865
- let ghcOptions bio =
866
- bioOneWordOpts bio ++
867
- bioOpts bio ++
868
- bioPackageFlags bio ++
869
- maybe [] (\cabalMacros -> ["-optP-include", "-optP" <> toFilePath cabalMacros]) (bioCabalMacros bio)
870
- return
871
- ( ("--dist-dir=" <> toFilePathNoTrailingSep dist) :
872
- -- FIXME: use compilerOptionsCabalFlag
873
- map ("--ghc-option=" ++) (concatMap (ghcOptions . snd) (ghciPkgOpts pkg))
874
- , mapMaybe
875
- (fmap toFilePath . stripProperPrefix pwd)
876
- (S.toList (ghciPkgCFiles pkg) <> S.toList (ghciPkgModFiles pkg) <>
877
- [paths_foo | paths_foo_exists]))
878
-
879
- -- | List load targets for a package target.
880
- targetsCmd :: Text -> GlobalOpts -> IO ()
881
- targetsCmd target go@GlobalOpts{..} =
882
- withBuildConfig go $
883
- do let boptsCli = defaultBuildOptsCLI { boptsCLITargets = [target] }
884
- (_realTargets,_,pkgs) <- ghciSetup (ideGhciOpts boptsCli)
885
- pwd <- getCurrentDir
886
- targets <-
887
- fmap
888
- (concat . snd . unzip)
889
- (mapM (getPackageOptsAndTargetFiles pwd) pkgs)
890
- forM_ targets (liftIO . putStrLn)
891
- -}
892
-
893
858
-- | Run a command and grab the first line of stdout, dropping
894
859
-- stderr's contexts completely.
895
860
runGrabFirstLine :: (HasProcessContext env , HasLogFunc env ) => String -> [String ] -> RIO env String
0 commit comments