module Language.Fixpoint.Files (
Ext (..)
, extFileName
, extModuleName
, isExtFile
, getIncludePath, getFixpointPath, getHqBotPath, getZ3LibPath, getCSSPath
, getHsTargets
, getFileInDirs
, findFileInDirs
, copyFiles, deleteBinFiles
) where
import qualified Control.Exception as Ex
import Control.Monad
import Data.Functor ((<$>))
import Data.List hiding (find)
import Data.Maybe (fromMaybe)
import System.Directory
import System.Environment
import System.FilePath
import System.FilePath.Find
import Language.Fixpoint.Misc
envVarName = "LIQUIDHS"
getIncludePath, getHqBotPath, getCSSPath, getFixpointPath :: IO FilePath
getIncludePath = getSuffixPath ["include"] >>= checkM doesDirectoryExist "include directory"
getCSSPath = getSuffixPath ["syntax", "liquid.css"] >>= checkM doesFileExist "css file"
getFixpointPath = fromMaybe msg <$> findExecutable "fixpoint.native"
where msg = errorstar "Cannot find fixpoint binary [fixpoint.native]"
getHqBotPath = liftM (`combine` "Bot.hquals") getIncludePath
getZ3LibPath = dropFileName <$> getFixpointPath
getSuffixPath :: [FilePath] -> IO FilePath
getSuffixPath suff
= (joinPath . (: suff)) `fmap` getEnv envVarName
checkM f msg p
= do ex <- f p
if ex then return p else errorstar $ "Cannot find " ++ msg ++ " at :" ++ p
data Ext = Cgi
| Fq
| Out
| Html
| Annot
| Hs
| LHs
| Spec
| Hquals
| Result
| Cst
| Mkdn
| Pred
| PAss
| Dat
deriving (Eq, Ord, Show)
extMap e = go e
where
go Cgi = "cgi"
go Pred = "pred"
go PAss = "pass"
go Dat = "dat"
go Out = "fqout"
go Fq = "fq"
go Html = "html"
go Cst = "cst"
go Annot = "annot"
go Hs = "hs"
go LHs = "lhs"
go Mkdn = "markdown"
go Spec = "spec"
go Hquals = "hquals"
go Result = "out"
go _ = errorstar $ "extMap: Unknown extension" ++ show e
extFileName :: Ext -> FilePath -> FilePath
extFileName ext = (`addExtension` (extMap ext))
isExtFile :: Ext -> FilePath -> Bool
isExtFile ext = ((extMap ext) `isSuffixOf`)
extModuleName :: String -> Ext -> FilePath
extModuleName modName ext =
case explode modName of
[] -> errorstar $ "malformed module name: " ++ modName
ws -> extFileName ext $ foldr1 (</>) ws
where explode = words . map (\c -> if c == '.' then ' ' else c)
copyFiles :: [FilePath] -> FilePath -> IO ()
copyFiles srcs tgt
= do Ex.catch (removeFile tgt) $ \(_ :: Ex.IOException) -> return ()
forM_ srcs (readFile >=> appendFile tgt)
deleteBinFiles :: FilePath -> IO ()
deleteBinFiles fn = mapM_ (tryIgnore "delete binaries" . removeFile)
$ (fn `replaceExtension`) `fmap` exts
where exts = ["hi", "o"]
getHsTargets p
| hasTrailingPathSeparator p = getHsSourceFiles p
| otherwise = return [p]
getHsSourceFiles = find dirs hs
where hs = extension ==? ".hs" ||? extension ==? ".lhs"
dirs = liftM (not . ("dist" `isSuffixOf`)) directory
getFileInDirs :: FilePath -> [FilePath] -> IO (Maybe FilePath)
getFileInDirs name = findFirst (testM doesFileExist . (</> name))
findFileInDirs :: FilePath -> [FilePath] -> IO FilePath
findFileInDirs file dirs
= liftM (fromMaybe err) (findFirst (find always (fileName ==? file)) dirs)
where err = errorstar $ "findFileInDirs: cannot find " ++ file ++ " in " ++ show dirs