--- /dev/null
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE QuasiQuotes #-}
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE TypeFamilies #-}
+
+-- | (At least) two different XML types have a notion of locations:
+-- "TSN.XML.News" and "TSN.XML.Scores". And in fact those two types
+-- agree on the city, state, and country -- at least for the
+-- database representation.
+--
+-- This module contains a data type for the common database
+-- representation.
+--
+module TSN.Location (
+ Location(..),
+ LocationConstructor(..) )
+where
+
+-- System imports
+import Database.Groundhog () -- Required for some String instance
+import Database.Groundhog.TH (
+ defaultCodegenConfig,
+ groundhog,
+ mkPersist )
+
+
+-- | Database representation of a location.
+--
+-- The country has always been present in the XML that we've
+-- seen. The city/state however have been observed missing in some
+-- cases. The Scores are better about always having a city/state,
+-- but in the interest of consolidation, we've made them optional so
+-- that they can be mushed together into this one type.
+--
+data Location =
+ Location {
+ city :: Maybe String,
+ state :: Maybe String,
+ country :: String }
+ deriving (Eq, Show)
+
+
+-- Generate the Groundhog code for 'Location'.
+mkPersist defaultCodegenConfig [groundhog|
+- entity: Location
+ dbName: locations
+ constructors:
+ - name: Location
+ uniques:
+ - name: unique_location
+ type: constraint
+ fields: [city, state, country]
+|]