]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blob - src/TSN/Location.hs
Allow "TBA" laps in TSN.XML.AutoRacingSchedule.
[dead/htsn-import.git] / src / TSN / Location.hs
1 {-# LANGUAGE FlexibleInstances #-}
2 {-# LANGUAGE GADTs #-}
3 {-# LANGUAGE QuasiQuotes #-}
4 {-# LANGUAGE TemplateHaskell #-}
5 {-# LANGUAGE TypeFamilies #-}
6
7 -- | (At least) two different XML types have a notion of locations:
8 -- "TSN.XML.News" and "TSN.XML.Scores". And in fact those two types
9 -- agree on the city, state, and country -- at least for the
10 -- database representation.
11 --
12 -- This module contains a data type for the common database
13 -- representation.
14 --
15 module TSN.Location (
16 Location(..),
17 pickle_location,
18 -- * WARNING: these are private but exported to silence warnings
19 LocationConstructor(..) )
20 where
21
22 -- System imports
23 import Data.Tuple.Curry ( uncurryN )
24 import Database.Groundhog () -- Required for some String instance
25 import Database.Groundhog.TH (
26 defaultCodegenConfig,
27 groundhog,
28 mkPersist )
29 import Text.XML.HXT.Core (
30 PU,
31 xpElem,
32 xpOption,
33 xpText,
34 xpTriple,
35 xpWrap )
36
37
38 -- | Database representation of a location.
39 --
40 -- The country has always been present in the XML that we've
41 -- seen. The city/state however have been observed missing in some
42 -- cases. The Scores are better about always having a city/state,
43 -- but in the interest of consolidation, we've made them optional so
44 -- that they can be mushed together into this one type.
45 --
46 data Location =
47 Location {
48 city :: Maybe String,
49 state :: Maybe String,
50 country :: String }
51 deriving (Eq, Show)
52
53
54 -- Generate the Groundhog code for 'Location'.
55 mkPersist defaultCodegenConfig [groundhog|
56 - entity: Location
57 dbName: locations
58 constructors:
59 - name: Location
60 uniques:
61 - name: unique_location
62 type: constraint
63 fields: [city, state, country]
64 |]
65
66
67
68 -- | We also provide an (un)pickler for one common XML representation,
69 -- used at least in "TSN.XML.News" and "TSN.XML.Location".
70 --
71 pickle_location :: PU Location
72 pickle_location =
73 xpElem "location" $
74 xpWrap (from_tuple, to_tuple) $
75 xpTriple (xpOption (xpElem "city" xpText))
76 (xpOption (xpElem "state" xpText))
77 (xpElem "country" xpText)
78 where
79 from_tuple = uncurryN Location
80 to_tuple l = (city l, state l, country l)