{-# LANGUAGE CPP #-} -- | -- Module : Seqaid.Demo -- Copyright : Andrew G. Seniuk 2014-2015 -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Andrew Seniuk -- Stability : provisional -- Portability : POSIX, Cabal -- -- Instrument a sample program (package -- ) -- with dynamic forcing functions. Refer to -- -- for more information about this methodology. module Main ( main ) where --module Seqaid.Demo ( main ) where import System.Environment ( getArgs ) import qualified System.IO.Temp as T import qualified System.Directory as D import System.Process import System.Exit import Paths_seqaid import Data.Version import Data.List ( intercalate ) leaky_version = (intercalate "." $ map show $ take 3 $ versionBranch version) ++ ".0" --leaky_version = "0.1.6.0" -- XXX need a better way!!.... main :: IO ExitCode main = do -- putStrLn $ leaky_version -- error "DEVEXIT" args <- getArgs if args /= ["demo"] then do putStrLn "seqaid: \"seqaid demo\" is the only supported invocation at this time." return $ ExitFailure 1 else do tdir <- T.createTempDirectory "." "leaky_" -- XXX Note that "cabal get" already extracts the tarball for you. -- XXX Note mingw32 still uses bash. let dos_str = concat [ "@echo off\n" , "cabal get leaky-" ++ leaky_version ++ "\n" , "cd leaky-" ++ leaky_version ++ "\n" , "cabal configure\n" , "cabal build\n" , "cabal run 234\n" , "echo.\n" , "echo \"(Please see " ++ tdir ++ "/leaky-" ++ leaky_version ++ "/README for the interpretation.)\"\n" , "echo.\n" ] let nix_str = concat [ "#!/bin/bash\nset -e\n" ++ "" , "cabal get leaky-" ++ leaky_version ++ "\n" , "cd leaky-" ++ leaky_version ++ "\n" , "cabal configure\n" , "cabal build\n" , "cabal run 234\n" , "echo\n" , "echo \"(Please see " ++ tdir ++ "/leaky-" ++ leaky_version ++ "/README for the interpretation.)\"\n" , "echo\n" ] #ifdef mingw32_HOST_OS let seqaid_init_bash = nix_str #else #if IS_WINDOWS let seqaid_init_bash = dos_str #else let seqaid_init_bash = nix_str #endif #endif D.setCurrentDirectory tdir writeFile "seqaidinit.sh" seqaid_init_bash p <- D.getPermissions "seqaidinit.sh" D.setPermissions "seqaidinit.sh" (p { D.executable = True }) st <- system "./seqaidinit.sh" case st of ExitSuccess -> return ExitSuccess ExitFailure n -> do putStrLn $ "Sorry, seqaid demo had a problem (status=" ++ show st ++ ").\nPlease report this bug to rasfar@gmail.com" return $ ExitFailure 2 _ -> error $ "unexpected ExitCode = " ++ show st ++ "\nPlease report this bug to rasfar@gmail.com"