module System.Plugins.Utils (
Arg,
hWrite,
mkUnique,
hMkUnique,
mkUniqueIn,
hMkUniqueIn,
findFile,
mkTemp, mkTempIn,
replaceSuffix,
outFilePath,
dropSuffix,
mkModid,
changeFileExt,
joinFileExt,
splitFileExt,
isSublistOf,
dirname,
basename,
(</>), (<.>), (<+>), (<>),
newer,
encode,
decode,
EncodedString,
panic
) where
#include "../../../config.h"
import System.Plugins.Env ( isLoaded )
import System.Plugins.Consts ( objSuf, hiSuf, tmpDir )
import Foreign.C (CInt(..), CString, withCString)
import Foreign.C.Error (Errno, eEXIST, getErrno, errnoToIOError)
import System.Posix.Internals
import System.Posix.Types (CMode)
import Control.Exception (IOException, catch)
import Data.Bits
import Data.Char
import Data.List
import Prelude hiding (catch)
import System.IO hiding (openBinaryTempFile, openTempFile)
import System.Random (randomRIO)
import GHC.IO.Encoding (getLocaleEncoding)
import GHC.IO.Handle.FD
import qualified GHC.IO.FD as FD
import System.Environment ( getEnv )
import System.Directory ( doesFileExist, getModificationTime, removeFile )
import System.FilePath (pathSeparator)
type Arg = String
panic s = ioError ( userError s )
hWrite :: Handle -> String -> IO ()
hWrite hdl src = hPutStr hdl src >> hClose hdl >> return ()
openTempFile :: FilePath
-> String
-> String
-> IO (FilePath, Handle)
openTempFile tmp_dir pfx sfx
= openTempFile' "openTempFile" tmp_dir pfx sfx False 0o600
openBinaryTempFile :: FilePath -> String -> String -> IO (FilePath, Handle)
openBinaryTempFile tmp_dir pfx sfx
= openTempFile' "openBinaryTempFile" tmp_dir pfx sfx True 0o600
openTempFileWithDefaultPermissions :: FilePath -> String -> String
-> IO (FilePath, Handle)
openTempFileWithDefaultPermissions tmp_dir pfx sfx
= openTempFile' "openTempFileWithDefaultPermissions" tmp_dir pfx sfx False 0o666
openBinaryTempFileWithDefaultPermissions :: FilePath -> String -> String
-> IO (FilePath, Handle)
openBinaryTempFileWithDefaultPermissions tmp_dir pfx sfx
= openTempFile' "openBinaryTempFileWithDefaultPermissions" tmp_dir pfx sfx True 0o666
badfnmsg :: String
badfnmsg = "openTempFile': Template string must not contain path separator characters: "
openTempFile' :: String -> FilePath -> String -> String -> Bool -> CMode
-> IO (FilePath, Handle)
openTempFile' loc tmp_dir pfx sfx binary mode
| pathSeparator `elem` pfx
= fail $ badfnmsg++pfx
| pathSeparator `elem` sfx
= fail $ badfnmsg++sfx
| otherwise = findTempName
where
findTempName = do
filename <- mkTempFileName tmp_dir pfx sfx
r <- openNewFile filename binary mode
case r of
FileExists -> findTempName
OpenNewError errno -> ioError (errnoToIOError loc errno Nothing (Just tmp_dir))
NewFileCreated fd -> do
(fD,fd_type) <- FD.mkFD fd ReadWriteMode Nothing
False
True
enc <- getLocaleEncoding
h <- mkHandleFromFD fD fd_type filename ReadWriteMode False (Just enc)
return (filename, h)
mkTempFileName :: FilePath -> String -> String -> IO String
mkTempFileName dir pfx sfx = do
let rs = filter isAlphaNum ['0'..'z']
maxInd = length rs 1
rchoose = do
i <- randomRIO (0, maxInd)
return (rs !! i)
rnd <- sequence $ replicate 6 rchoose
return $ dir </> pfx ++ rnd ++ sfx
data OpenNewFileResult
= NewFileCreated CInt
| FileExists
| OpenNewError Errno
openNewFile :: FilePath -> Bool -> CMode -> IO OpenNewFileResult
openNewFile filepath binary mode = do
let oflags1 = rw_flags .|. o_EXCL
binary_flags
| binary = o_BINARY
| otherwise = 0
oflags = oflags1 .|. binary_flags
fd <- withFilePath filepath $ \ f ->
c_open f oflags mode
if fd < 0
then do
errno <- getErrno
case errno of
_ | errno == eEXIST -> return FileExists
#ifdef mingw32_HOST_OS
_ | errno == eACCES -> do
withCString filepath $ \path -> do
exists <- c_fileExists path
return $ if exists
then FileExists
else OpenNewError errno
#endif
_ -> return (OpenNewError errno)
else return (NewFileCreated fd)
#ifdef mingw32_HOST_OS
foreign import ccall "file_exists" c_fileExists :: CString -> IO Bool
#endif
std_flags, output_flags, rw_flags :: CInt
std_flags = o_NONBLOCK .|. o_NOCTTY
output_flags = std_flags .|. o_CREAT
rw_flags = output_flags .|. o_RDWR
mkTemp :: IO (String,Handle)
mkTemp = do tmpd <- catch (getEnv "TMPDIR") (\ (_ :: IOException) -> return tmpDir)
mkTempIn tmpd
mkTempIn :: String -> IO (String, Handle)
mkTempIn tmpd = do
(tmpf, hdl) <- openTempFile tmpd "Hsplugins" ".hs"
let modname = mkModid tmpf
if and $ map (\c -> isAlphaNum c && c /= '_') modname
then return (tmpf,hdl)
else panic $ "Illegal characters in temp file: `"++tmpf++"'"
mkUnique :: IO FilePath
mkUnique = do (t,h) <- hMkUnique
hClose h >> return t
hMkUnique :: IO (FilePath,Handle)
hMkUnique = do (t,h) <- mkTemp
alreadyLoaded <- isLoaded t
if alreadyLoaded
then hClose h >> removeFile t >> hMkUnique
else return (t,h)
mkUniqueIn :: FilePath -> IO FilePath
mkUniqueIn dir = do (t,h) <- hMkUniqueIn dir
hClose h >> return t
hMkUniqueIn :: FilePath -> IO (FilePath,Handle)
hMkUniqueIn dir = do (t,h) <- mkTempIn dir
alreadyLoaded <- isLoaded t
if alreadyLoaded
then hClose h >> removeFile t >> hMkUniqueIn dir
else return (t,h)
findFile :: [String] -> FilePath -> IO (Maybe FilePath)
findFile [] _ = return Nothing
findFile (ext:exts) file
= do let l = changeFileExt file ext
b <- doesFileExist l
if b then return $ Just l
else findFile exts file
infixr 6 </>
infixr 6 <.>
(</>), (<.>), (<+>), (<>) :: FilePath -> FilePath -> FilePath
[] </> b = b
a </> b = a ++ "/" ++ b
[] <.> b = b
a <.> b = a ++ "." ++ b
[] <+> b = b
a <+> b = a ++ " " ++ b
[] <> b = b
a <> b = a ++ b
dirname :: FilePath -> FilePath
dirname p =
let x = findIndices (== '\\') p
y = findIndices (== '/') p
in
if not $ null x
then if not $ null y
then if (maximum x) > (maximum y) then dirname' '\\' p else dirname' '/' p
else dirname' '\\' p
else dirname' '/' p
where
dirname' chara pa =
case reverse $ dropWhile (/= chara) $ reverse pa of
[] -> "."
pa' -> pa'
basename :: FilePath -> FilePath
basename p =
let x = findIndices (== '\\') p
y = findIndices (== '/') p
in
if not $ null x
then if not $ null y
then if (maximum x) > (maximum y) then basename' '\\' p else basename' '/' p
else basename' '\\' p
else basename' '/' p
where
basename' chara pa = reverse $ takeWhile (/= chara) $ reverse pa
dropSuffix :: FilePath -> FilePath
dropSuffix f = reverse . tail . dropWhile (/= '.') $ reverse f
mkModid :: String -> String
mkModid = (takeWhile (/= '.')) . reverse . (takeWhile (\x -> ('/'/= x) && ('\\' /= x))) . reverse
changeFileExt :: FilePath
-> String
-> FilePath
changeFileExt fpath ext = joinFileExt name ext
where
(name,_) = splitFileExt fpath
joinFileExt :: String -> String -> FilePath
joinFileExt fpath "" = fpath
joinFileExt fpath ext = fpath ++ '.':ext
splitFileExt :: FilePath -> (String, String)
splitFileExt p =
case break (== '.') fname of
(suf@(_:_),_:pre) -> (reverse (pre++fpath), reverse suf)
_ -> (p, [])
where
(fname,fpath) = break isPathSeparator (reverse p)
isPathSeparator :: Char -> Bool
isPathSeparator ch =
#if defined(CYGWIN) || defined(__MINGW32__)
ch == '/' || ch == '\\'
#else
ch == '/'
#endif
replaceSuffix :: FilePath -> String -> FilePath
replaceSuffix [] _ = []
replaceSuffix f suf =
case reverse $ dropWhile (/= '.') $ reverse f of
[] -> f ++ suf
f' -> f' ++ tail suf
outFilePath :: FilePath -> [Arg] -> (FilePath,FilePath)
outFilePath src args =
let objs = find_o args
paths = find_p args
in case () of { _
| not (null objs)
-> let obj = last objs in (obj, mk_hi obj)
| not (null paths)
-> let obj = last paths </> mk_o (basename src) in (obj, mk_hi obj)
| otherwise
-> (mk_o src, mk_hi src)
}
where
outpath = "-o"
outdir = "-odir"
mk_hi s = replaceSuffix s hiSuf
mk_o s = replaceSuffix s objSuf
find_o [] = []
find_o (f:f':fs) | f == outpath = [f']
| otherwise = find_o $! f':fs
find_o _ = []
find_p [] = []
find_p (f:f':fs) | f == outdir = [f']
| otherwise = find_p $! f':fs
find_p _ = []
newer :: FilePath -> FilePath -> IO Bool
newer a b = do
a_t <- getModificationTime a
b_exists <- doesFileExist b
if not b_exists
then return True
else do b_t <- getModificationTime b
return ( a_t > b_t )
type EncodedString = String
encode :: String -> EncodedString
encode [] = []
encode (c:cs) = encode_ch c ++ encode cs
unencodedChar :: Char -> Bool
unencodedChar 'Z' = False
unencodedChar 'z' = False
unencodedChar c = c >= 'a' && c <= 'z'
|| c >= 'A' && c <= 'Z'
|| c >= '0' && c <= '9'
decode :: EncodedString -> String
decode [] = []
decode ('Z' : d : rest) | isDigit d = decode_tuple d rest
| otherwise = decode_upper d : decode rest
decode ('z' : d : rest) | isDigit d = decode_num_esc d rest
| otherwise = decode_lower d : decode rest
decode (c : rest) = c : decode rest
decode_upper, decode_lower :: Char -> Char
decode_upper 'L' = '('
decode_upper 'R' = ')'
decode_upper 'M' = '['
decode_upper 'N' = ']'
decode_upper 'C' = ':'
decode_upper 'Z' = 'Z'
decode_upper ch = error $ "decode_upper can't handle this char `"++[ch]++"'"
decode_lower 'z' = 'z'
decode_lower 'a' = '&'
decode_lower 'b' = '|'
decode_lower 'c' = '^'
decode_lower 'd' = '$'
decode_lower 'e' = '='
decode_lower 'g' = '>'
decode_lower 'h' = '#'
decode_lower 'i' = '.'
decode_lower 'l' = '<'
decode_lower 'm' = '-'
decode_lower 'n' = '!'
decode_lower 'p' = '+'
decode_lower 'q' = '\''
decode_lower 'r' = '\\'
decode_lower 's' = '/'
decode_lower 't' = '*'
decode_lower 'u' = '_'
decode_lower 'v' = '%'
decode_lower ch = error $ "decode_lower can't handle this char `"++[ch]++"'"
decode_num_esc :: Char -> [Char] -> String
decode_num_esc d cs
= go (digitToInt d) cs
where
go n (c : rest) | isDigit c = go (10*n + digitToInt c) rest
go n ('U' : rest) = chr n : decode rest
go _ other = error $
"decode_num_esc can't handle this: \""++other++"\""
encode_ch :: Char -> EncodedString
encode_ch c | unencodedChar c = [c]
encode_ch '(' = "ZL"
encode_ch ')' = "ZR"
encode_ch '[' = "ZM"
encode_ch ']' = "ZN"
encode_ch ':' = "ZC"
encode_ch 'Z' = "ZZ"
encode_ch 'z' = "zz"
encode_ch '&' = "za"
encode_ch '|' = "zb"
encode_ch '^' = "zc"
encode_ch '$' = "zd"
encode_ch '=' = "ze"
encode_ch '>' = "zg"
encode_ch '#' = "zh"
encode_ch '.' = "zi"
encode_ch '<' = "zl"
encode_ch '-' = "zm"
encode_ch '!' = "zn"
encode_ch '+' = "zp"
encode_ch '\'' = "zq"
encode_ch '\\' = "zr"
encode_ch '/' = "zs"
encode_ch '*' = "zt"
encode_ch '_' = "zu"
encode_ch '%' = "zv"
encode_ch c = 'z' : shows (ord c) "U"
decode_tuple :: Char -> EncodedString -> String
decode_tuple d cs
= go (digitToInt d) cs
where
go n (c : rest) | isDigit c = go (10*n + digitToInt c) rest
go 0 ['T'] = "()"
go n ['T'] = '(' : replicate (n1) ',' ++ ")"
go 1 ['H'] = "(# #)"
go n ['H'] = '(' : '#' : replicate (n1) ',' ++ "#)"
go _ other = error $ "decode_tuple \'"++other++"'"
isSublistOf :: Eq a => [a] -> [a] -> Bool
isSublistOf [] _ = True
isSublistOf _ [] = False
isSublistOf x y@(_:ys)
| isPrefixOf x y = True
| otherwise = isSublistOf x ys