module Hhp.List (listModules, modules) where
import DynFlags (DynFlags)
import GHC (Ghc)
import qualified GHC as G
import Module (moduleNameString, moduleName)
import Packages (lookupModuleInAllPackages, listVisibleModuleNames)
import Control.Exception (SomeException(..))
import Data.List (nub, sort)
import Hhp.GHCApi
import Hhp.Types
listModules :: Options -> Cradle -> IO String
listModules :: Options -> Cradle -> IO String
listModules 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
modules Options
opt
modules :: Options -> Ghc String
modules :: Options -> Ghc String
modules Options
opt = Options -> [String] -> String
forall a. ToString a => Options -> a -> String
convert Options
opt ([String] -> String)
-> ([Module] -> [String]) -> [Module] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Module] -> [String]
arrange ([Module] -> String) -> Ghc [Module] -> Ghc String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ghc [Module]
getModules Ghc [Module] -> (SomeException -> Ghc [Module]) -> Ghc [Module]
forall (m :: * -> *) e a.
(ExceptionMonad m, Exception e) =>
m a -> (e -> m a) -> m a
`G.gcatch` SomeException -> Ghc [Module]
forall (m :: * -> *) a. Monad m => SomeException -> m [a]
handler)
where
getModules :: Ghc [Module]
getModules = DynFlags -> [Module]
listVisibleModules (DynFlags -> [Module]) -> Ghc DynFlags -> Ghc [Module]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ghc DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
G.getSessionDynFlags
arrange :: [Module] -> [String]
arrange = [String] -> [String]
forall a. Eq a => [a] -> [a]
nub ([String] -> [String])
-> ([Module] -> [String]) -> [Module] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
forall a. Ord a => [a] -> [a]
sort ([String] -> [String])
-> ([Module] -> [String]) -> [Module] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Module -> String) -> [Module] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (ModuleName -> String
moduleNameString (ModuleName -> String)
-> (Module -> ModuleName) -> Module -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module -> ModuleName
moduleName)
handler :: SomeException -> m [a]
handler (SomeException e
_) = [a] -> m [a]
forall (m :: * -> *) a. Monad m => a -> m a
return []
listVisibleModules :: DynFlags -> [G.Module]
listVisibleModules :: DynFlags -> [Module]
listVisibleModules DynFlags
df = [Module]
mods
where
modNames :: [ModuleName]
modNames = DynFlags -> [ModuleName]
listVisibleModuleNames DynFlags
df
mods :: [Module]
mods = [ Module
m | ModuleName
mn <- [ModuleName]
modNames, (Module
m, PackageConfig
_) <- DynFlags -> ModuleName -> [(Module, PackageConfig)]
lookupModuleInAllPackages DynFlags
df ModuleName
mn ]