{-- | Module : TransferPlan Description : Logic for reading and writing transfer plan configuration options. Copyright : (c) Mihai Giurgeanu, 2017 License : GPL-3 Maintainer : mihai.giurgeanu@gmail.com Stability : experimental Portability : Portable --} -- Allow to use Text literals {-# LANGUAGE OverloadedStrings #-} module TransferPlan where import Data.Yaml.Aeson (ToJSON(toJSON, toEncoding), FromJSON(parseJSON), Value(Object), object, (.=), (.:), (.:?)) import Data.Aeson (pairs) import Data.Aeson.Types (typeMismatch) import Data.Semigroup ((<>)) -- | information about the source and destination data sources, about -- the data that should be transferred and about how to split this data -- in batches data TransferPlan = TransferPlan { plan_Source :: DatabaseScope, -- ^ defines the source database connection and schema plan_Destination :: DatabaseScope, -- ^ defines the destination database connection and schema plan_Batches :: [Batch] -- ^ defines what data should be transferred between the 2 scopes } instance ToJSON TransferPlan where toJSON x = object ["source" .= plan_Source x, "destination" .= plan_Destination x, "batches" .= plan_Batches x] toEncoding x = pairs ("source" .= plan_Source x <> "destination" .= plan_Destination x <> "batches" .= plan_Batches x) instance FromJSON TransferPlan where parseJSON (Object x) = TransferPlan <$> x .: "source" <*> x .: "destination" <*> x .: "batches" parseJSON invalid = typeMismatch "TransferPlan" invalid -- | information for locating the tables in the source and destination databases data DatabaseScope = Scope { scope_Db :: String, -- ^ data source name scope_UserName :: String, -- ^ user name to connect to the data source scope_Password :: String, -- ^ password to connect to the data source scope_Schema :: String -- ^ the schema for source or destination tables } instance ToJSON DatabaseScope where toJSON x = object ["db" .= scope_Db x, "user" .= scope_UserName x, "password" .= scope_Password x, "schema" .= scope_Schema x] toEncoding x = pairs ("db" .= scope_Db x <> "user" .= scope_UserName x <> "password" .= scope_Password x <> "schema" .= scope_Schema x) instance FromJSON DatabaseScope where parseJSON (Object x) = do db <- x .: "db" user' <- x .:? "user" password' <- x .:? "password" schema' <- x .:? "schema" let user = maybe "" id user' password = maybe "" id password' schema = maybe user id schema' return $ Scope db user password schema parseJSON invalid = typeMismatch "DatabaseScope" invalid data Batch = Batch { batch_Name :: String, -- ^ a name identifying the batch to the user; it is used in log messages batch_Items :: [BatchItem] -- ^ each batch item defines what data in a table will be transferred in that batch } instance ToJSON Batch where toJSON x = object ["name" .= batch_Name x, "items" .= batch_Items x] toEncoding x = pairs ("name" .= batch_Name x <> "items" .= batch_Items x) instance FromJSON Batch where parseJSON (Object x) = Batch <$> x .: "name" <*> x .: "items" parseJSON invalid = typeMismatch "Batch" invalid data BatchItem = BatchItem { batch_Table :: String, -- ^ the table name in the source database batch_OrderBy :: Maybe [ColumnName], -- ^ the columns the query should be ordered by; usually the keys by witch we split the batch batch_Where :: Maybe WhereCondition -- ^ the where clause to select the records in this batch } instance ToJSON BatchItem where toJSON x = object ["table" .= batch_Table x, "orderBy" .= batch_OrderBy x, "where" .= batch_Where x] toEncoding x = pairs ps where ps = case batch_Where x of Nothing -> psOrderAndTable y -> psOrderAndTable <> "where" .= y psOrderAndTable = case batch_OrderBy x of Nothing -> psTable y -> psTable <> "orderBy" .= y psTable = "table" .= batch_Table x instance FromJSON BatchItem where parseJSON (Object x) = do table <- x .: "table" orderBy <- x .:? "orderBy" whereClause <- x .:? "where" let orderBy' = maybe Nothing listOrNothing orderBy whereClause' = maybe Nothing listOrNothing whereClause return $ BatchItem table orderBy' whereClause' parseJSON invalid = typeMismatch "BatchOption" invalid -- | returns Nothing for an empty parameter list listOrNothing :: [a] -> Maybe [a] listOrNothing [] = Nothing listOrNothing x = Just x type ColumnName = String type WhereCondition = String