{-# LANGUAGE LambdaCase #-}
module HIE.Bios.Internal.Debug (debugInfo, rootInfo, configInfo, cradleInfo) where
import Control.Monad
import Colog.Core (LogAction (..), WithSeverity (..))
import Data.Void
import qualified Data.Char as Char
import HIE.Bios.Cradle
import HIE.Bios.Environment
import HIE.Bios.Types
import HIE.Bios.Flags
import System.Directory
debugInfo :: Show a
=> FilePath
-> Cradle a
-> IO String
debugInfo :: forall a. Show a => FilePath -> Cradle a -> IO FilePath
debugInfo FilePath
fp Cradle a
cradle = [FilePath] -> FilePath
unlines ([FilePath] -> FilePath) -> IO [FilePath] -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
let logger :: LogAction IO (WithSeverity Log)
logger = Cradle a -> LogAction IO (WithSeverity Log)
forall a. Cradle a -> LogAction IO (WithSeverity Log)
cradleLogger Cradle a
cradle
CradleLoadResult ComponentOptions
res <- FilePath
-> LoadStyle -> Cradle a -> IO (CradleLoadResult ComponentOptions)
forall a.
FilePath
-> LoadStyle -> Cradle a -> IO (CradleLoadResult ComponentOptions)
getCompilerOptions FilePath
fp LoadStyle
LoadFile Cradle a
cradle
FilePath
canonFp <- FilePath -> IO FilePath
canonicalizePath FilePath
fp
FilePath
conf <- FilePath -> IO FilePath
findConfig FilePath
canonFp
FilePath
crdl <- LogAction IO (WithSeverity Log) -> FilePath -> IO FilePath
findCradle' LogAction IO (WithSeverity Log)
logger FilePath
canonFp
CradleLoadResult FilePath
ghcLibDir <- Cradle a -> IO (CradleLoadResult FilePath)
forall a. Cradle a -> IO (CradleLoadResult FilePath)
getRuntimeGhcLibDir Cradle a
cradle
CradleLoadResult FilePath
ghcVer <- Cradle a -> IO (CradleLoadResult FilePath)
forall a. Cradle a -> IO (CradleLoadResult FilePath)
getRuntimeGhcVersion Cradle a
cradle
case CradleLoadResult ComponentOptions
res of
CradleSuccess (ComponentOptions [FilePath]
gopts FilePath
croot [FilePath]
deps) -> do
[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
"Component directory: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
croot
, FilePath
"GHC options: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
unwords ((FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> FilePath
quoteIfNeeded [FilePath]
gopts)
, FilePath
"GHC library directory: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ CradleLoadResult FilePath -> FilePath
forall a. Show a => a -> FilePath
show CradleLoadResult FilePath
ghcLibDir
, FilePath
"GHC version: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ CradleLoadResult FilePath -> FilePath
forall a. Show a => a -> FilePath
show CradleLoadResult FilePath
ghcVer
, FilePath
"Config Location: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
conf
, FilePath
"Cradle: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
crdl
, FilePath
"Dependencies: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
unwords [FilePath]
deps
]
CradleFail (CradleError [FilePath]
deps ExitCode
ext [FilePath]
stderr) ->
[FilePath] -> IO [FilePath]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [FilePath
"Cradle failed to load"
, FilePath
"Deps: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
forall a. Show a => a -> FilePath
show [FilePath]
deps
, FilePath
"Exit Code: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ ExitCode -> FilePath
forall a. Show a => a -> FilePath
show ExitCode
ext
, FilePath
"Stderr: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
unlines [FilePath]
stderr]
CradleLoadResult ComponentOptions
CradleNone ->
[FilePath] -> IO [FilePath]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [FilePath
"No cradle"]
where
rootDir :: FilePath
rootDir = Cradle a -> FilePath
forall a. Cradle a -> FilePath
cradleRootDir Cradle a
cradle
quoteIfNeeded :: FilePath -> FilePath
quoteIfNeeded FilePath
option
| (Char -> Bool) -> FilePath -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
Char.isSpace FilePath
option = FilePath
"\"" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
option FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\""
| Bool
otherwise = FilePath
option
rootInfo :: Cradle a
-> IO String
rootInfo :: forall a. Cradle a -> IO FilePath
rootInfo Cradle a
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
$ Cradle a -> FilePath
forall a. Cradle a -> FilePath
cradleRootDir Cradle a
cradle
configInfo :: [FilePath] -> IO String
configInfo :: [FilePath] -> IO FilePath
configInfo [] = FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
"No files given"
configInfo [FilePath]
args =
([FilePath] -> FilePath) -> IO [FilePath] -> IO FilePath
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [FilePath] -> FilePath
unlines (IO [FilePath] -> IO FilePath) -> IO [FilePath] -> IO FilePath
forall a b. (a -> b) -> a -> b
$ [FilePath] -> (FilePath -> IO FilePath) -> IO [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [FilePath]
args ((FilePath -> IO FilePath) -> IO [FilePath])
-> (FilePath -> IO FilePath) -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ \FilePath
fp -> do
FilePath
fp' <- FilePath -> IO FilePath
canonicalizePath FilePath
fp
((FilePath
"Config for \"" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
fp' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\": ") FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++) (FilePath -> FilePath) -> IO FilePath -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO FilePath
findConfig FilePath
fp'
findConfig :: FilePath -> IO String
findConfig :: FilePath -> IO FilePath
findConfig FilePath
fp = FilePath -> IO (Maybe FilePath)
findCradle FilePath
fp IO (Maybe FilePath)
-> (Maybe FilePath -> IO FilePath) -> IO FilePath
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Just FilePath
yaml -> FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
yaml
Maybe FilePath
_ -> FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
"No explicit config found"
cradleInfo :: LogAction IO (WithSeverity Log) -> [FilePath] -> IO String
cradleInfo :: LogAction IO (WithSeverity Log) -> [FilePath] -> IO FilePath
cradleInfo LogAction IO (WithSeverity Log)
_ [] = FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
"No files given"
cradleInfo LogAction IO (WithSeverity Log)
l [FilePath]
args =
([FilePath] -> FilePath) -> IO [FilePath] -> IO FilePath
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [FilePath] -> FilePath
unlines (IO [FilePath] -> IO FilePath) -> IO [FilePath] -> IO FilePath
forall a b. (a -> b) -> a -> b
$ [FilePath] -> (FilePath -> IO FilePath) -> IO [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [FilePath]
args ((FilePath -> IO FilePath) -> IO [FilePath])
-> (FilePath -> IO FilePath) -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ \FilePath
fp -> do
FilePath
fp' <- FilePath -> IO FilePath
canonicalizePath FilePath
fp
((FilePath
"Cradle for \"" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
fp' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\": ") FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++) (FilePath -> FilePath) -> IO FilePath -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LogAction IO (WithSeverity Log) -> FilePath -> IO FilePath
findCradle' LogAction IO (WithSeverity Log)
l FilePath
fp'
findCradle' :: LogAction IO (WithSeverity Log) -> FilePath -> IO String
findCradle' :: LogAction IO (WithSeverity Log) -> FilePath -> IO FilePath
findCradle' LogAction IO (WithSeverity Log)
l FilePath
fp =
FilePath -> IO (Maybe FilePath)
findCradle FilePath
fp IO (Maybe FilePath)
-> (Maybe FilePath -> IO FilePath) -> IO FilePath
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Just FilePath
yaml -> do
Cradle Void
crdl <- LogAction IO (WithSeverity Log) -> FilePath -> IO (Cradle Void)
loadCradle LogAction IO (WithSeverity Log)
l FilePath
yaml
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
$ Cradle Void -> FilePath
forall a. Show a => a -> FilePath
show Cradle Void
crdl
Maybe FilePath
Nothing -> do
Cradle Void
crdl <- LogAction IO (WithSeverity Log) -> FilePath -> IO (Cradle Void)
forall a.
Show a =>
LogAction IO (WithSeverity Log) -> FilePath -> IO (Cradle a)
loadImplicitCradle LogAction IO (WithSeverity Log)
l FilePath
fp :: IO (Cradle Void)
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
$ Cradle Void -> FilePath
forall a. Show a => a -> FilePath
show Cradle Void
crdl