-- | Parse the command-line options, and display help text if
-- necessary.
+--
module CommandLine (
get_args )
where
+-- System imports.
import System.Console.CmdArgs (
(&=),
args,
summary,
typ,
typFile )
+import Paths_htsn_import ( version ) -- These let us get the
+import Data.Version ( showVersion ) -- version from Cabal.
--- This let's us get the version from Cabal.
-import Paths_htsn_import (version)
-import Data.Version (showVersion)
-
+-- Local imports.
import OptionalConfiguration ( OptionalConfiguration(..) )
+
-- | The description of the program, displayed as part of the help.
description :: String
description = "Import XML files from The Sports Network into an RDBMS."
+
-- | The name of this program.
program_name :: String
program_name = "htsn-import"
+
-- | A summary string output as part of the help.
my_summary :: String
my_summary = program_name ++ "-" ++ (showVersion version)
+
-- | A description of the "backend" option.
backend_help :: String
backend_help =
"Database choice, either \"Sqlite\" or \"Postgres\"."
+
-- | A description of the "connection_string" option.
connection_string_help :: String
connection_string_help =
"A database-specific connection string (depends on the backend)."
+
-- | A description of the "log_file" option.
log_file_help :: String
log_file_help =
"Log to the given file."
+
-- | A description of the "log_level" option.
log_level_help :: String
log_level_help =
"How verbose should the logs be? One of INFO, WARNING, ERROR."
+
-- | A description of the "remove" option.
remove_help :: String
remove_help =
"Remove files that have been successfully imported."
+
-- | A description of the "syslog" option.
syslog_help :: String
syslog_help =
-- | A data structure representing the possible command-line
-- options. The CmdArgs library is doing heavy magic beneath the
-- hood here.
+--
arg_spec :: OptionalConfiguration
arg_spec =
OptionalConfiguration {
-- | A convenience function; our only export. Meant to be used in
-- 'main' to retrieve the command-line arguments.
+--
get_args :: IO OptionalConfiguration
get_args = cmdArgs arg_spec
merge_optional )
where
+-- System imports.
import System.Console.CmdArgs.Default ( Default(..) )
import System.Log ( Priority( INFO ) )
+-- Local imports.
import Backend ( Backend(..) )
import ConnectionString ( ConnectionString )
import qualified OptionalConfiguration as OC (
OptionalConfiguration(..),
merge_maybes )
--- | The main configuration data type. This will be passed to most of
--- the important functions once it has been created.
+
+-- | The main configuration data type. It contains all options that
+-- can be set in a config file or on the command line.
+--
data Configuration =
Configuration {
backend :: Backend,
-- | Merge a Configuration with an OptionalConfiguration. This is more
--- or less the Monoid instance for OptionalConfiguration, but since
+-- or less the Monoid instance for 'OptionalConfiguration', but since
-- the two types are different, we have to repeat ourselves.
+--
merge_optional :: Configuration
-> OC.OptionalConfiguration
-> Configuration
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
--- | Definition of and instances for the ConnectionString type.
+-- | Definition of and instances for the ConnectionString type. This
+-- type is simply a wrapper around a 'String', but the newtype
+-- allows us to give it a separate 'Default' instance.
--
module ConnectionString (
ConnectionString(..) )
where
+-- System imports.
-- DC is needed only for the DCT.Configured instance of String.
import qualified Data.Configurator as DC()
import qualified Data.Configurator.Types as DCT (
import System.Console.CmdArgs.Default (Default(..))
import Data.Typeable (Typeable)
+
-- | A newtype around a string that allows us to give a more
-- appropriate default value for a connection string.
--
ConnectionString { get_connection_string :: String }
deriving (Data, Show, Typeable)
+
instance Default ConnectionString where
-- | This default is appropriate for SQLite databases which require
-- no authentication and live entirely in a file (or in this case,
merge_maybes )
where
+-- System imports.
import qualified Data.Configurator as DC (
Worth(Optional),
load,
import System.Log ( Priority(..) )
import Text.Read ( readMaybe )
+-- Local imports.
import Backend ( Backend(..) )
import ConnectionString ( ConnectionString )
import Network.Services.TSN.Report ( report_error )
deriving instance Data Priority
deriving instance Typeable Priority
--- | The same as Configuration, except everything is optional. It's easy to
--- merge two of these by simply dropping the Nothings in favor of
--- the Justs. The 'feed_hosts' are left un-maybed so that cmdargs
--- can parse more than one of them.
+-- | The same as 'Configuration', except everything is optional. It's
+-- easy to merge two of these by simply dropping the 'Nothing's in
+-- favor of the 'Just's. The 'xml_files' are left un-maybed so that
+-- cmdargs can parse more than one of them.
--
data OptionalConfiguration =
OptionalConfiguration {
merge_maybes (Just _) (Just y) = Just y
--- | The Monoid instance for these lets us "combine" two
--- OptionalConfigurations. The "combine" operation that we'd like to
+-- | The Monoid instance for these lets us \"combine\" two
+-- OptionalConfigurations. The \"combine\" operation that we'd like to
-- perform is, essentially, to mash them together. So if we have two
-- OptionalConfigurations, each half full, we could combine them
-- into one big one.
tsn_db_field_namer _ _ _ fieldname _ =
(join "_") . tail . (split "_") $ fieldname
+
-- | An expression field name creator. \"Expression\" in the context
-- of Groundhog means a constructor/type that you can use in queries
-- and update statement. We take the field name (from a record type)
-- | Definition of the DbImport typeclass.
+--
+-- When we parse an XML tree, there are two functions that we would
+-- like to call on the result independent of its type. First, we
+-- would like to be able to run the database migrations for that
+-- type. The migrations are kept separate from insertion because, at
+-- some later point, it make make sense to disable automatic
+-- migrations.
+--
+-- Next we want to import the thing.
+--
+-- Neither of these should depend on the type -- we should just be
+-- able to call 'dbmigrate' followed by 'dbimport' on the
+-- datastructure and have the right thing happen. That is the
+-- purpose of the 'DbImport' typeclass. It allows the XML types to
+-- define their own \"migrate me\" and \"insert me\" functions that
+-- the rest of the application doesn't have to care about.
+--
module TSN.DbImport (
DbImport(..),
ImportResult(..),
-- The second field should contain info.
--- | Instances of this type know how to insert themselves into a
--- Groundhog database.
+-- | Instances of this type know how to run their own database
+-- migrations and insert themselves into a database.
--
class DbImport a where
-- | Import an instance of type @a@.
dbimport :: (PersistBackend m) => a -> m ImportResult
-- | This must migrate *all* stuffs that can potentially be
- -- created/used by the type @a@.
+ -- created/used by the type @a@.
dbmigrate :: (MonadIO m, PersistBackend m) => a -> m ()
-- | The simplest possible implementation of 'dbimport', for types
--- which happen to be members of the XmlImport typeclass.
+-- which happen to be members of the 'XmlImport' typeclass.
--
dbimport_generic :: (XmlImport a, MonadIO m, PersistBackend m)
=> a
-- | A migration runner that will use our normal info reporting
-- mechanism.
+--
run_dbmigrate :: (MonadIO m, PersistBackend m) => Migration m -> m ()
run_dbmigrate =
runMigration pretty_migration_logger
xp_team_id )
where
+-- System imports.
import Data.Time.Clock ( UTCTime )
import Data.Time.Format ( formatTime, parseTime )
import System.Locale ( defaultTimeLocale )
from_date = formatTime defaultTimeLocale format
--- | Parse a team_id. This *should* just be an 'Int', but TSN is doing
+-- | Parse a team_id. This /should/ just be an 'Int', but TSN is doing
-- something weird. First of all, player IDs do look like normal
-- 'Int's. But the team IDs are all stuck in the triple digits, and
-- double-digit team IDs appear to be padded to three characters
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
+-- | Definition of the XmlImport class.
+--
module TSN.XmlImport (
XmlImport(..) )
where
import Xml ( FromXml(..) )
+-- | In Groundhog, there is a typeclass of things you can insert into
+-- the database. What we usually have, though, is an XML
+-- representation of something that has a Groundhog analogue that we
+-- could insert into the database. It would be real nice if we could
+-- just insert the XML thing and not have to convert back and
+-- forth. That's what the 'XmlImport' class lets you do.
+--
+-- Moreover, there is a contraint on the class that the type must
+-- also be a member of the 'FromXml' class. This allows us to define
+-- default implementations of \"insert me\" generically. Given any
+-- XML thing that can be converted to a database thing, we just do
+-- the conversion and then insert normally (however Groundhog would
+-- do it).
+--
class (FromXml a, PersistEntity (Db a)) => XmlImport a where
-- | This is similar to the signature for Groundhog's 'insert'
-- function, except the 'AutoKey' we return is for our 'Db'