module Main where import Data.Char import Data.List import System.Directory import System.FilePath import System.FilePath.Find as F import System.Info import System.IO.Temp import System.Process main :: IO () main = putStrLn "-- Creating venzone release --\n" >> if isWin then error "Sorry, this packing script doesn't yet work on Windows." else -- rebuild callCommand "cabal new-clean" >> callCommand "cabal new-build venzone" >> -- find exe F.find always exec "dist-newstyle" >>= \(e:_) -> -- temp folder withSystemTempDirectory "vpack" (callb e) >> return () where exec :: FindClause Bool exec = -- correct name ( fileName ==? "venzone" ||? fileName ==? "venzone.exe" ) &&? -- correct filetype fileType ==? RegularFile -- exe filepath, tmpdir path callb :: FilePath -> FilePath -> IO () callb we fp = -- crea dir structure let rd = fp "venzone" sd = rd "stories" in createDirectory rd >> createDirectory sd >> -- muovi eseguibile qui copyFile we (rd "venzone") >> -- muovi readme qui copyFile ("." "assets" "readme.txt") (rd "readme.txt") >> -- muovi livelli qui let ls = "." "stories" f lp = copyFile (ls lp) (sd lp) in listDirectory ls >>= \ss -> mapM_ f ss >> -- elimina gymnasium removeFile (sd "t_gymnasium.vns") >> sysCompress fp >> return () -- tmp-dir sysCompress :: FilePath -> IO () sysCompress fp = withCurrentDirectory fp stripZip >> copyFile (fp aName) ("." aName) >> putStrLn ("\n" ++ aName ++ " created!") where aName :: String aName = "venzone-" ++ os ++ "-" ++ arch ++ ".zip" stripZip :: IO () stripZip = strip ("venzone" "venzone") >> callCommand ("zip -r " ++ aName ++ " venzone/") -- hackish but works on wine zipCommand :: String -> String -> String zipCommand an fl | isWin = "\"C:\\Program Files\\7-Zip\\7za.exe\" a -r " ++ an ++ " -w " ++ fl ++ " -mem=AES256" | otherwise = "zip -r " ++ an ++ " " ++ fl strip :: FilePath -> IO () strip fp | isWin = return () | otherwise = callCommand ("strip " ++ fp) isWin :: Bool isWin = isPrefixOf "windows" (map toLower os)