module Language.Eval.Internal where
import Data.Char
import Data.List
import Data.String
import System.Exit
import System.IO
import System.Process
newtype Pkg = Pkg String deriving (Eq, Ord, Show)
newtype Mod = Mod String deriving (Eq, Ord, Show)
newtype Expr = Expr ([Pkg], [Mod], String) deriving (Show)
instance Eq Expr where
(Expr (p1, m1, e1)) == (Expr (p2, m2, e2)) = e1 == e2 &&
perm p1 p2 &&
perm m1 m2
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
eval :: Expr -> IO (Maybe String)
eval x@(Expr (pkgs, mods, expr)) = do
(code, out, err) <- let (cmd, args) = mkCmd x
in readProcessWithExitCode cmd args (mkHs x)
hPutStr stderr err
return $ case code of
ExitSuccess -> Just (trim out)
ExitFailure _ -> Nothing
mkCmd :: Expr -> (String, [String])
mkCmd (Expr (ps, _, _)) = ("nix-shell", ["--run", "runhaskell",
"-p", mkGhcPkg ps])
mkGhcPkg ps = let pkgs = map (\(Pkg p) -> "(h." ++ p ++ ")") ps
in concat ["haskellPackages.ghcWithPackages ",
"(h: [", unwords pkgs, "])"]
mkHs :: Expr -> String
mkHs (Expr (_, ms, e)) = unlines (imports ++ [main])
where imports = map (\(Mod m) -> "import " ++ m) ms
main = "main = putStr (" ++ e ++ ")"
trim :: String -> String
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
raw :: String -> Expr
raw s = Expr ([], [], s)
($$) :: Expr -> Expr -> Expr
(Expr (p1, m1, e1)) $$ (Expr (p2, m2, e2)) = Expr
(nub (p1 ++ p2),
nub (m1 ++ m2),
concat ["((", e1, ") (", e2, "))"])
asString :: (Show a) => a -> Expr
asString = raw . show
qualified :: Mod -> String -> Expr
qualified (Mod m) e = Expr ([], [Mod m], m ++ "." ++ e)
withMods :: [Mod] -> Expr -> Expr
withMods ms (Expr (ps, ms', e)) = Expr (ps, ms' ++ ms, e)
withPkgs :: [Pkg] -> Expr -> Expr
withPkgs ps (Expr (ps', ms, e)) = Expr (ps' ++ ps, ms, e)