]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/TSN/XML/MLBBoxScore.hs
Fix hlint suggestions.
[dead/htsn-import.git] / src / TSN / XML / MLBBoxScore.hs
index b7388991b9ce2b8d5aaa68bdf01be4992fda63ac..67ba23659422439a8d7179dc13acc1ffe576a011 100644 (file)
@@ -1,4 +1,5 @@
 {-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE QuasiQuotes #-}
@@ -16,21 +17,25 @@ module TSN.XML.MLBBoxScore (
   -- * WARNING: these are private but exported to silence warnings
   MLBBoxScore_MLBBoxScoreTeamBreakdownConstructor(..),
   MLBBoxScoreConstructor(..),
-  MLBBoxScoreHomerunStats(..),
+  MLBBoxScoreHomerunStatsListingConstructor(..),
+  MLBBoxScoreHomerunStatsListingPitcherConstructor(..),
   MLBBoxScoreMiscellaneousGameInfo(..),
-  MLBBoxScoreMiscPitchingStats(..),
+  MLBBoxScoreMiscPitchingStatsHitByPitchConstructor(..),
+  MLBBoxScoreMiscPitchingStatsIntentionalWalkConstructor(..),
   MLBBoxScoreRunsByInningsConstructor(..),
   MLBBoxScoreTeamBreakdownConstructor(..),
-  MLBBoxScoreTeamSummary(..)
- )
---  AutoRacingResultsListingConstructor(..),
---  AutoRacingResultsRaceInformationConstructor(..) )
+  MLBBoxScoreTeamSummary(..) -- can go eventually
+  )
 where
 
 -- System imports.
 import Control.Monad ( forM_ )
+import Data.Data ( Data )
+import Data.Maybe ( fromMaybe )
 import Data.Time ( UTCTime(..) )
 import Data.Tuple.Curry ( uncurryN )
+import qualified Data.Vector.HFixed as H ( HVector, cons, convert, tail )
+import Data.Typeable ( Typeable )
 import Database.Groundhog (
   insert,
   insert_,
@@ -56,7 +61,6 @@ 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 (
@@ -104,6 +108,7 @@ data MLBBoxScore =
     db_game_time :: UTCTime,
     db_game_number :: Int,
     db_capacity :: Int,
+    db_wild_pitches :: Maybe Int, -- From misc pitching stats
     db_title :: String,
     db_time_stamp :: UTCTime }
 
@@ -137,15 +142,15 @@ data Message =
     xml_game_breakdown :: MLBBoxScoreGameBreakdownXml,
     xml_team_summaries :: [MLBBoxScoreTeamSummaryXml],
     xml_misc_pitching_stats :: MLBBoxScoreMiscPitchingStatsXml,
-    xml_homerun_stats :: Maybe MLBBoxScoreHomerunStatsXml,
+    xml_homerun_stats_listings :: Maybe [MLBBoxScoreHomerunStatsListingXml],
     xml_miscellaneous_game_info :: MLBBoxScoreMiscellaneousGameInfoXml,
     xml_time_stamp :: UTCTime }
   deriving (Eq, GHC.Generic, Show)
 
 
--- | For 'Generics.to_tuple'.
+-- | For 'H.convert'.
 --
-instance Generic Message
+instance H.HVector Message
 
 instance ToDb Message where
   -- | The database analogue of a 'Message' is a 'MLBBoxScore'.
@@ -184,6 +189,7 @@ instance FromXmlFkTeams Message where
       db_game_time = make_game_time,
       db_game_number = xml_game_number,
       db_capacity = xml_capacity,
+      db_wild_pitches = xml_wild_pitches xml_misc_pitching_stats,
       db_title = xml_title,
       db_time_stamp = xml_time_stamp }
     where
@@ -200,14 +206,137 @@ data MLBBoxScoreGameBreakdownXml =
     xml_home_team :: MLBBoxScoreTeamBreakdownXml }
   deriving (Eq, GHC.Generic, Show)
 
--- | For 'Generics.to_tuple'
+-- | For 'H.convert'
 --
-instance Generic MLBBoxScoreGameBreakdownXml
+instance H.HVector MLBBoxScoreGameBreakdownXml
+
+
+-- | The leading underscores prevent unused field warnings.
+--
+data MLBBoxScoreHomerunStatsListingBatter =
+  MLBBoxScoreHomerunStatsListingBatter {
+    _db_batter_first_name :: String,
+    _db_batter_last_name :: String,
+    _db_batter_rbis :: Int,
+    _db_batter_id :: Int }
+  deriving (Data, Eq, GHC.Generic, Show, Typeable)
+
+-- | For 'H.convert'
+--
+instance H.HVector MLBBoxScoreHomerunStatsListingBatter
+
+
+data MLBBoxScoreHomerunStatsListing =
+  MLBBoxScoreHomerunStatsListing {
+    db_mlb_box_scores_id :: DefaultKey MLBBoxScore,
+    db_batter :: MLBBoxScoreHomerunStatsListingBatter, -- embedded
+    db_season_homeruns :: Int }
+
+data MLBBoxScoreHomerunStatsListingXml =
+  MLBBoxScoreHomerunStatsListingXml {
+    xml_batter :: MLBBoxScoreHomerunStatsListingBatter,
+    xml_season_homeruns :: Int,
+    xml_pitchers :: [MLBBoxScoreHomerunStatsListingPitcherXml] }
+  deriving (Eq, GHC.Generic, Show)
+
+-- | For 'H.convert'
+--
+instance H.HVector MLBBoxScoreHomerunStatsListingXml
+
+instance Child MLBBoxScoreHomerunStatsListingXml where
+  -- | Each 'MLBBoxScoreHomerunStatsListingXml' is contained in (i.e. has a
+  --   foreign key to) a 'MLBBoxScore'.
+  --
+  type Parent MLBBoxScoreHomerunStatsListingXml = MLBBoxScore
+
+
+instance ToDb MLBBoxScoreHomerunStatsListingXml where
+  -- | The database representation of
+  --   'MLBBoxScoreHomerunStatsListingXml' is
+  --   'MLBBoxScoreHomerunStatsListing'.
+    --
+  type Db MLBBoxScoreHomerunStatsListingXml = MLBBoxScoreHomerunStatsListing
+
+instance FromXmlFk MLBBoxScoreHomerunStatsListingXml where
+  -- | To convert an 'MLBBoxScoreHomerunStatsListingXml' to an
+  --   'MLBBoxScoreHomerunStatsListing', we add the foreign key and
+  --   drop the pitchers.
+  --
+  from_xml_fk fk MLBBoxScoreHomerunStatsListingXml{..} =
+    MLBBoxScoreHomerunStatsListing {
+      db_mlb_box_scores_id = fk,
+      db_batter = xml_batter,
+      db_season_homeruns = xml_season_homeruns }
+
+
+-- | This allows us to insert the XML representation
+--   'MLBBoxScoreHomerunStatsListingXml' directly.
+--
+instance XmlImportFk MLBBoxScoreHomerunStatsListingXml
+
+
+-- | The leading underscores prevent unused field warnings.
+--
+data MLBBoxScoreHomerunStatsListingPitcher =
+  MLBBoxScoreHomerunStatsListingPitcher {
+    _db_mlb_box_score_homerun_stats_listings_id ::
+      DefaultKey MLBBoxScoreHomerunStatsListing,
+    _db_homeruns_off_pitcher :: Int,
+    _db_pitcher_first_name :: String,
+    _db_pitcher_last_name :: String,
+    _db_pitchers_pitcher_id :: Int }
+  deriving ( GHC.Generic )
+
+
+-- | For 'H.cons' and 'H.convert'.
+--
+instance H.HVector MLBBoxScoreHomerunStatsListingPitcher
+
+
+-- | The leading underscores prevent unused field warnings.
+--
+data MLBBoxScoreHomerunStatsListingPitcherXml =
+  MLBBoxScoreHomerunStatsListingPitcherXml {
+    _xml_homeruns_off_pitcher :: Int,
+    _xml_pitcher_first_name :: String,
+    _xml_pitcher_last_name :: String,
+    _xml_pitchers_pitcher_id :: Int }
+  deriving (Eq, GHC.Generic, Show)
+
+-- | For 'H.convert'
+--
+instance H.HVector MLBBoxScoreHomerunStatsListingPitcherXml
+
+instance Child MLBBoxScoreHomerunStatsListingPitcherXml where
+  -- | Each 'MLBBoxScoreHomerunStatsListingPitcherXml' is contained in
+  --   (i.e. has a foreign key to) a 'MLBBoxScoreHomerunStatsListing'.
+  --
+  type Parent MLBBoxScoreHomerunStatsListingPitcherXml =
+    MLBBoxScoreHomerunStatsListing
+
+
+instance ToDb MLBBoxScoreHomerunStatsListingPitcherXml where
+  -- | The database representation of
+  --   'MLBBoxScoreHomerunStatsListingPitcherXml' is
+  --   'MLBBoxScoreHomerunStatsListingPitcher'.
+  --
+  type Db MLBBoxScoreHomerunStatsListingPitcherXml = MLBBoxScoreHomerunStatsListingPitcher
+
+
+instance FromXmlFk MLBBoxScoreHomerunStatsListingPitcherXml where
+  -- | To convert an 'MLBBoxScoreHomerunStatsListingPitcherXml' to an
+  --   'MLBBoxScoreHomerunStatsListingPitcher', we add the foreign key.
+  --
+  from_xml_fk = H.cons
+
+
+-- | This allows us to insert the XML representation
+--   'MLBBoxScoreHomerunStatsListingPitcherXml' directly.
+--
+instance XmlImportFk MLBBoxScoreHomerunStatsListingPitcherXml
+
 
 
-data MLBBoxScoreHomerunStats = MLBBoxScoreHomerunStats
-data MLBBoxScoreHomerunStatsXml = MLBBoxScoreHomerunStatsXml
-  deriving (Eq, Show)
 
 data MLBBoxScoreMiscellaneousGameInfo = MLBBoxScoreMiscellaneousGameInfo
 data MLBBoxScoreMiscellaneousGameInfoXml = MLBBoxScoreMiscellaneousGameInfoXml
@@ -215,22 +344,33 @@ data MLBBoxScoreMiscellaneousGameInfoXml = MLBBoxScoreMiscellaneousGameInfoXml
 
 
 -- Team Breakdown
+
+-- | The leading underscores prevent unused field warnings.
+--
 data MLBBoxScoreTeamBreakdown =
   MLBBoxScoreTeamBreakdown {
-    db_runs :: Int,
-    db_hits :: Int,
-    db_errors :: Int }
+    _db_runs :: Int,
+    _db_hits :: Int,
+    _db_errors :: Int }
+  deriving ( GHC.Generic )
+
+-- | For 'H.cons' and 'H.convert'.
+--
+instance H.HVector MLBBoxScoreTeamBreakdown
+
+-- | The leading underscores prevent unused field warnings.
+--
 data MLBBoxScoreTeamBreakdownXml =
   MLBBoxScoreTeamBreakdownXml {
     xml_runs_by_innings :: [MLBBoxScoreRunsByInningsXml],
-    xml_runs :: Int,
-    xml_hits :: Int,
-    xml_errors :: Int }
+    _xml_runs :: Int,
+    _xml_hits :: Int,
+    _xml_errors :: Int }
   deriving (Eq, GHC.Generic, Show)
 
 
--- | For 'Generics.to_tuple'.
-instance Generic MLBBoxScoreTeamBreakdownXml
+-- | For 'H.convert'.
+instance H.HVector MLBBoxScoreTeamBreakdownXml
 
 instance ToDb MLBBoxScoreTeamBreakdownXml where
   -- | The database analogue of a 'MLBBoxScoreTeamBreakdownXml' is
@@ -247,26 +387,33 @@ instance FromXml MLBBoxScoreTeamBreakdownXml where
   --   'MLBBoxScoreTeamBreakdown', we just drop the
   --   'xml_runs_by_innings'.
   --
-  from_xml MLBBoxScoreTeamBreakdownXml{..} =
-    MLBBoxScoreTeamBreakdown {
-      db_runs = xml_runs,
-      db_hits = xml_hits,
-      db_errors = xml_errors }
+  from_xml = H.tail
 
 instance XmlImport MLBBoxScoreTeamBreakdownXml
 
 -- Runs by innings
+
+-- | The leading underscores prevent unused field warnings.
+--
 data MLBBoxScoreRunsByInnings =
   MLBBoxScoreRunsByInnings {
-    db_mlb_box_scores_team_breakdowns_id :: DefaultKey
+    _db_mlb_box_scores_team_breakdowns_id :: DefaultKey
                                            MLBBoxScoreTeamBreakdown,
-    db_runs_by_innings_inning_number :: Int,
-    db_runs_by_innings_runs   :: Int }
+    _db_runs_by_innings_inning_number :: Int,
+    _db_runs_by_innings_runs   :: Int }
+  deriving ( GHC.Generic )
+
+
+-- | For 'H.cons' and 'H.convert'.
+instance H.HVector MLBBoxScoreRunsByInnings
+
 
+-- | The leading underscores prevent unused field warnings.
+--
 data MLBBoxScoreRunsByInningsXml =
   MLBBoxScoreRunsByInningsXml {
-    xml_runs_by_innings_inning_number :: Int,
-    xml_runs_by_innings_runs   :: Int }
+    _xml_runs_by_innings_inning_number :: Int,
+    _xml_runs_by_innings_runs   :: Int }
   deriving (Eq, GHC.Generic, Show)
 
 
@@ -284,9 +431,9 @@ data MLBBoxScore_MLBBoxScoreTeamBreakdown =
 
 
 
--- | For 'Generics.to_tuple'.
+-- | For 'H.convert'.
 --
-instance Generic MLBBoxScoreRunsByInningsXml
+instance H.HVector MLBBoxScoreRunsByInningsXml
 
 
 instance ToDb MLBBoxScoreRunsByInningsXml where
@@ -308,11 +455,7 @@ instance FromXmlFk MLBBoxScoreRunsByInningsXml where
   --   'MLBBoxScoreRunsByInnings', we add the foreign key and copy
   --   everything else verbatim.
   --
-  from_xml_fk fk MLBBoxScoreRunsByInningsXml{..} =
-    MLBBoxScoreRunsByInnings {
-      db_mlb_box_scores_team_breakdowns_id = fk,
-      db_runs_by_innings_inning_number = xml_runs_by_innings_inning_number,
-      db_runs_by_innings_runs = xml_runs_by_innings_runs }
+  from_xml_fk = H.cons
 
 
 -- | This allows us to insert the XML representation
@@ -322,8 +465,11 @@ instance XmlImportFk MLBBoxScoreRunsByInningsXml
 
 
 
-
-data MLBBoxScoreMiscPitchingStats = MLBBoxScoreMiscPitchingStats
+-- | The type representing \<Misc_Pitching_Stats\> XML elements. It
+--   has no associated database type; the 'xml_wild_pitches' are
+--   stored directly in the 'MLBBoxScore', and the two linked tables
+--   are treated as children of the 'MLBBoxScore'.
+--
 data MLBBoxScoreMiscPitchingStatsXml =
   MLBBoxScoreMiscPitchingStatsXml {
     xml_wild_pitches :: Maybe Int,
@@ -332,33 +478,138 @@ data MLBBoxScoreMiscPitchingStatsXml =
   deriving (Eq, GHC.Generic, Show)
 
 
--- | For 'Generics.to_tuple'.
-instance Generic MLBBoxScoreMiscPitchingStatsXml
+-- | For 'H.convert'.
+--
+instance H.HVector MLBBoxScoreMiscPitchingStatsXml
+
+
+-- * MLBBoxScoreMiscPitchingStatsIntentionalWalk
+
+-- | Database representation of an intentional walk. The weird
+--   prefixes avoid collisions with the other batter/pitcher_ids, and
+--   still get mangled properly by Groundhog.
+--
+--   The leading underscores prevent unused field warnings.
+--
+data MLBBoxScoreMiscPitchingStatsIntentionalWalk =
+  MLBBoxScoreMiscPitchingStatsIntentionalWalk {
+    _dbiw_mlb_box_scores_id :: DefaultKey MLBBoxScore,
+    _dbiw_batter_id :: Int,
+    _dbiw_pitcher_id :: Int,
+    _dbiw_number_of_times_walked :: Int }
+  deriving ( GHC.Generic )
+
 
+-- | For 'H.cons' and 'H.convert'.
+--
+instance H.HVector MLBBoxScoreMiscPitchingStatsIntentionalWalk
 
+-- | The leading underscores prevent unused field warnings.
+--
 data MLBBoxScoreMiscPitchingStatsIntentionalWalkXml =
   MLBBoxScoreMiscPitchingStatsIntentionalWalkXml {
-    xml_iw_batter_id :: Int,
-    xml_iw_pitcher_id :: Int,
-    xml_iw_number_of_times_walked :: Int }
+    _xml_iw_batter_id :: Int,
+    _xml_iw_pitcher_id :: Int,
+    _xml_iw_number_of_times_walked :: Int }
   deriving (Eq, GHC.Generic, Show)
 
+-- | For 'H.convert'.
+--
+instance H.HVector MLBBoxScoreMiscPitchingStatsIntentionalWalkXml
+
+
+instance ToDb MLBBoxScoreMiscPitchingStatsIntentionalWalkXml where
+  -- | The database analogue of a
+  -- 'MLBBoxScoreMiscPitchingStatsIntentionalWalkXml' is a
+  -- 'MLBBoxScoreMiscPitchingStatsIntentionalWalk'.
+  --
+  type Db MLBBoxScoreMiscPitchingStatsIntentionalWalkXml =
+    MLBBoxScoreMiscPitchingStatsIntentionalWalk
+
 
--- | For 'Generics.to_tuple'.
-instance Generic MLBBoxScoreMiscPitchingStatsIntentionalWalkXml
+instance Child MLBBoxScoreMiscPitchingStatsIntentionalWalkXml where
+  -- | Each 'MLBBoxScoreMiscPitchingStatsIntentionalWalkXml' is
+  --   contained in (i.e. has a foreign key to) a 'MLBBoxScore'.
+  --
+  type Parent MLBBoxScoreMiscPitchingStatsIntentionalWalkXml =
+    MLBBoxScore
+
+
+instance FromXmlFk MLBBoxScoreMiscPitchingStatsIntentionalWalkXml where
+  -- | To convert an 'MLBBoxScoreMiscPitchingStatsIntentionalWalkXml'
+  --   to an 'MLBBoxScoreMiscPitchingStatsIntentionalWalk', we add the
+  --   foreign key and copy everything else verbatim.
+  --
+  from_xml_fk = H.cons
 
 
+-- | This allows us to insert the XML representation
+--   'MLBBoxScoreMiscPitchingStatsIntentionalWalkXml' directly.
+--
+instance XmlImportFk MLBBoxScoreMiscPitchingStatsIntentionalWalkXml
+
+
+
+-- * MLBBoxScoreMiscPitchingStatsHitByPitchXml
+
+-- | The leading underscores prevent unused field warnings.
+--
+data MLBBoxScoreMiscPitchingStatsHitByPitch =
+  MLBBoxScoreMiscPitchingStatsHitByPitch {
+    _dbhbp_mlb_box_scores_id :: DefaultKey MLBBoxScore,
+    _dbhbp_batter_id :: Int,
+    _dbhbp_pitcher_id :: Int,
+    _dbhbp_number_of_times_hit :: Int }
+  deriving ( GHC.Generic )
+
+-- | For 'H.cons' and 'H.convert'.
+--
+instance H.HVector MLBBoxScoreMiscPitchingStatsHitByPitch
+
+instance ToDb MLBBoxScoreMiscPitchingStatsHitByPitchXml where
+  -- | The database analogue of a
+  -- 'MLBBoxScoreMiscPitchingStatsHitByPitchXml' is a
+  -- 'MLBBoxScoreMiscPitchingStatsHitByPitch'.
+  --
+  type Db MLBBoxScoreMiscPitchingStatsHitByPitchXml =
+    MLBBoxScoreMiscPitchingStatsHitByPitch
+
+
+instance Child MLBBoxScoreMiscPitchingStatsHitByPitchXml where
+  -- | Each 'MLBBoxScoreMiscPitchingStatsHitByPitchXml' is
+  --   contained in (i.e. has a foreign key to) a 'MLBBoxScore'.
+  --
+  type Parent MLBBoxScoreMiscPitchingStatsHitByPitchXml =
+    MLBBoxScore
+
+
+instance FromXmlFk MLBBoxScoreMiscPitchingStatsHitByPitchXml where
+  -- | To convert an 'MLBBoxScoreMiscPitchingStatsHitByPitchXml'
+  --   to an 'MLBBoxScoreMiscPitchingStatsHitByPitch', we add the
+  --   foreign key and copy everything else verbatim.
+  --
+  from_xml_fk = H.cons
+
+
+-- | This allows us to insert the XML representation
+--   'MLBBoxScoreMiscPitchingStatsHitByPitchXml' directly.
+--
+instance XmlImportFk MLBBoxScoreMiscPitchingStatsHitByPitchXml
+
+
+-- | The leading underscores prevent unused field warnings.
+--
 data MLBBoxScoreMiscPitchingStatsHitByPitchXml =
   MLBBoxScoreMiscPitchingStatsHitByPitchXml {
-    xml_hbp_batter_id :: Int,
-    xml_hbp_pitcher_id :: Int,
-    xml_hbp_number_of_times_hit :: Int }
+    _xml_hbp_batter_id :: Int,
+    _xml_hbp_pitcher_id :: Int,
+    _xml_hbp_number_of_times_hit :: Int }
   deriving (Eq, GHC.Generic, Show)
 
 
--- | For 'Generics.to_tuple'.
+-- | For 'H.convert'.
 --
-instance Generic MLBBoxScoreMiscPitchingStatsHitByPitchXml
+instance H.HVector MLBBoxScoreMiscPitchingStatsHitByPitchXml
 
 
 --
@@ -369,6 +620,13 @@ instance DbImport Message where
   dbmigrate _ =
     run_dbmigrate $ do
       migrate (undefined :: MLBBoxScore)
+      migrate (undefined :: MLBBoxScoreMiscPitchingStatsIntentionalWalk)
+      migrate (undefined :: MLBBoxScoreMiscPitchingStatsHitByPitch)
+      migrate (undefined :: MLBBoxScoreHomerunStatsListing)
+      migrate (undefined :: MLBBoxScoreHomerunStatsListingPitcher)
+      migrate (undefined :: MLBBoxScoreTeamBreakdown)
+      migrate (undefined :: MLBBoxScoreRunsByInnings)
+      migrate (undefined :: MLBBoxScore_MLBBoxScoreTeamBreakdown)
 
   -- | We insert the message.
   dbimport m = do
@@ -407,6 +665,25 @@ instance DbImport Message where
 
     insert_ msg__breakdown
 
+    -- Now insert the homerun stats listings, keyed to the message.
+    -- They need not be present, but we're going to loop through them
+    -- all anyway, so if we have 'Nothing', we convert that to an
+    -- empty list instead. This simplifies the `forM_` code.
+    let listings = fromMaybe [] (xml_homerun_stats_listings m)
+    forM_ listings $ \listing -> do
+      -- Insert the listing itself.
+      listing_id <- insert_xml_fk msg_id listing
+      -- And all of its pitchers
+      forM_ (xml_pitchers listing) $ insert_xml_fk listing_id
+
+    -- We have two tables of pitching stats that need to be keyed to
+    -- the message, too.
+    let iws = xml_intentional_walks (xml_misc_pitching_stats m)
+    forM_ iws $ insert_xml_fk_ msg_id
+
+    let hbps = xml_hits_by_pitch (xml_misc_pitching_stats m)
+    forM_ hbps $ insert_xml_fk_ msg_id
+
     return ImportSucceeded
 
 
@@ -423,6 +700,59 @@ mkPersist tsn_codegen_config [groundhog|
           fields: [db_xml_file_id]
 
 
+
+- entity: MLBBoxScoreMiscPitchingStatsIntentionalWalk
+  dbName: mlb_box_scores_misc_pitching_stats_intentional_walks
+  constructors:
+    - name: MLBBoxScoreMiscPitchingStatsIntentionalWalk
+      fields:
+        - name: _dbiw_mlb_box_scores_id
+          reference:
+            onDelete: cascade
+
+
+- entity: MLBBoxScoreMiscPitchingStatsHitByPitch
+  dbName: mlb_box_scores_misc_pitching_stats_hits_by_pitch
+  constructors:
+    - name: MLBBoxScoreMiscPitchingStatsHitByPitch
+      fields:
+        - name: _dbhbp_mlb_box_scores_id
+          reference:
+            onDelete: cascade
+
+
+- embedded: MLBBoxScoreHomerunStatsListingBatter
+  fields:
+    - name: _db_batter_first_name
+      dbName: batter_first_name
+    - name: _db_batter_last_name
+      dbName: batter_last_name
+    - name: _db_batter_rbis
+      dbName: batter_rbis
+    - name: _db_batter_id
+      dbName: batter_id
+
+- entity: MLBBoxScoreHomerunStatsListing
+  dbName: mlb_box_score_homerun_stats_listings
+  constructors:
+    - name: MLBBoxScoreHomerunStatsListing
+      fields:
+        - name: db_batter
+          embeddedType:
+            - {name: batter_first_name, dbName: batter_first_name}
+            - {name: batter_last_name, dbName: batter_last_name}
+            - {name: batter_rbis, dbName: batter_rbis}
+            - {name: batter_id, dbName: batter_id}
+
+- entity: MLBBoxScoreHomerunStatsListingPitcher
+  dbName: mlb_box_score_homerun_stats_listing_pitchers
+  constructors:
+    - name: MLBBoxScoreHomerunStatsListingPitcher
+      fields:
+        - name: _db_mlb_box_score_homerun_stats_listings_id
+          reference:
+            onDelete: cascade
+
 - entity: MLBBoxScoreTeamBreakdown
   dbName: mlb_box_scores_team_breakdowns
   constructors:
@@ -433,7 +763,7 @@ mkPersist tsn_codegen_config [groundhog|
   constructors:
     - name: MLBBoxScoreRunsByInnings
       fields:
-        - name: db_mlb_box_scores_team_breakdowns_id
+        - name: _db_mlb_box_scores_team_breakdowns_id
           reference:
             onDelete: cascade
 
@@ -466,7 +796,7 @@ mkPersist tsn_codegen_config [groundhog|
 pickle_message :: PU Message
 pickle_message =
   xpElem "message" $
-    xpWrap (from_tuple, to_tuple) $
+    xpWrap (from_tuple, H.convert) $
       xp23Tuple (xpElem "XML_File_ID" xpInt)
                 (xpElem "heading" xpText)
                 (xpElem "category" xpText)
@@ -487,7 +817,7 @@ pickle_message =
                 pickle_game_breakdown
                 (xpList pickle_team_summary)
                 pickle_misc_pitching_stats
-                pickle_homerun_stats
+                (xpOption pickle_homerun_stats_listings)
                 pickle_miscellaneous_game_info
                 (xpElem "time_stamp" xp_time_stamp)
   where
@@ -496,7 +826,7 @@ pickle_message =
 
 pickle_team_summary :: PU MLBBoxScoreTeamSummaryXml
 pickle_team_summary =
-  xpElem "Team_Summary" $ xpWrap (from_tuple, to_tuple') xpUnit
+  xpElem "Team_Summary" $ xpWrap (from_tuple, to_tuple') xpUnit
   where
     from_tuple _ = MLBBoxScoreTeamSummaryXml
     to_tuple'   _ = ()
@@ -504,7 +834,7 @@ pickle_team_summary =
 pickle_game_breakdown :: PU MLBBoxScoreGameBreakdownXml
 pickle_game_breakdown =
   xpElem "Game_Breakdown" $
-    xpWrap (from_tuple, to_tuple) $
+    xpWrap (from_tuple, H.convert) $
       xpPair pickle_away_team
              pickle_home_team
   where
@@ -514,7 +844,7 @@ pickle_game_breakdown =
 pickle_runs_by_innings :: PU MLBBoxScoreRunsByInningsXml
 pickle_runs_by_innings =
   xpElem "Runs_By_Innings" $
-    xpWrap (from_tuple, to_tuple) $
+    xpWrap (from_tuple, H.convert) $
       xpPair (xpAttr "Inning" xpInt)
              xpInt
   where
@@ -523,7 +853,7 @@ pickle_runs_by_innings =
 
 pickle_team :: PU MLBBoxScoreTeamBreakdownXml
 pickle_team =
-  xpWrap (from_tuple, to_tuple) $
+  xpWrap (from_tuple, H.convert) $
     xp4Tuple (xpList pickle_runs_by_innings)
              (xpElem "Runs" xpInt)
              (xpElem "Hits" xpInt)
@@ -540,18 +870,51 @@ pickle_home_team :: PU MLBBoxScoreTeamBreakdownXml
 pickle_home_team =
   xpElem "HomeTeam" pickle_team
 
-pickle_homerun_stats :: PU (Maybe MLBBoxScoreHomerunStatsXml)
-pickle_homerun_stats =
-  xpOption $ xpElem "Homerun_Stats" $ xpWrap (from_tuple, to_tuple') $ xpUnit
+
+pickle_batter :: PU MLBBoxScoreHomerunStatsListingBatter
+pickle_batter =
+  xpElem "HRS_Batter_ID" $
+    xpWrap (from_tuple, H.convert) $
+    xp4Tuple (xpAttr "HRS_Batter_FirstName" xpText)
+             (xpAttr "HRS_Batter_LastName" xpText)
+             (xpAttr "RBIs" xpInt)
+             xpInt
   where
-    from_tuple _ = MLBBoxScoreHomerunStatsXml
-    to_tuple'   _ = ()
+    from_tuple = uncurryN MLBBoxScoreHomerunStatsListingBatter
+
+
+pickle_pitcher :: PU MLBBoxScoreHomerunStatsListingPitcherXml
+pickle_pitcher =
+  xpElem "HRS_Pitcher_ID" $
+    xpWrap (from_tuple, H.convert) $
+    xp4Tuple (xpAttr "HRS_Homeruns_Off_Pitcher" xpInt)
+             (xpAttr "HRS_Pitcher_FirstName" xpText)
+             (xpAttr "HRS_Pitcher_LastName" xpText)
+             xpInt
+  where
+    from_tuple = uncurryN MLBBoxScoreHomerunStatsListingPitcherXml
+
+
+pickle_homerun_stats_listing :: PU MLBBoxScoreHomerunStatsListingXml
+pickle_homerun_stats_listing =
+  xpElem "HRS_Listing" $
+    xpWrap (from_tuple, H.convert) $
+    xpTriple pickle_batter
+             (xpElem "Season_Homeruns" xpInt)
+             (xpList pickle_pitcher)
+  where
+    from_tuple = uncurryN MLBBoxScoreHomerunStatsListingXml
+
+
+pickle_homerun_stats_listings :: PU [MLBBoxScoreHomerunStatsListingXml]
+pickle_homerun_stats_listings =
+  xpElem "Homerun_Stats" $ xpList pickle_homerun_stats_listing
 
 
 pickle_misc_pitching_stats :: PU MLBBoxScoreMiscPitchingStatsXml
 pickle_misc_pitching_stats =
   xpElem "Misc_Pitching_Stats" $
-    xpWrap (from_tuple, to_tuple) $
+    xpWrap (from_tuple, H.convert) $
       xpTriple (xpOption $ xpElem "Wild_Pitches" xpInt)
                pickle_intentional_walks
                pickle_hits_by_pitch
@@ -563,7 +926,7 @@ pickle_misc_pitching_stats =
 pickle_intentional_walks :: PU [MLBBoxScoreMiscPitchingStatsIntentionalWalkXml]
 pickle_intentional_walks =
   xpElem "Intentional_Walks" $ xpList $ xpElem "IW_Listing" $
-    xpWrap (from_tuple, to_tuple) $
+    xpWrap (from_tuple, H.convert) $
       xpTriple (xpElem "IW_Batter_ID" xpInt)
                (xpElem "IW_Pitcher_ID" xpInt)
                (xpElem "IW_Number_Of_Times_Walked" xpInt)
@@ -575,7 +938,7 @@ pickle_intentional_walks =
 pickle_hits_by_pitch :: PU [MLBBoxScoreMiscPitchingStatsHitByPitchXml]
 pickle_hits_by_pitch =
   xpElem "Hit_By_Pitch" $ xpList $ xpElem "HBP_Listing" $
-    xpWrap (from_tuple, to_tuple) $
+    xpWrap (from_tuple, H.convert) $
       xpTriple (xpElem "HBP_Batter_ID" xpInt)
                (xpElem "HBP_Pitcher_ID" xpInt)
                (xpElem "HBP_Number_Of_Times_Hit" xpInt)
@@ -586,7 +949,7 @@ pickle_hits_by_pitch =
 
 pickle_miscellaneous_game_info :: PU MLBBoxScoreMiscellaneousGameInfoXml
 pickle_miscellaneous_game_info =
-  xpElem "Miscelaneous_Game_Info" $ xpWrap (from_tuple, to_tuple') xpUnit
+  xpElem "Miscelaneous_Game_Info" $ xpWrap (from_tuple, to_tuple') xpUnit
   where
     from_tuple _ = MLBBoxScoreMiscellaneousGameInfoXml
     to_tuple'  _ = ()