Browse Source

Text.JSON.Generic deleted

adaptedStrategy0
Andrea Bellandi 9 years ago
parent
commit
687d6054fe
2 changed files with 24 additions and 16 deletions
  1. +12
    -6
      src/Main0.hs
  2. +12
    -10
      src/ReadString.hs

+ 12
- 6
src/Main0.hs View File

@ -1,10 +1,13 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Main where module Main where
import GHC.Generics
import Data.Aeson
import Data.Aeson.Types
import System.Environment import System.Environment
import qualified Data.ByteString.Lazy as BS import qualified Data.ByteString.Lazy as BS
import System.IO
import Text.JSON.Generic
import System.IO
import Datatypes import Datatypes
import Opt import Opt
import JSONDeser import JSONDeser
@ -15,7 +18,10 @@ data JSONSer = JSONSer { problemId :: Int,
seed :: Int, seed :: Int,
tag :: String, tag :: String,
solution :: String solution :: String
} deriving (Show, Data, Typeable)
} deriving (Show, Generic)
instance FromJSON JSONSer
instance ToJSON JSONSer
main :: IO () main :: IO ()
main = do args <- getArgs main = do args <- getArgs
@ -26,7 +32,7 @@ main = do args <- getArgs
commandspoints <- return (map (\(seed,game) -> strat0 game) gmseed) commandspoints <- return (map (\(seed,game) -> strat0 game) gmseed)
(commands,points) <- return $ unzip commandspoints (commands,points) <- return $ unzip commandspoints
seeds <- return ((map (\(seed, _) -> seed)) gmseed) seeds <- return ((map (\(seed, _) -> seed)) gmseed)
putStrLn . encodeJSON $ (packAll id seeds commands)
putStrLn $ show $ encode $ (packAll id seeds commands)
writeFile ("scores") (scoredata id (fst $ unzip gmseed) points) writeFile ("scores") (scoredata id (fst $ unzip gmseed) points)
@ -38,7 +44,7 @@ packAll id seeds commandLists = zipWith (\x y -> JSONSer id x "lilik0" y) seeds
scoredata :: Int -> [Int] -> [Int] -> String scoredata :: Int -> [Int] -> [Int] -> String
scoredata id seeds points = pretty scoredata id seeds points = pretty
where where
pretty = foldl (\x (a,b,c) -> (show a) ++ " " ++ (show b) ++ " " ++ (show c) ++ "\n" ++ x) "" zipdata
pretty = foldl (\x (a,b,c) -> (show a) ++ " " ++ (show b) ++ (show c) ++ "\n" ++ x) "" zipdata
zipdata = zip3 ids seeds points zipdata = zip3 ids seeds points
ids = replicate (length seeds) id ids = replicate (length seeds) id

+ 12
- 10
src/ReadString.hs View File

@ -1,32 +1,34 @@
{-# LANGUAGE DeriveGeneric #-}
module Main where module Main where
import GHC.Generics
import Data.Aeson
import Data.Aeson.Types
import System.Environment import System.Environment
import qualified Data.ByteString.Lazy as BS import qualified Data.ByteString.Lazy as BS
import System.IO
import Text.JSON.Generic
import System.IO
import Datatypes import Datatypes
import Opt import Opt
import JSONDeser import JSONDeser
import Strategy0
import VM (Command, cmdToString)
data JSONSer = JSONSer { problemId :: Int, data JSONSer = JSONSer { problemId :: Int,
seed :: Int, seed :: Int,
tag :: String, tag :: String,
solution :: String solution :: String
} deriving (Show, Data, Typeable)
} deriving (Show, Generic)
instance FromJSON JSONSer
instance ToJSON JSONSer
main :: IO () main :: IO ()
main = do args <- getArgs main = do args <- getArgs
opt <- parseArgs args opt <- parseArgs args
file <- return ((optFile opt) !! 0) file <- return ((optFile opt) !! 0)
str <- BS.readFile file str <- BS.readFile file
(id, gmseed) <- return (readInput str)
commands <- return (map (\(seed,game) -> strat0 game) gmseed)
seeds <- return ((map (\(seed, _) -> seed)) gmseed)
putStrLn . encodeJSON $ (packAll id seeds commands)
packAll :: Int -> [Int] -> [[Command]] -> [JSONSer] packAll :: Int -> [Int] -> [[Command]] -> [JSONSer]
packAll id seeds commandLists = zipWith (\x y -> JSONSer id x "lilik0" y) seeds commandStrings packAll id seeds commandLists = zipWith (\x y -> JSONSer id x "lilik0" y) seeds commandStrings
where where


Loading…
Cancel
Save