Browse Source

deepseq awesomeness

adaptedStrategy0
Slash 9 years ago
parent
commit
26b59c0a9a
1 changed files with 31 additions and 23 deletions
  1. +31
    -23
      src/Main.hs

+ 31
- 23
src/Main.hs View File

@ -5,8 +5,9 @@
module Main where module Main where
import Control.DeepSeq (deepseq, NFData(..))
import Data.Int import Data.Int
import Data.List
import Data.List (zip4)
import qualified Data.ByteString.Lazy.Char8 as BS import qualified Data.ByteString.Lazy.Char8 as BS
import System.Environment import System.Environment
import System.Random import System.Random
@ -24,15 +25,20 @@ import Opt
import JSONDeser(readInput) import JSONDeser(readInput)
import PowerPhrases import PowerPhrases
ptag :: String
ptag = "lilik0"
logfilename :: String
logfilename = "scores"
import Debug.Trace (trace)
strategyTag :: String
strategyTag = "lilik0"
logFileName :: String
logFileName = "scores"
timeLimitRatio :: Double
timeLimitRatio = 1.0
memLimitRatio :: Double
memLimitRatio = 1.0
timelimitratio :: Double
timelimitratio = 1.0
memlimitratio :: Double
memlimitratio = 1.0
gccompperstep :: Integer gccompperstep :: Integer
gccompperstep = 100 gccompperstep = 100
@ -78,7 +84,7 @@ main = do args <- getArgs
let (commandswpoints,strat) = unzip results let (commandswpoints,strat) = unzip results
let (commandlists, points) = unzip commandswpoints let (commandlists, points) = unzip commandswpoints
let wordlists = map cmdToString commandlists let wordlists = map cmdToString commandlists
let outJSONstructs = zipWith3 (\x y z -> (JSONSer x y ptag z)) ids seeds wordlists
let outJSONstructs = zipWith3 (\x y z -> (JSONSer x y strategyTag z)) ids seeds wordlists
BS.putStrLn $ encode outJSONstructs BS.putStrLn $ encode outJSONstructs
writelogfile logf (zip4 ids seeds points strat) writelogfile logf (zip4 ids seeds points strat)
where where
@ -105,27 +111,29 @@ readFiles (x:xs) = do f <- BS.readFile x
fs <- readFiles xs fs <- readFiles xs
return (f:fs) return (f:fs)
instance NFData Command where rnf x = seq x ()
iterategc :: [GameComputation] -> Maybe (Int,Int64) -> Maybe Int -> IO [(([Command], Int), Int)] iterategc :: [GameComputation] -> Maybe (Int,Int64) -> Maybe Int -> IO [(([Command], Int), Int)]
iterategc gcs tlimit mlimit = do rtl <- timeLimit tlimit iterategc gcs tlimit mlimit = do rtl <- timeLimit tlimit
rml <- memLimit mlimit rml <- memLimit mlimit
(gcresult rtl rml)
if rtl || rml
then return best
else if (and $ map finishedGameComputation gcs)
then return best
else let mona = (applyNtimes gccompperstep itf gcs)
mona1 = map getBestGameComputation gcs
in mona1 `deepseq` (iterategc mona tlimit mlimit)
where where
gcresult True _ = return best
gcresult _ True = return best
gcresult _ _ = if (and $ map finishedGameComputation gcs)
then return best
else iterategc (applyNtimes gccompperstep itf gcs) tlimit mlimit
where
itf gcs1 = map advanceGameComputation gcs1
applyNtimes 0 _ accum = accum
applyNtimes n f accum = applyNtimes (n - 1) f (f accum)
best = map getBestGameComputation gcs
itf gcs1 = map advanceGameComputation gcs1
applyNtimes 0 _ accum = accum
applyNtimes n f accum = applyNtimes (n - 1) f (f accum)
best = map getBestGameComputation gcs
timeLimit :: Maybe (Int,Int64) -> IO Bool timeLimit :: Maybe (Int,Int64) -> IO Bool
timeLimit Nothing = return False timeLimit Nothing = return False
timeLimit (Just (itime,limit)) = do atime <- secTime timeLimit (Just (itime,limit)) = do atime <- secTime
let diff = (atime - (fromIntegral itime)) let diff = (atime - (fromIntegral itime))
return (((fromIntegral limit) * timelimitratio) < (fromIntegral diff))
return (((fromIntegral limit) * timeLimitRatio) < (fromIntegral diff))
memLimit :: Maybe Int -> IO Bool memLimit :: Maybe Int -> IO Bool
@ -137,7 +145,7 @@ secTime = do (TimeSpec s _) <- getTime Monotonic
writelogfile :: Bool -> [(Int,Int,Int,Int)] -> IO () writelogfile :: Bool -> [(Int,Int,Int,Int)] -> IO ()
writelogfile False _ = return () writelogfile False _ = return ()
writelogfile _ els = writeFile logfilename scoredata
writelogfile _ els = writeFile logFileName scoredata
where where
scoredata = foldl strlog "\n" els scoredata = foldl strlog "\n" els
strlog x (a,b,c,d) = sa ++ sb ++ sc ++ sd ++ x ++ "\n" strlog x (a,b,c,d) = sa ++ sb ++ sc ++ sd ++ x ++ "\n"


Loading…
Cancel
Save