{-# 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(..), pickle_location, -- * WARNING: these are private but exported to silence warnings LocationConstructor(..) ) where -- System imports import Data.Tuple.Curry ( uncurryN ) import Database.Groundhog () -- Required for some String instance import Database.Groundhog.TH ( defaultCodegenConfig, groundhog, mkPersist ) import Text.XML.HXT.Core ( PU, xpElem, xpOption, xpText, xpTriple, xpWrap ) -- | 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] |] -- | We also provide an (un)pickler for one common XML representation, -- used at least in "TSN.XML.News" and "TSN.XML.Location". -- pickle_location :: PU Location pickle_location = xpElem "location" $ xpWrap (from_tuple, to_tuple) $ xpTriple (xpOption (xpElem "city" xpText)) (xpOption (xpElem "state" xpText)) (xpElem "country" xpText) where from_tuple = uncurryN Location to_tuple l = (city l, state l, country l)