X-Git-Url: http://gitweb.michael.orlitzky.com/?a=blobdiff_plain;f=src%2FTSN%2FXML%2FInjuries.hs;h=03f956595606ae2c342faa9c68384141d8497e88;hb=d476419274cdf2997d768444cecc47922a902fdf;hp=92bf4e27757dca8c1de4320a920a982be609d1df;hpb=76cf3eee776d35ba2b18dd0d07df7496a083ae3a;p=dead%2Fhtsn-import.git diff --git a/src/TSN/XML/Injuries.hs b/src/TSN/XML/Injuries.hs index 92bf4e2..03f9565 100644 --- a/src/TSN/XML/Injuries.hs +++ b/src/TSN/XML/Injuries.hs @@ -1,7 +1,7 @@ +{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE QuasiQuotes #-} -{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} @@ -14,43 +14,63 @@ -- automatically. The root message is not retained. -- module TSN.XML.Injuries ( - Listing, - Message( listings ), - injuries_tests ) + pickle_message, + -- * Tests + injuries_tests, + -- * WARNING: these are private but exported to silence warnings + ListingConstructor(..) ) where -import Data.Tuple.Curry ( uncurryN ) -import Database.Groundhog() +import Data.Data ( Data ) +import Data.Typeable ( Typeable ) +import Database.Groundhog ( + migrate ) import Database.Groundhog.TH ( defaultCodegenConfig, groundhog, mkPersist ) +import Data.Tuple.Curry ( uncurryN ) import Test.Tasty ( TestTree, testGroup ) import Test.Tasty.HUnit ( (@?=), testCase ) import Text.XML.HXT.Core ( PU, - XmlPickler(..), xp4Tuple, xp6Tuple, + xpAttr, xpElem, + xpInt, xpList, + xpOption, + xpPair, xpPrim, xpText, xpWrap ) -import TSN.DbImport ( DbImport(..), import_generic ) -import Xml ( pickle_unpickle ) +import TSN.DbImport ( DbImport(..), ImportResult(..), run_dbmigrate ) +import TSN.XmlImport ( XmlImport(..) ) +import Xml ( FromXml(..), pickle_unpickle, unpickleable ) +data InjuriesTeam = + InjuriesTeam { + team_name :: String, + team_league :: Maybe String } + deriving (Data, Eq, Show, Typeable) data Listing = Listing { - team :: String, - teamno :: Int, + team :: InjuriesTeam, + teamno :: Maybe Int, injuries :: String, - updated :: Bool } + updated :: Maybe Bool } deriving (Eq, Show) +instance FromXml Listing where + type Db Listing = Listing + from_xml = id + +instance XmlImport Listing + data Message = Message { xml_file_id :: Int, @@ -61,34 +81,56 @@ data Message = time_stamp :: String } deriving (Eq, Show) +instance DbImport Message where + dbimport msg = mapM_ insert_xml (listings msg) >> return ImportSucceeded + + dbmigrate _ = run_dbmigrate $ migrate (undefined :: Listing) mkPersist defaultCodegenConfig [groundhog| - entity: Listing - dbName: injuries + dbName: injuries_listings + constructors: + - name: Listing + fields: + - name: team + embeddedType: + - {name: team_name, dbName: team_name} + - {name: team_league, dbName: team_league} +- embedded: InjuriesTeam + fields: + - name: team_name + - name: team_league |] +pickle_injuries_team :: PU InjuriesTeam +pickle_injuries_team = + xpElem "team" $ + xpWrap (from_tuple, to_tuple) $ + xpPair xpText (xpOption $ xpAttr "league" xpText) + where + from_tuple = uncurryN InjuriesTeam + to_tuple m = (team_name m, team_league m) + + pickle_listing :: PU Listing pickle_listing = xpElem "listing" $ xpWrap (from_tuple, to_tuple) $ - xp4Tuple (xpElem "team" xpText) - (xpElem "teamno" xpPrim) + xp4Tuple pickle_injuries_team + (xpOption $ xpElem "teamno" xpInt) (xpElem "injuries" xpText) - (xpElem "updated" xpPrim) + (xpOption $ xpElem "updated" xpPrim) where from_tuple = uncurryN Listing to_tuple l = (team l, teamno l, injuries l, updated l) -instance XmlPickler Listing where - xpickle = pickle_listing - pickle_message :: PU Message pickle_message = xpElem "message" $ xpWrap (from_tuple, to_tuple) $ - xp6Tuple (xpElem "XML_File_ID" xpPrim) + xp6Tuple (xpElem "XML_File_ID" xpInt) (xpElem "heading" xpText) (xpElem "category" xpText) (xpElem "sport" xpText) @@ -103,25 +145,39 @@ pickle_message = listings m, time_stamp m) -instance XmlPickler Message where - xpickle = pickle_message +-- +-- Tasty Tests +-- - -instance DbImport Listing where - dbimport = import_generic listings - --- * Tasty Tests +-- | A list of all tests for this module. +-- injuries_tests :: TestTree injuries_tests = testGroup "Injuries tests" - [ test_pickle_of_unpickle_is_identity ] + [ test_pickle_of_unpickle_is_identity, + test_unpickle_succeeds ] +-- | 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/injuriesxml.xml" - (expected :: [Message], actual) <- pickle_unpickle "message" path + (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/injuriesxml.xml" + actual <- unpickleable path pickle_message + let expected = True + actual @?= expected