{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Language.Alloy.Call (
CallAlloyConfig (maxInstances, noOverflow, timeout),
defaultCallAlloyConfig,
existsInstance,
getInstances,
getInstancesWith,
module Functions,
module Types,
) where
import qualified Data.ByteString as BS
(hGetLine, intercalate, isSuffixOf, writeFile)
import qualified Data.ByteString.Char8 as BS (unlines)
import Control.Concurrent (
ThreadId,
forkIO, killThread, newEmptyMVar, putMVar, takeMVar, threadDelay,
)
import Control.Exception (IOException)
import Control.Lens.Internal.ByteString (unpackStrict8)
import Control.Monad (unless, void, when)
import Data.ByteString (ByteString)
import Data.Hashable (hash)
import Data.IORef (IORef, newIORef, readIORef)
import Data.List.Split (splitOn)
import Data.Maybe (fromMaybe)
import System.Directory
(XdgDirectory (..), createDirectory, doesFileExist, doesDirectoryExist,
getTemporaryDirectory, getXdgDirectory)
import System.Directory.Internal (setFileMode)
import System.Directory.Internal.Prelude
(catch, isDoesNotExistError)
import System.Exit (ExitCode (..))
import System.FilePath
((</>), (<.>), searchPathSeparator, takeDirectory)
import System.IO
(BufferMode (..), Handle, hClose, hFlush, hIsEOF, hPutStr, hSetBuffering)
import System.IO.Unsafe (unsafePerformIO)
import System.Process (
CreateProcess (..), StdStream (..), ProcessHandle,
createProcess, proc, terminateProcess, waitForProcess,
)
#if defined(mingw32_HOST_OS)
import System.Win32.Info (getUserName)
#else
import System.Posix.User (getLoginName)
#endif
import Language.Alloy.Functions as Functions
import Language.Alloy.Parser (parseInstance)
import Language.Alloy.RessourceNames (
alloyJarName, className, classPackage, commonsCliJarName
)
import Language.Alloy.Ressources (alloyJar, classFile, commonsCliJar)
import Language.Alloy.Types as Types
(AlloyInstance, AlloySig, Entries, Object, Signature)
data CallAlloyConfig = CallAlloyConfig {
maxInstances :: Maybe Integer,
noOverflow :: Bool,
timeout :: Maybe Int
}
defaultCallAlloyConfig :: CallAlloyConfig
defaultCallAlloyConfig = CallAlloyConfig {
maxInstances = Nothing,
noOverflow = True,
timeout = Nothing
}
{-# NOINLINE mclassPath #-}
mclassPath :: IORef (Maybe FilePath)
mclassPath = unsafePerformIO (newIORef Nothing)
getInstances
:: Maybe Integer
-> String
-> IO [AlloyInstance]
getInstances maxIs = getInstancesWith defaultCallAlloyConfig {
maxInstances = maxIs
}
getInstancesWith
:: CallAlloyConfig
-> String
-> IO [AlloyInstance]
getInstancesWith config content = do
classPath <- getClassPath
let callAlloy = proc "java"
$ ["-cp", classPath, classPackage ++ '.' : className,
"-i", show $ fromMaybe (-1) $ maxInstances config]
++ ["-o" | not $ noOverflow config]
(Just hin, Just hout, Just herr, ph) <-
createProcess callAlloy {
std_out = CreatePipe,
std_in = CreatePipe,
std_err = CreatePipe
}
pout <- listenForOutput hout
perr <- listenForOutput herr
#ifndef mingw32_HOST_OS
hSetBuffering hin NoBuffering
#endif
hPutStr hin content
hFlush hin
hClose hin
maybe (return ()) (void . startTimeout hin hout herr ph) $ timeout config
out <- getOutput pout
err <- getOutput perr
printContentOnError ph
unless (null err) $ fail $ unpackStrict8 $ BS.unlines err
let instas = fmap (BS.intercalate "\n") $ drop 1 $ splitOn [begin] out
let finstas = filterLast (not . (partialInstance `BS.isSuffixOf`)) instas
return $ either (error . show) id . parseInstance <$> finstas
where
begin :: ByteString
begin = "---INSTANCE---"
partialInstance :: ByteString
partialInstance = "---PARTIAL_INSTANCE---"
filterLast _ [] = []
filterLast p x@[_] = filter p x
filterLast p (x:xs) = x:filterLast p xs
getWholeOutput h = do
eof <- hIsEOF h
if eof
then return []
else catch
((:) <$> BS.hGetLine h <*> getWholeOutput h)
(\(_ :: IOException) -> return [partialInstance])
printContentOnError ph = do
code <- waitForProcess ph
when (code == ExitFailure 1)
$ putStrLn $ "Failed parsing the Alloy code:\n" <> content
listenForOutput h = do
mvar <- newEmptyMVar
pid <- forkIO $ getWholeOutput h >>= putMVar mvar
return (pid, mvar)
getOutput (pid, mvar) = do
output <- takeMVar mvar
killThread pid
return output
startTimeout
:: Handle
-> Handle
-> Handle
-> ProcessHandle
-> Int -> IO ThreadId
startTimeout i o e ph t = forkIO $ do
threadDelay t
void $ forkIO $ hClose e
void $ forkIO $ hClose o
terminateProcess ph
hClose i
getClassPath :: IO FilePath
getClassPath = do
mclassPath' <- readIORef mclassPath
maybe readClassPath return mclassPath'
fallbackToTempDir :: IO FilePath -> IO FilePath
fallbackToTempDir m = catch m $ \e ->
if isDoesNotExistError e
then do
tmp <- getTemporaryDirectory
#if defined(mingw32_HOST_OS)
login <- getUserName
#else
login <- getLoginName
#endif
let tmpDir = tmp </> show (hash login) </> appName
createUserDirectoriesIfMissing tmpDir
return tmpDir
else error $ show e
readClassPath :: IO FilePath
readClassPath = do
configDir <- fallbackToTempDir $ getXdgDirectory XdgConfig appName
let versionFile = configDir </> "version"
exists <- doesFileExist versionFile
if exists
then do
version <- read <$> readFile versionFile
unless (version == versionHash) $ createVersionFile configDir versionFile
else createVersionFile configDir versionFile
dataDir <- getXdgDirectory XdgData $ appName </> "dataDir"
return $ dataDir ++ searchPathSeparator : dataDir </> alloyJarName
++ searchPathSeparator : dataDir </> commonsCliJarName
createVersionFile :: FilePath -> FilePath -> IO ()
createVersionFile configDir versionFile = do
createDataDir
createUserDirectoriesIfMissing configDir
writeFile versionFile $ show versionHash
createDataDir :: IO ()
createDataDir = do
dataDir <- fallbackToTempDir $ getXdgDirectory XdgData $ appName </> "dataDir"
createUserDirectoriesIfMissing $ dataDir </> classPackage
BS.writeFile (dataDir </> classPackage </> className <.> "class") classFile
BS.writeFile (dataDir </> alloyJarName) alloyJar
BS.writeFile (dataDir </> commonsCliJarName) commonsCliJar
createUserDirectoriesIfMissing :: FilePath -> IO ()
createUserDirectoriesIfMissing fp = do
isDir <- doesDirectoryExist fp
let parent = takeDirectory fp
unless (isDir || parent == fp) $ do
createUserDirectoriesIfMissing parent
createDirectory fp
#ifndef mingw32_HOST_OS
setFileMode fp (7*8*8)
#endif
existsInstance
:: String
-> IO Bool
existsInstance = fmap (not . null) . getInstances (Just 1)
appName :: String
appName = "call-alloy"
{-# INLINE versionHash #-}
versionHash :: Int
versionHash = hash $ alloyHash + commonsCliHash + classFileHash
where
alloyHash = hash alloyJar
commonsCliHash = hash commonsCliJar
classFileHash = hash classFile