module Hhp.Check (
checkSyntax,
check,
expandTemplate,
expand,
) where
import GHC (DynFlags (..), Ghc)
import GHC.Driver.Session (DumpFlag (Opt_D_dump_splices), dopt_set)
import Hhp.GHCApi
import Hhp.Logger
import Hhp.Types
checkSyntax
:: Options
-> Cradle
-> [FilePath]
-> IO String
checkSyntax :: Options -> Cradle -> [FilePath] -> IO FilePath
checkSyntax Options
_ Cradle
_ [] = FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
""
checkSyntax Options
opt Cradle
cradle [FilePath]
files = FilePath -> Ghc FilePath -> IO FilePath
forall a. FilePath -> Ghc a -> IO a
withGHC FilePath
sessionName (Ghc FilePath -> IO FilePath) -> Ghc FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ do
Options -> Cradle -> Ghc ()
initializeFlagsWithCradle Options
opt Cradle
cradle
(FilePath -> FilePath)
-> (FilePath -> FilePath) -> Either FilePath FilePath -> FilePath
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either FilePath -> FilePath
forall a. a -> a
id FilePath -> FilePath
forall a. a -> a
id (Either FilePath FilePath -> FilePath)
-> Ghc (Either FilePath FilePath) -> Ghc FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Options -> [FilePath] -> Ghc (Either FilePath FilePath)
check Options
opt [FilePath]
files
where
sessionName :: FilePath
sessionName = case [FilePath]
files of
[FilePath
file] -> FilePath
file
[FilePath]
_ -> FilePath
"MultipleFiles"
check
:: Options
-> [FilePath]
-> Ghc (Either String String)
check :: Options -> [FilePath] -> Ghc (Either FilePath FilePath)
check Options
opt [FilePath]
fileNames =
Options
-> (DynFlags -> DynFlags)
-> Ghc ()
-> Ghc (Either FilePath FilePath)
withLogger Options
opt (DynFlags -> DynFlags
setAllWarningFlags (DynFlags -> DynFlags)
-> (DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DynFlags -> DynFlags
setPartialSignatures (DynFlags -> DynFlags)
-> (DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DynFlags -> DynFlags
setDeferTypedHoles) (Ghc () -> Ghc (Either FilePath FilePath))
-> Ghc () -> Ghc (Either FilePath FilePath)
forall a b. (a -> b) -> a -> b
$
[FilePath] -> Ghc ()
setTargetFiles [FilePath]
fileNames
expandTemplate
:: Options
-> Cradle
-> [FilePath]
-> IO String
expandTemplate :: Options -> Cradle -> [FilePath] -> IO FilePath
expandTemplate Options
_ Cradle
_ [] = FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
""
expandTemplate Options
opt Cradle
cradle [FilePath]
files = FilePath -> Ghc FilePath -> IO FilePath
forall a. FilePath -> Ghc a -> IO a
withGHC FilePath
sessionName (Ghc FilePath -> IO FilePath) -> Ghc FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ do
Options -> Cradle -> Ghc ()
initializeFlagsWithCradle Options
opt Cradle
cradle
(FilePath -> FilePath)
-> (FilePath -> FilePath) -> Either FilePath FilePath -> FilePath
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either FilePath -> FilePath
forall a. a -> a
id FilePath -> FilePath
forall a. a -> a
id (Either FilePath FilePath -> FilePath)
-> Ghc (Either FilePath FilePath) -> Ghc FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Options -> [FilePath] -> Ghc (Either FilePath FilePath)
expand Options
opt [FilePath]
files
where
sessionName :: FilePath
sessionName = case [FilePath]
files of
[FilePath
file] -> FilePath
file
[FilePath]
_ -> FilePath
"MultipleFiles"
expand
:: Options
-> [FilePath]
-> Ghc (Either String String)
expand :: Options -> [FilePath] -> Ghc (Either FilePath FilePath)
expand Options
opt [FilePath]
fileNames =
Options
-> (DynFlags -> DynFlags)
-> Ghc ()
-> Ghc (Either FilePath FilePath)
withLogger Options
opt (DynFlags -> DynFlags
setDumpSplices (DynFlags -> DynFlags)
-> (DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DynFlags -> DynFlags
setNoWarningFlags) (Ghc () -> Ghc (Either FilePath FilePath))
-> Ghc () -> Ghc (Either FilePath FilePath)
forall a b. (a -> b) -> a -> b
$
[FilePath] -> Ghc ()
setTargetFiles [FilePath]
fileNames
setDumpSplices :: DynFlags -> DynFlags
setDumpSplices :: DynFlags -> DynFlags
setDumpSplices DynFlags
dflag = DynFlags -> DumpFlag -> DynFlags
dopt_set DynFlags
dflag DumpFlag
Opt_D_dump_splices