module Language.Fixpoint.Utils.Files (
  
    Ext (..)
  , extFileName
  , extFileNameR
  , tempDirectory
  , extModuleName
  , withExt
  , isExtFile
  , isBinary
  
  , getFixpointPath
  , getZ3LibPath
  
  , getFileInDirs
  , copyFiles
) where
import qualified Control.Exception      as Ex
import           Control.Monad
import           Data.List              hiding (find)
import           Data.Maybe             (fromMaybe)
import           System.Directory
import           System.FilePath
import           Language.Fixpoint.Misc (errorstar)
getFixpointPath :: IO FilePath
getFixpointPath = fromMaybe msg . msum <$>
                  sequence [ findExecutable "fixpoint.native"
                           , findExecutable "fixpoint.native.exe"
                             
                           , findFile ["external/fixpoint"] "fixpoint.native"
                           ]
  where
    msg = errorstar "Cannot find fixpoint binary [fixpoint.native]"
getZ3LibPath :: IO FilePath
getZ3LibPath    = dropFileName <$> getFixpointPath
 
data Ext = Cgi      
         | Fq       
         | Out      
         | Html     
         | Annot    
         | Vim      
         | Hs       
         | HsBoot   
         | LHs      
         | Js       
         | Ts       
         | Spec     
         | BinSpec  
         | Hquals   
         | Result   
         | Cst      
         | Mkdn     
         | Json     
         | Saved    
         | Cache    
         | Dot      
         | Part Int 
         | Auto Int 
         | Pred
         | PAss
         | Dat
         | BinFq    
         | Smt2     
         | Min      
         | MinQuals 
         | MinKVars 
         deriving (Eq, Ord, Show)
extMap :: Ext -> FilePath
extMap          = go
  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 Vim      = ".vim.annot"
    go Hs       = ".hs"
    go LHs      = ".lhs"
    go HsBoot   = ".hs-boot"
    go Js       = ".js"
    go Ts       = ".ts"
    go Mkdn     = ".markdown"
    go Json     = ".json"
    go Spec     = ".spec"
    go BinSpec  = ".bspec"
    go Hquals   = ".hquals"
    go Result   = ".out"
    go Saved    = ".bak"
    go Cache    = ".err"
    go Smt2     = ".smt2"
    go (Auto n) = ".auto." ++ show n
    go Dot      = ".dot"
    go BinFq    = ".bfq"
    go (Part n) = "." ++ show n
    go Min      = ".minfq"
    go MinQuals = ".minquals"
    go MinKVars = ".minkvars"
    
withExt         :: FilePath -> Ext -> FilePath
withExt f ext   =  replaceExtension f (extMap ext)
extFileName     :: Ext -> FilePath -> FilePath
extFileName e f = path </> addExtension file ext
  where
    path        = tempDirectory f
    file        = takeFileName  f
    ext         = extMap e
tempDirectory   :: FilePath -> FilePath
tempDirectory f
  | isTmp dir   = dir
  | otherwise   = dir </> tmpDirName
  where
    dir         = takeDirectory f
    isTmp       = (tmpDirName `isSuffixOf`)
tmpDirName :: FilePath
tmpDirName      = ".liquid"
extFileNameR     :: Ext -> FilePath -> FilePath
extFileNameR ext = (`addExtension` extMap ext)
isExtFile ::  Ext -> FilePath -> Bool
isExtFile ext = (extMap ext ==) . takeExtension
extModuleName ::  String -> Ext -> FilePath
extModuleName modName ext =
  case explode modName of
    [] -> errorstar $ "malformed module name: " ++ modName
    ws -> extFileNameR 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)
getFileInDirs :: FilePath -> [FilePath] -> IO (Maybe FilePath)
getFileInDirs name = findFirst (testM doesFileExist . (</> name))
testM :: (Monad m) => (a -> m Bool) -> a -> m [a]
testM f x = do b <- f x
               return [ x | b ]
findFirst ::  Monad m => (t -> m [a]) -> [t] -> m (Maybe a)
findFirst _ []     = return Nothing
findFirst f (x:xs) = do r <- f x
                        case r of
                          y:_ -> return (Just y)
                          []  -> findFirst f xs
isBinary :: FilePath -> Bool
isBinary = isExtFile BinFq