|
|
@ -5,6 +5,7 @@ |
|
|
|
module Mainf where |
|
|
|
|
|
|
|
import Data.Int |
|
|
|
import Data.List |
|
|
|
import qualified Data.ByteString.Lazy.Char8 as BS |
|
|
|
import System.Environment |
|
|
|
import System.Random |
|
|
@ -18,11 +19,13 @@ import Datatypes |
|
|
|
import Datatypes.Game |
|
|
|
import VM |
|
|
|
import Opt |
|
|
|
import JSONDeser(Input(..),readInput) |
|
|
|
import JSONDeser(readInput) |
|
|
|
import PowerPhrases |
|
|
|
|
|
|
|
ptag :: String |
|
|
|
ptag = "lilik0" |
|
|
|
logfilename :: String |
|
|
|
logfilename = "scores" |
|
|
|
|
|
|
|
timelimitratio :: Double |
|
|
|
timelimitratio = 0.9 |
|
|
@ -61,6 +64,7 @@ main = do args <- getArgs |
|
|
|
let memlimit = optMem opt |
|
|
|
let powerp = optPowerPhrase opt |
|
|
|
let cores = optCores opt |
|
|
|
let logf = optLog opt |
|
|
|
rng <- getStdGen |
|
|
|
loaddata <- createComputationsFromFiles files rng powerp |
|
|
|
let (ids,seeds,gamecomputations) = unzip3 loaddata |
|
|
@ -71,6 +75,7 @@ main = do args <- getArgs |
|
|
|
let wordlists = map cmdToString commandlists |
|
|
|
let outJSONstructs = zipWith3 (\x y z -> (JSONSer x y ptag z)) ids seeds wordlists |
|
|
|
BS.putStrLn $ encode outJSONstructs |
|
|
|
writelogfile logf (zip4 ids seeds points strat) |
|
|
|
where |
|
|
|
timestruct Nothing _ = Nothing |
|
|
|
timestruct (Just maxtime) intime = Just (maxtime, intime) |
|
|
@ -125,3 +130,15 @@ memLimit _ = return False |
|
|
|
secTime :: IO Int64 |
|
|
|
secTime = do (TimeSpec s _) <- getTime Monotonic |
|
|
|
return s |
|
|
|
|
|
|
|
writelogfile :: Bool -> [(Int,Int,Int,Int)] -> IO () |
|
|
|
writelogfile False _ = return () |
|
|
|
writelogfile _ els = writeFile logfilename scoredata |
|
|
|
where |
|
|
|
scoredata = foldl strlog "\n" els |
|
|
|
strlog x (a,b,c,d) = sa ++ sb ++ sc ++ sd ++ x ++ "\n" |
|
|
|
where |
|
|
|
sa = (show a) ++ " " |
|
|
|
sb = (show b) ++ " " |
|
|
|
sc = (show c) ++ " " |
|
|
|
sd = (show d) ++ " " |