module Hhp.Debug (debugInfo, rootInfo) where
import GHC.Utils.Monad (liftIO)
import Control.Applicative ((<|>))
import Data.List (intercalate)
import Data.Maybe (fromJust, fromMaybe, isJust)
import Hhp.CabalApi
import Hhp.GHCApi
import Hhp.Types
debugInfo
:: Options
-> Cradle
-> IO String
debugInfo :: Options -> Cradle -> IO FilePath
debugInfo Options
opt Cradle
cradle =
Options -> [FilePath] -> FilePath
forall a. ToString a => Options -> a -> FilePath
convert Options
opt ([FilePath] -> FilePath) -> IO [FilePath] -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
CompilerOptions [FilePath]
gopts [FilePath]
incDir [Package]
pkgs <-
if Bool
cabal
then IO CompilerOptions -> IO CompilerOptions
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CompilerOptions
fromCabalFile IO CompilerOptions -> IO CompilerOptions -> IO CompilerOptions
forall a. IO a -> IO a -> IO a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> CompilerOptions -> IO CompilerOptions
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CompilerOptions
simpleCompilerOption)
else CompilerOptions -> IO CompilerOptions
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CompilerOptions
simpleCompilerOption
Maybe FilePath
mglibdir <- IO (Maybe FilePath) -> IO (Maybe FilePath)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO (Maybe FilePath)
getSystemLibDir
[FilePath] -> IO [FilePath]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
[ FilePath
"Root directory: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
rootDir
, FilePath
"Current directory: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
currentDir
, FilePath
"Cabal file: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
cabalFile
, FilePath
"GHC options: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
unwords [FilePath]
gopts
, FilePath
"Include directories: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
unwords [FilePath]
incDir
, FilePath
"Dependent packages: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate FilePath
", " ((Package -> FilePath) -> [Package] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Package -> FilePath
showPkg [Package]
pkgs)
, FilePath
"System libraries: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
"" Maybe FilePath
mglibdir
]
where
currentDir :: FilePath
currentDir = Cradle -> FilePath
cradleCurrentDir Cradle
cradle
mCabalFile :: Maybe FilePath
mCabalFile = Cradle -> Maybe FilePath
cradleCabalFile Cradle
cradle
rootDir :: FilePath
rootDir = Cradle -> FilePath
cradleRootDir Cradle
cradle
cabal :: Bool
cabal = Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust Maybe FilePath
mCabalFile
cabalFile :: FilePath
cabalFile = FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
"" Maybe FilePath
mCabalFile
origGopts :: [FilePath]
origGopts = Options -> [FilePath]
ghcOpts Options
opt
simpleCompilerOption :: CompilerOptions
simpleCompilerOption = [FilePath] -> [FilePath] -> [Package] -> CompilerOptions
CompilerOptions [FilePath]
origGopts [] []
fromCabalFile :: IO CompilerOptions
fromCabalFile = do
PackageDescription
pkgDesc <- FilePath -> IO PackageDescription
parseCabalFile FilePath
file
[FilePath] -> Cradle -> PackageDescription -> IO CompilerOptions
getCompilerOptions [FilePath]
origGopts Cradle
cradle PackageDescription
pkgDesc
where
file :: FilePath
file = Maybe FilePath -> FilePath
forall a. HasCallStack => Maybe a -> a
fromJust Maybe FilePath
mCabalFile
rootInfo
:: Options
-> Cradle
-> IO String
rootInfo :: Options -> Cradle -> IO FilePath
rootInfo Options
opt Cradle
cradle = FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> IO FilePath) -> FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ Options -> FilePath -> FilePath
forall a. ToString a => Options -> a -> FilePath
convert Options
opt (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ Cradle -> FilePath
cradleRootDir Cradle
cradle