X-Git-Url: http://gitweb.michael.orlitzky.com/?a=blobdiff_plain;f=src%2FTSN%2FXML%2FOdds.hs;h=509b436d05760022d636e42a51a53e3249920087;hb=1f260c118e8da5679820c8cfa489d8fe4a521140;hp=7143c459a4d9fbba182d9ef877c259d6ace59e45;hpb=6883632cfac0e3ee7ad6781300555dbf40d98b40;p=dead%2Fhtsn-import.git diff --git a/src/TSN/XML/Odds.hs b/src/TSN/XML/Odds.hs index 7143c45..509b436 100644 --- a/src/TSN/XML/Odds.hs +++ b/src/TSN/XML/Odds.hs @@ -1,293 +1,649 @@ -{-# LANGUAGE BangPatterns #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} -module TSN.XML.Odds ( - Message, - odds_tests ) -where - - -- | Parse TSN XML for the DTD "Odds_XML.dtd". Each document contains -- a root element \ that contains a bunch of other -- unorganized crap. -- +module TSN.XML.Odds ( + pickle_message, + -- * Tests + odds_tests, + -- * WARNING: these are private but exported to silence warnings + Odds_OddsGameConstructor(..), + OddsCasinoConstructor(..), + OddsConstructor(..), + OddsGame_OddsGameTeamConstructor(..), + OddsGameConstructor(..), + OddsGameLineConstructor(..), + OddsGameTeamConstructor(..) ) +where -import Data.Data ( Data, constrFields, dataTypeConstrs, dataTypeOf ) -import Data.List.Utils ( join, split ) +-- System imports. +import Control.Monad ( forM_, join ) +import Data.Time ( UTCTime ) import Data.Tuple.Curry ( uncurryN ) -import Data.Typeable ( Typeable ) import Database.Groundhog ( - defaultMigrationLogger, - insert, + (=.), + (==.), + insert_, + insertByAll, migrate, - runMigration ) + update ) import Database.Groundhog.Core ( DefaultKey ) import Database.Groundhog.TH ( groundhog, mkPersist ) -import System.Console.CmdArgs.Default ( Default(..) ) import Test.Tasty ( TestTree, testGroup ) import Test.Tasty.HUnit ( (@?=), testCase ) +import Text.Read ( readMaybe ) import Text.XML.HXT.Core ( PU, - XmlPickler(..), - unpickleDoc, xp5Tuple, xp6Tuple, - xp11Tuple, + xp8Tuple, xpAttr, xpElem, xpInt, xpList, xpOption, xpPair, - xpPrim, xpText, - xpText0, xpTriple, xpWrap ) +-- Local imports. import TSN.Codegen ( - tsn_codegen_config, - tsn_db_field_namer ) -import TSN.DbImport ( DbImport(..), ImportResult(..) ) -import Xml ( ToFromXml(..), pickle_unpickle, unpickleable ) + tsn_codegen_config ) +import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate ) +import TSN.Picklers ( xp_date, xp_team_id, xp_time ) +import TSN.XmlImport ( XmlImport(..) ) +import Xml ( FromXml(..), pickle_unpickle, unpickleable ) -data OddsCasino = - OddsCasino { +-- | The home/away lines are 'Double's, but the over/under lines are +-- textual. If we want to use one data type for both, we have to go +-- with a 'String' and then attempt to 'read' a 'Double' later when we +-- go to insert the thing. +-- +data OddsGameCasinoXml = + OddsGameCasinoXml { xml_casino_client_id :: Int, xml_casino_name :: String, - xml_casino_line :: Maybe Float } + xml_casino_line :: Maybe String } + deriving (Eq, Show) + + +-- | Try to get a 'Double' out of the 'xml_casino_line' which is a +-- priori textual (because it might be an over/under line). +-- +home_away_line :: OddsGameCasinoXml -> Maybe Double +home_away_line = join . (fmap readMaybe) . xml_casino_line + + +-- | The casinos should have their own table, but the lines don't +-- belong in that table (there should be another table joining the +-- casinos and the thing the lines are for together.) +-- +-- We drop the 'Game' prefix because the Casinos really aren't +-- children of the games; the XML just makes it seem that way. +-- +data OddsCasino = + OddsCasino { + casino_client_id :: Int, + casino_name :: String } + deriving (Eq, Show) + + +instance FromXml OddsGameCasinoXml where + -- | The database representation of an 'OddsGameCasinoXml' is an + -- 'OddsCasino'. + -- + type Db OddsGameCasinoXml = OddsCasino + + -- | We convert from XML to the database by dropping the line field. + from_xml OddsGameCasinoXml{..} = + OddsCasino { + casino_client_id = xml_casino_client_id, + casino_name = xml_casino_name } + +-- | This allows us to call 'insert_xml' on an 'OddsGameCasinoXml' +-- without first converting it to the database representation. +instance XmlImport OddsGameCasinoXml + + +-- | The database representation of teams as they appear in odds +-- games. +-- +data OddsGameTeam = + OddsGameTeam { + db_team_id :: String, -- ^ The home/away team IDs are 3 characters + db_abbr :: String, + db_team_name :: String } deriving (Eq, Show) -data OddsHomeTeam = - OddsHomeTeam { - xml_home_team_id :: Int, + +-- | The XML representation of a \, as found in \s. +-- +data OddsGameHomeTeamXml = + OddsGameHomeTeamXml { + xml_home_team_id :: String, -- ^ These are three-character IDs. xml_home_rotation_number :: Int, xml_home_abbr :: String, xml_home_team_name :: String, - xml_home_casinos :: [OddsCasino] } + xml_home_casinos :: [OddsGameCasinoXml] } deriving (Eq, Show) -data OddsAwayTeam = - OddsAwayTeam { - xml_away_team_id :: Int, +instance FromXml OddsGameHomeTeamXml where + -- | The database representation of an 'OddsGameHomeTeamXml' is an + -- 'OddsGameTeam'. + -- + type Db OddsGameHomeTeamXml = OddsGameTeam + + -- | We convert from XML to the database by dropping the lines and + -- rotation number (which are specific to the games, not the teams + -- themselves). + -- + from_xml OddsGameHomeTeamXml{..} = + OddsGameTeam { + db_team_id = xml_home_team_id, + db_abbr = xml_home_abbr, + db_team_name = xml_home_team_name } + +-- | XmlImport allows us to call 'insert_xml' directly on an +-- 'OddsGameHomeTeamXml' without explicitly converting it to the +-- associated database type. +-- +instance XmlImport OddsGameHomeTeamXml where + + +-- | -- | The XML representation of a \, as found in \s. +-- +data OddsGameAwayTeamXml = + OddsGameAwayTeamXml { + xml_away_team_id :: String, -- ^ These are 3 character IDs. xml_away_rotation_number :: Int, xml_away_abbr :: String, xml_away_team_name :: String, - xml_away_casinos :: [OddsCasino] } + xml_away_casinos :: [OddsGameCasinoXml] } deriving (Eq, Show) --- | Can't use a newtype with Groundhog. -data OddsOverUnder = - OddsOverUnder [OddsCasino] +instance FromXml OddsGameAwayTeamXml where + -- | The database representation of an 'OddsGameAwayTeamXml' is an + -- 'OddsGameTeam'. + -- + type Db OddsGameAwayTeamXml = OddsGameTeam + + -- | We convert from XML to the database by dropping the lines and + -- rotation number (which are specific to the games, not the teams + -- themselves). + -- + from_xml OddsGameAwayTeamXml{..} = OddsGameTeam + xml_away_team_id + xml_away_abbr + xml_away_team_name + +-- | XmlImport allows us to call 'insert_xml' directly on an +-- 'OddsGameAwayTeamXml' without explicitly converting it to the +-- associated database type. +-- +instance XmlImport OddsGameAwayTeamXml where + + +-- | Database mapping between games and their home/away teams. +data OddsGame_OddsGameTeam = + OddsGame_OddsGameTeam { + ogogt_odds_games_id :: DefaultKey OddsGame, + ogogt_away_team_id :: DefaultKey OddsGameTeam, + ogogt_home_team_id :: DefaultKey OddsGameTeam } + + +-- | XML representation of the over/under. A wrapper around a bunch of +-- casino elements. +-- +newtype OddsGameOverUnderXml = + OddsGameOverUnderXml { xml_casinos :: [OddsGameCasinoXml] } deriving (Eq, Show) + +-- | This database representation of the casino lines can't be +-- constructed from the one in the XML. The casinos within +-- Game>HomeTeam, Game>AwayTeam, and Game>Over_Under are all more or +-- less the same. We don't need a bajillion different tables to +-- store that, just one tying the casino/game pair to the three +-- lines. +-- +-- The one small difference between the over/under casinos and the +-- home/away ones is that the home/away lines are all 'Double's, but +-- the over/under lines appear to be textual. +-- +data OddsGameLine = + OddsGameLine { + ogl_odds_games_id :: DefaultKey OddsGame, + ogl_odds_casinos_id :: DefaultKey OddsCasino, + ogl_over_under :: Maybe String, + ogl_away_line :: Maybe Double, + ogl_home_line :: Maybe Double } + + +-- | Database representation of a game. We retain the rotation number +-- of the home/away teams, since those are specific to the game and +-- not the teams. +-- data OddsGame = OddsGame { + db_game_id :: Int, + db_game_date :: UTCTime, + db_game_time :: UTCTime, + db_game_away_team_rotation_number :: Int, + db_game_home_team_rotation_number :: Int } + deriving (Eq, Show) + +-- | XML representation of a game. +-- +data OddsGameXml = + OddsGameXml { xml_game_id :: Int, - xml_game_date :: String, -- TODO - xml_game_time :: String, -- TODO - xml_game_away_team :: OddsAwayTeam, - xml_game_home_team :: OddsHomeTeam, - xml_game_over_under :: OddsOverUnder } + xml_game_date :: UTCTime, + xml_game_time :: UTCTime, + xml_game_away_team :: OddsGameAwayTeamXml, + xml_game_home_team :: OddsGameHomeTeamXml, + xml_game_over_under :: OddsGameOverUnderXml } deriving (Eq, Show) -data Message = - Message { +-- | Pseudo-field that lets us get the 'OddsGameCasinoXml's out of +-- xml_game_over_under. +-- +xml_game_over_under_casinos :: OddsGameXml -> [OddsGameCasinoXml] +xml_game_over_under_casinos = xml_casinos . xml_game_over_under + + +instance FromXml OddsGameXml where + -- | The database representation of an 'OddsGameXml' is an + -- 'OddsGame'. + -- + type Db OddsGameXml = OddsGame + + -- | To convert from the XML representation to the database one, we + -- drop the home/away teams and the casino lines, but retain the + -- home/away rotation numbers. + -- + from_xml OddsGameXml{..} = + OddsGame { + db_game_id = xml_game_id, + db_game_date = xml_game_date, + db_game_time = xml_game_time, + db_game_away_team_rotation_number = + (xml_away_rotation_number xml_game_away_team), + db_game_home_team_rotation_number = + (xml_home_rotation_number xml_game_home_team) } + +-- | This lets us call 'insert_xml' directly on an 'OddsGameXml' +-- without converting it to the database representation explicitly. +-- +instance XmlImport OddsGameXml + + +-- | Database and representation of the top-level Odds object (a +-- 'Message'). +data Odds = + Odds { db_sport :: String, db_title :: String, - db_line_time :: String, - db_notes1 :: String, - db_notes2 :: String } + db_line_time :: String } + -data MessageXml = - MessageXml { +-- | Map 'Odds' to their children 'OddsGame's. +-- +data Odds_OddsGame = Odds_OddsGame + (DefaultKey Odds) + (DefaultKey OddsGame) + + +-- | This is our best guess at what occurs in the Odds_XML +-- documents. It looks like each consecutive set of games can +-- optionally have some notes appear before it. Each "note" comes as +-- its own ... element. +-- +-- The notes are ignored completely in the database; we only bother +-- with them to ensure that we're (un)pickling correctly. +-- +-- We can't group the notes with a "set" of 'OddsGame's, because that +-- leads to ambiguity in parsing. Since we're going to ignore the +-- notes anyway, we just stick them with an arbitrary game. C'est la +-- vie. +-- +data OddsGameWithNotes = + OddsGameWithNotes { + notes :: [String], + game :: OddsGameXml } + deriving (Eq, Show) + +-- | The XML representation of 'Odds'. +data Message = + Message { xml_xml_file_id :: Int, xml_heading :: String, xml_category :: String, xml_sport :: String, xml_title :: String, - xml_line_time :: String, -- The DTD goes crazy here. - xml_notes1 :: String, - xml_games1 :: [OddsGame], - xml_notes2 :: String, - xml_games2 :: [OddsGame], + xml_line_time :: String, + xml_games_with_notes :: [OddsGameWithNotes], xml_time_stamp :: String } deriving (Eq, Show) +-- | Pseudo-field that lets us get the 'OddsGame's out of +-- 'xml_games_with_notes'. +-- +xml_games :: Message -> [OddsGameXml] +xml_games m = map game (xml_games_with_notes m) + + +instance FromXml Message where + -- | The database representation of a 'Message' is 'Odds'. + -- + type Db Message = Odds + + -- | To convert from the XML representation to the database one, we + -- just drop a bunch of fields. + -- + from_xml Message{..} = + Odds { + db_sport = xml_sport, + db_title = xml_title, + db_line_time = xml_line_time } + +-- | This lets us call 'insert_xml' on a Message directly, without +-- having to convert it to its database representation explicitly. +-- +instance XmlImport Message -instance ToFromXml Message where - type Xml Message = MessageXml - type Container Message = () - - -- Use a record wildcard here so GHC doesn't complain that we never - -- used our named fields. - to_xml (Message {..}) = - MessageXml - def - def - def - db_sport - db_title - db_line_time - db_notes1 - def - db_notes2 - def - def - - -- We don't need the key argument (from_xml_fk) since the XML type - -- contains more information in this case. - from_xml (MessageXml _ _ _ d e f g _ i _ _) = - Message d e f g i - - -pickle_casino :: PU OddsCasino + + +-- | Groundhog database schema. This must come before the DbImport +-- instance definition. +-- +mkPersist tsn_codegen_config [groundhog| +- entity: Odds + +- entity: OddsCasino + dbName: odds_casinos + constructors: + - name: OddsCasino + uniques: + - name: unique_odds_casino + type: constraint + fields: [casino_client_id] + +- entity: OddsGameTeam + dbName: odds_games_teams + constructors: + - name: OddsGameTeam + fields: + - name: db_team_id + type: varchar(3) # We've only seen 3, so far... + uniques: + - name: unique_odds_games_team + type: constraint + fields: [db_team_id] + + +- entity: OddsGame + dbName: odds_games + constructors: + - name: OddsGame + uniques: + - name: unique_odds_game + type: constraint + fields: [db_game_id] + +- entity: OddsGameLine + dbName: odds_games_lines + +- entity: Odds_OddsGame + dbName: odds__odds_games + constructors: + - name: Odds_OddsGame + fields: + - name: odds_OddsGame0 # Default created by mkNormalFieldName + dbName: odds_id + - name: odds_OddsGame1 # Default created by mkNormalFieldName + dbName: odds_games_id + +- entity: OddsGame_OddsGameTeam + dbName: odds_games__odds_games_teams +|] + +instance DbImport Message where + dbmigrate _= + run_dbmigrate $ do + migrate (undefined :: Odds) + migrate (undefined :: OddsCasino) + migrate (undefined :: OddsGameTeam) + migrate (undefined :: OddsGame) + migrate (undefined :: Odds_OddsGame) + migrate (undefined :: OddsGame_OddsGameTeam) + migrate (undefined :: OddsGameLine) + + dbimport m = do + -- Insert the root "odds" element and acquire its primary key (id). + odds_id <- insert_xml m + + -- Next, we insert the home and away teams. We do this before + -- inserting the game itself because the game has two foreign keys + -- pointing to odds_games_teams. + forM_ (xml_games m) $ \g -> do + game_id <- insert_xml_or_select g + -- Insert a record into odds__odds_game mapping this game + -- to its parent in the odds table. + insert_ (Odds_OddsGame odds_id game_id) + + -- Next to insert the home and away teams. + away_team_id <- insert_xml_or_select (xml_game_away_team g) + home_team_id <- insert_xml_or_select (xml_game_home_team g) + + -- Insert a record into odds_games__odds_games_teams mapping the + -- home/away teams to this game. Use the full record syntax + -- because the types would let us mix up the home/away teams. + insert_ OddsGame_OddsGameTeam { + ogogt_odds_games_id = game_id, + ogogt_away_team_id = away_team_id, + ogogt_home_team_id = home_team_id } + + -- Finaly, we insert the lines. The over/under entries for this + -- game and the lines for the casinos all wind up in the same + -- table, odds_games_lines. We can insert the over/under entries + -- freely with empty away/home lines: + forM_ (xml_game_over_under_casinos g) $ \c -> do + -- Start by inderting the casino. + ou_casino_id <- insert_xml_or_select c + + -- Now add the over/under entry with the casino's id. + let ogl = OddsGameLine { + ogl_odds_games_id = game_id, + ogl_odds_casinos_id = ou_casino_id, + ogl_over_under = (xml_casino_line c), + ogl_away_line = Nothing, + ogl_home_line = Nothing } + + insertByAll ogl + + -- ...but then when we insert the home/away team lines, we + -- prefer to update the existing entry rather than overwrite it + -- or add a new record. + forM_ (xml_away_casinos $ xml_game_away_team g) $ \c ->do + -- insert, or more likely retrieve the existing, casino + a_casino_id <- insert_xml_or_select c + + -- Get a Maybe Double instead of the Maybe String that's in there. + let away_line = home_away_line c + + -- Unconditionally update that casino's away team line with ours. + update [Ogl_Away_Line =. away_line] $ -- WHERE + Ogl_Odds_Casinos_Id ==. a_casino_id + + -- Repeat all that for the home team. + forM_ (xml_home_casinos $ xml_game_home_team g) $ \c ->do + h_casino_id <- insert_xml_or_select c + let home_line = home_away_line c + update [Ogl_Home_Line =. home_line] $ -- WHERE + Ogl_Odds_Casinos_Id ==. h_casino_id + + return game_id + + return ImportSucceeded + +-- | Pickler for an 'OddsGame' optionally preceded by some notes. +-- +pickle_game_with_notes :: PU OddsGameWithNotes +pickle_game_with_notes = + xpWrap (from_pair, to_pair) $ + xpPair + (xpList $ xpElem "Notes" xpText) + pickle_game + where + from_pair = uncurry OddsGameWithNotes + to_pair OddsGameWithNotes{..} = (notes, game) + + +-- | Pickler for an 'OddsGameCasinoXml'. +-- +pickle_casino :: PU OddsGameCasinoXml pickle_casino = xpElem "Casino" $ xpWrap (from_tuple, to_tuple) $ xpTriple (xpAttr "ClientID" xpInt) (xpAttr "Name" xpText) - (xpOption xpPrim) + (xpOption xpText) where - from_tuple = uncurryN OddsCasino - to_tuple (OddsCasino x y z) = (x, y, z) - -instance XmlPickler OddsCasino where - xpickle = pickle_casino + from_tuple = uncurryN OddsGameCasinoXml + -- Use record wildcards to avoid unused field warnings. + to_tuple OddsGameCasinoXml{..} = (xml_casino_client_id, + xml_casino_name, + xml_casino_line) -pickle_home_team :: PU OddsHomeTeam +-- | Pickler for an 'OddsGameHomeTeamXml'. +-- +pickle_home_team :: PU OddsGameHomeTeamXml pickle_home_team = xpElem "HomeTeam" $ - xpWrap (from_tuple, to_tuple) $ - xp5Tuple - (xpElem "HomeTeamID" xpPrim) - (xpElem "HomeRotationNumber" xpPrim) - (xpElem "HomeAbbr" xpText) - (xpElem "HomeTeamName" xpText) - (xpList pickle_casino) + xpWrap (from_tuple, to_tuple) $ + xp5Tuple + (xpElem "HomeTeamID" xp_team_id) + (xpElem "HomeRotationNumber" xpInt) + (xpElem "HomeAbbr" xpText) + (xpElem "HomeTeamName" xpText) + (xpList pickle_casino) where - from_tuple = uncurryN OddsHomeTeam - to_tuple (OddsHomeTeam v w x y z) = (v, w, x, y, z) - + from_tuple = uncurryN OddsGameHomeTeamXml + -- Use record wildcards to avoid unused field warnings. + to_tuple OddsGameHomeTeamXml{..} = (xml_home_team_id, + xml_home_rotation_number, + xml_home_abbr, + xml_home_team_name, + xml_home_casinos) -instance XmlPickler OddsHomeTeam where - xpickle = pickle_home_team - -pickle_away_team :: PU OddsAwayTeam +-- | Pickler for an 'OddsGameAwayTeamXml'. +-- +pickle_away_team :: PU OddsGameAwayTeamXml pickle_away_team = xpElem "AwayTeam" $ - xpWrap (from_tuple, to_tuple) $ - xp5Tuple - (xpElem "AwayTeamID" xpPrim) - (xpElem "AwayRotationNumber" xpPrim) - (xpElem "AwayAbbr" xpText) - (xpElem "AwayTeamName" xpText) - (xpList pickle_casino) + xpWrap (from_tuple, to_tuple) $ + xp5Tuple + (xpElem "AwayTeamID" xp_team_id) + (xpElem "AwayRotationNumber" xpInt) + (xpElem "AwayAbbr" xpText) + (xpElem "AwayTeamName" xpText) + (xpList pickle_casino) where - from_tuple = uncurryN OddsAwayTeam - to_tuple (OddsAwayTeam v w x y z) = (v, w, x, y, z) - + from_tuple = uncurryN OddsGameAwayTeamXml + -- Use record wildcards to avoid unused field warnings. + to_tuple OddsGameAwayTeamXml{..} = (xml_away_team_id, + xml_away_rotation_number, + xml_away_abbr, + xml_away_team_name, + xml_away_casinos) -instance XmlPickler OddsAwayTeam where - xpickle = pickle_away_team -pickle_over_under :: PU OddsOverUnder +-- | Pickler for an 'OddsGameOverUnderXml'. +-- +pickle_over_under :: PU OddsGameOverUnderXml pickle_over_under = xpElem "Over_Under" $ xpWrap (to_newtype, from_newtype) $ xpList pickle_casino where - from_newtype (OddsOverUnder cs) = cs - to_newtype = OddsOverUnder - -instance XmlPickler OddsOverUnder where - xpickle = pickle_over_under + from_newtype (OddsGameOverUnderXml cs) = cs + to_newtype = OddsGameOverUnderXml -pickle_game :: PU OddsGame +-- | Pickler for an 'OddsGameXml'. +-- +pickle_game :: PU OddsGameXml pickle_game = xpElem "Game" $ xpWrap (from_tuple, to_tuple) $ xp6Tuple - (xpElem "GameID" xpPrim) - (xpElem "Game_Date" xpText) - (xpElem "Game_Time" xpText) + (xpElem "GameID" xpInt) + (xpElem "Game_Date" xp_date) + (xpElem "Game_Time" xp_time) pickle_away_team pickle_home_team pickle_over_under where - from_tuple = uncurryN OddsGame - to_tuple (OddsGame u v w x y z) = (u,v,w,x,y,z) - -instance XmlPickler OddsGame where - xpickle = pickle_game + from_tuple = uncurryN OddsGameXml + -- Use record wildcards to avoid unused field warnings. + to_tuple OddsGameXml{..} = (xml_game_id, + xml_game_date, + xml_game_time, + xml_game_away_team, + xml_game_home_team, + xml_game_over_under) -pickle_message :: PU MessageXml +-- | Pickler for the top-level 'Message'. +-- +pickle_message :: PU Message pickle_message = xpElem "message" $ xpWrap (from_tuple, to_tuple) $ - xp11Tuple (xpElem "XML_File_ID" xpPrim) - (xpElem "heading" xpText) - (xpElem "category" xpText) - (xpElem "sport" xpText) - (xpElem "Title" xpText) - (xpElem "Line_Time" xpText) - pickle_notes - (xpList pickle_game) - pickle_notes - (xpList pickle_game) - (xpElem "time_stamp" xpText) + xp8Tuple (xpElem "XML_File_ID" xpInt) + (xpElem "heading" xpText) + (xpElem "category" xpText) + (xpElem "sport" xpText) + (xpElem "Title" xpText) + (xpElem "Line_Time" xpText) + (xpList pickle_game_with_notes) + (xpElem "time_stamp" xpText) where - from_tuple = uncurryN MessageXml + from_tuple = uncurryN Message to_tuple m = (xml_xml_file_id m, xml_heading m, xml_category m, xml_sport m, xml_title m, xml_line_time m, - xml_notes1 m, - xml_games1 m, - xml_notes2 m, - xml_games2 m, + xml_games_with_notes m, xml_time_stamp m) - pickle_notes :: PU String - pickle_notes = - xpWrap (to_string, from_string) $ - xpList (xpElem "Notes" xpText) - where - from_string :: String -> [String] - from_string = split "\n" - - to_string :: [String] -> String - to_string = join "\n" - -instance XmlPickler MessageXml where - xpickle = pickle_message - - - - +-- +-- Tasty Tests +-- --- * Tasty Tests +-- | A list of all tests for this module. +-- odds_tests :: TestTree odds_tests = testGroup @@ -296,20 +652,46 @@ odds_tests = test_unpickle_succeeds ] --- | Warning, succeess of this test does not mean that unpickling --- succeeded. +-- | If we unpickle something and then pickle it, we should wind up +-- with the same thing we started with. WARNING: succeess of this +-- test does not mean that unpickling succeeded. +-- test_pickle_of_unpickle_is_identity :: TestTree -test_pickle_of_unpickle_is_identity = - testCase "pickle composed with unpickle is the identity" $ do - let path = "test/xml/Odds_XML.xml" - (expected :: [MessageXml], actual) <- pickle_unpickle "message" path - actual @?= expected +test_pickle_of_unpickle_is_identity = testGroup "pickle-unpickle tests" + [ check "pickle composed with unpickle is the identity" + "test/xml/Odds_XML.xml", + check "pickle composed with unpickle is the identity (non-int team_id)" + "test/xml/Odds_XML-noninteger-team-id.xml", + + check "pickle composed with unpickle is the identity (positive(+) line)" + "test/xml/Odds_XML-positive-line.xml", + + check "pickle composed with unpickle is the identity (large file)" + "test/xml/Odds_XML-largefile.xml" ] + where + check desc path = testCase desc $ do + (expected, actual) <- pickle_unpickle pickle_message path + actual @?= expected + +-- | Make sure we can actually unpickle these things. +-- test_unpickle_succeeds :: TestTree -test_unpickle_succeeds = - testCase "unpickling succeeds" $ do - let path = "test/xml/Odds_XML.xml" - actual <- unpickleable path pickle_message - let expected = True - actual @?= expected +test_unpickle_succeeds = testGroup "unpickle tests" + [ check "unpickling succeeds" + "test/xml/Odds_XML.xml", + + check "unpickling succeeds (non-int team_id)" + "test/xml/Odds_XML-noninteger-team-id.xml", + + check "unpickling succeeds (positive(+) line)" + "test/xml/Odds_XML-positive-line.xml", + + check "unpickling succeeds (large file)" + "test/xml/Odds_XML-largefile.xml" ] + where + check desc path = testCase desc $ do + actual <- unpickleable path pickle_message + let expected = True + actual @?= expected