+{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE QuasiQuotes #-}
import Database.Groundhog.TH (
groundhog,
mkPersist )
+import qualified GHC.Generics as GHC ( Generic )
import Test.Tasty ( TestTree, testGroup )
import Test.Tasty.HUnit ( (@?=), testCase )
import Text.XML.HXT.Core (
xpWrap )
-- Local imports.
+import Generics ( Generic(..), to_tuple )
import TSN.Codegen ( tsn_codegen_config )
import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate )
import TSN.Picklers( xp_date, xp_time_stamp )
xml_sport :: String,
xml_listings :: [InjuriesDetailListingXml],
xml_time_stamp :: UTCTime }
- deriving (Eq, Show)
+ deriving (Eq, GHC.Generic, Show)
+
+
+-- | For 'Generics.to_tuple'.
+--
+instance Generic Message
+
-- | Database representation of a 'Message'.
--
xml_full_name :: String, -- ^ Team full name
xml_player_listings :: [InjuriesDetailListingPlayerListingXml] }
- deriving (Eq, Show)
+ deriving (Eq, GHC.Generic, Show)
+
+
+-- | For 'Generics.to_tuple'.
+--
+instance Generic InjuriesDetailListingXml
+
instance ToDb InjuriesDetailListingXml where
-- | The database analogue of an 'InjuriesDetailListingXml' is a
xml_fantasy :: Maybe String, -- ^ Nobody knows what this is.
xml_injured :: Bool,
xml_type :: String }
- deriving (Eq, Show)
+ deriving (Eq, GHC.Generic, Show)
+
+-- | For 'Generics.to_tuple'.
+--
+instance Generic InjuriesDetailListingPlayerListingXml
-- | Database representation of a
(xpElem "Type" xpText)
where
from_tuple = uncurryN InjuriesDetailListingPlayerListingXml
- to_tuple pl = (xml_player_team_id pl,
- xml_player_id pl,
- xml_date pl,
- xml_pos pl,
- xml_name pl,
- xml_injury pl,
- xml_status pl,
- xml_fantasy pl,
- xml_injured pl,
- xml_type pl)
-- | Convert 'Listing's to/from XML.
(xpList pickle_player_listing)
where
from_tuple = uncurryN InjuriesDetailListingXml
- to_tuple l = (xml_team_id l,
- xml_full_name l,
- xml_player_listings l)
-- | Convert 'Message's to/from XML.
(xpElem "time_stamp" xp_time_stamp)
where
from_tuple = uncurryN Message
- to_tuple m = (xml_xml_file_id m,
- xml_heading m,
- xml_category m,
- xml_sport m,
- xml_listings m,
- xml_time_stamp m)
--