module Language.Eval.Internal where
import Data.Char
import Data.List
import Data.String
import Paths_nix_eval (getDataFileName)
import System.Exit
import System.IO
import qualified System.IO.Strict
import System.IO.Unsafe
import System.Process
newtype Pkg = Pkg String deriving (Eq, Ord, Show)
newtype Mod = Mod String deriving (Eq, Ord, Show)
newtype Flag = Flag String deriving (Eq, Ord, Show)
data Expr = Expr {
ePkgs :: [Pkg]
, eMods :: [Mod]
, eFlags :: [Flag]
, ePreamble :: [String]
, eExpr :: String
} deriving (Show)
instance Eq Expr where
e1 == e2 = eExpr e1 == eExpr e2 &&
perm (ePkgs e1) (ePkgs e2) &&
perm (eMods e1) (eMods e2) &&
perm (eFlags e1) (eFlags e2)
where perm xs ys = allIn xs ys && allIn ys xs
allIn xs ys = all (`elem` ys) xs
instance IsString Expr where
fromString = raw
instance IsString Pkg where
fromString = Pkg
instance IsString Mod where
fromString = Mod
instance IsString Flag where
fromString = Flag
eval :: Expr -> IO (Maybe String)
eval = eval' mkHs
eval' :: (String -> String) -> Expr -> IO (Maybe String)
eval' f x = do
cmd <- decideCmd x
(out, code) <- runCmdStdIO cmd (buildInput f x)
case code of
ExitSuccess -> return $ Just (trim out)
ExitFailure _ -> hPutStr stderr out >> return Nothing
runCmdStdIO :: CreateProcess -> String -> IO (String, ExitCode)
runCmdStdIO c i = do (Just hIn, Just hOut, Nothing, hProc) <- createProcess c
hPutContents hIn i
out <- System.IO.Strict.hGetContents hOut
code <- waitForProcess hProc
return (out, code)
buildInput f x = unlines (map mkImport mods ++ ePreamble x ++ [f expr])
where mods = nub $ eMods x
expr = eExpr x
decideCmd :: Expr -> IO CreateProcess
decideCmd x = do
newEnv <- needNewEnv (nub $ ePkgs x)
return (buildCmd (if newEnv then mkCmd x
else noShellCmd x))
buildCmd (cmd, args) = (proc cmd args) {
std_in = CreatePipe,
std_out = CreatePipe,
std_err = Inherit
}
noShellCmd :: Expr -> (String, [String])
noShellCmd x = ("sh", wrapCmd' x)
flagsOf x = map (\(Flag x) -> x) (nub $ eFlags x)
hPutContents h c = hPutStr h c >> hClose h
mkCmd :: Expr -> (String, [String])
mkCmd x = ("nix-shell", ["--show-trace", "--run", cmdLine x, "-p", pkgOf x])
pkgOf = mkGhcPkg . nub . ePkgs
cmdLine x = unwords (map shellEscape ("sh" : wrapCmd' x ++ [show (pkgsToName pkgs)]))
where pkgs = nub $ ePkgs x
shellEscape s = if ' ' `elem` s then show s else s
wrapCmd' x = [wrapperPath, unwords . ("runhaskell" :) . flagsOf $ x]
wrapperPath :: FilePath
wrapperPath = unsafePerformIO (getDataFileName "wrapper.sh")
ghcEnvWithPkgsPath :: FilePath
ghcEnvWithPkgsPath = unsafePerformIO (getDataFileName "ghcEnvWithPkgs.nix")
mkGhcPkg ps = env ++ " { name = " ++ name ++ "; pkgNames = " ++ args ++ "; }"
where env = "import " ++ show ghcEnvWithPkgsPath
args = "[ " ++ unwords pkgs ++ " ]"
pkgs = map (\(Pkg p) -> show p) ps
name = show (pkgsToName ps)
pkgsToName [] = "ghc-env"
pkgsToName ps = "ghc-env-with-" ++ intercalate "-" (map clean pkgs)
where pkgs = map (\(Pkg p) -> p) ps
clean = filter isAlphaNum
havePkgs :: [Pkg] -> IO Bool
havePkgs [] = return True
havePkgs (Pkg p:ps) = do
out <- readProcess "ghc-pkg" ["--simple-output", "list", p] ""
if p `isInfixOf` out
then havePkgs ps
else return False
needNewEnv ps = do
hgp <- haveGhcPkg
if hgp then fmap not (havePkgs ps)
else return True
mkImport :: Mod -> String
mkImport (Mod m) = "import " ++ m
mkHs :: String -> String
mkHs e = "main = Prelude.putStr (" ++ e ++ ")"
trim :: String -> String
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
haveCommand c = do
(c, _, _) <- readCreateProcessWithExitCode (shell ("hash " ++ c)) ""
return (c == ExitSuccess)
haveNix :: IO Bool
haveNix = haveCommand "nix-shell"
haveGhcPkg = haveCommand "ghc-pkg"
raw :: String -> Expr
raw s = Expr { ePkgs = [], eMods = [], eExpr = s, eFlags = [], ePreamble = [] }
infixr 8 $$
($$) :: Expr -> Expr -> Expr
x $$ y = Expr {
ePkgs = nub (ePkgs x ++ ePkgs y),
eMods = nub (eMods x ++ eMods y),
eFlags = nub (eFlags x ++ eFlags y),
ePreamble = ePreamble x ++ ePreamble y ,
eExpr = concat ["((", eExpr x, ") (", eExpr y, "))"] }
asString :: (Show a) => a -> Expr
asString = raw . show
qualified :: Mod -> Expr -> Expr
qualified (Mod m) x = x { eMods = Mod m : eMods x,
eExpr = m ++ "." ++ eExpr x }
withMods :: [Mod] -> Expr -> Expr
withMods ms x = x { eMods = eMods x ++ ms }
withPkgs :: [Pkg] -> Expr -> Expr
withPkgs ps x = x { ePkgs = ePkgs x ++ ps }
withFlags :: [Flag] -> Expr -> Expr
withFlags fs x = x { eFlags = eFlags x ++ fs }
withPreamble :: String -> Expr -> Expr
withPreamble p x = x { ePreamble = ePreamble x ++ [p] }