Browse Source

finished Mainfp

adaptedStrategy0
Andrea Bellandi 9 years ago
parent
commit
33924f5ef8
2 changed files with 27 additions and 4 deletions
  1. +18
    -1
      src/Mainpf.hs
  2. +9
    -3
      src/Opt.hs

+ 18
- 1
src/Mainpf.hs View File

@ -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) ++ " "

+ 9
- 3
src/Opt.hs View File

@ -16,7 +16,8 @@ data Options = Options { optFile :: [String],
optMem :: Maybe Int,
optPowerPhrase :: Maybe String,
optSeedNumber :: Int,
optCores :: Int
optCores :: Int,
optLog :: Bool
}
deriving Show
@ -25,7 +26,8 @@ startOptions = Options { optFile = [],
optMem = Nothing,
optPowerPhrase = Nothing,
optSeedNumber = 0,
optCores = 1
optCores = 1,
optLog = True
}
options :: [ OptDescr (Options -> IO Options) ]
@ -59,7 +61,11 @@ options = [ Option "f" ["filename"]
(\arg opt -> return opt { optCores = (read arg) })
"CORES")
"Cores"
]
, Option "l" ["log"]
(NoArg
(\ opt -> return opt { optLog = True }))
"Log"
]
parseArgs :: [String] -> IO Options
parseArgs args = do


Loading…
Cancel
Save