module Hhp.Boot where
import GHC (Ghc)
import GHC.Utils.Monad (liftIO)
import Hhp.Browse
import Hhp.Flag
import Hhp.GHCApi
import Hhp.Lang
import Hhp.List
import Hhp.Types
bootInfo :: Options -> Cradle -> IO String
bootInfo :: Options -> Cradle -> IO String
bootInfo Options
opt Cradle
cradle = Ghc String -> IO String
forall a. Ghc a -> IO a
withGHC' (Ghc String -> IO String) -> Ghc String -> IO String
forall a b. (a -> b) -> a -> b
$ do
Options -> Cradle -> Ghc ()
initializeFlagsWithCradle Options
opt Cradle
cradle
Options -> Ghc String
boot Options
opt
boot :: Options -> Ghc String
boot :: Options -> Ghc String
boot Options
opt = do
String
mods <- Options -> Ghc String
modules Options
opt
String
langs <- IO String -> Ghc String
forall a. IO a -> Ghc a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> Ghc String) -> IO String -> Ghc String
forall a b. (a -> b) -> a -> b
$ Options -> IO String
listLanguages Options
opt
String
flags <- IO String -> Ghc String
forall a. IO a -> Ghc a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> Ghc String) -> IO String -> Ghc String
forall a b. (a -> b) -> a -> b
$ Options -> IO String
listFlags Options
opt
String
pre <- [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String) -> Ghc [String] -> Ghc String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Ghc String) -> [String] -> Ghc [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Options -> String -> Ghc String
browse Options
opt) [String]
preBrowsedModules
String -> Ghc String
forall a. a -> Ghc a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Ghc String) -> String -> Ghc String
forall a b. (a -> b) -> a -> b
$ String
mods String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
langs String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
flags String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
pre
preBrowsedModules :: [String]
preBrowsedModules :: [String]
preBrowsedModules =
[ String
"Prelude"
, String
"Control.Applicative"
, String
"Control.Exception"
, String
"Control.Monad"
, String
"Data.Char"
, String
"Data.List"
, String
"Data.Maybe"
, String
"System.IO"
]