Removes FactColumnType pattern synonyms to simplify the code.

pull/1/head
Abhinav Sarkar 2016-06-22 16:52:04 +05:30
parent b912e451f7
commit ade13f767b
7 changed files with 13 additions and 40 deletions

View File

@ -2,7 +2,6 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PatternSynonyms #-}
module Ringo.Generator.Create (dimensionTableDefnSQL, factTableDefnSQL) where
@ -78,8 +77,8 @@ factTableIndexStmts fact table = do
Settings {..} <- asks envSettings
tables <- asks envTables
let dimTimeCol = head [ cName | DimTimeV cName <- factColumns fact ]
tenantIdCol = listToMaybe [ cName | TenantIdV cName <- factColumns fact ]
let dimTimeCol = head [ cName | FactColumn cName DimTime <- factColumns fact ]
tenantIdCol = listToMaybe [ cName | FactColumn cName TenantId <- factColumns fact ]
tabName = tableName table <> settingTableNameSuffixTemplate
dimTimeColName cName = timeUnitColumnName settingDimTableIdColumnName cName settingTimeUnit

View File

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE GADTs #-}
module Ringo.Generator.Populate.Dimension (dimensionTablePopulateSQL) where
@ -34,7 +34,7 @@ dimensionTablePopulateStmt popMode fact dimTableName = withReader envView $ do
selectCols = [ flip sia (nmc cName) $ coalesceColumn defaults (factTableName fact) col
| (_, cName) <- colMapping
, let col = fromJust . findColumn cName $ tableColumns factTable ]
timeCol = head ([ cName | DimTimeV cName <- factColumns fact ] :: [ColumnName])
timeCol = head ([ cName | FactColumn cName DimTime <- factColumns fact ] :: [ColumnName])
isNotNullC = parens . foldBinop "or" . map (postop "isnotnull" . ei . snd) $ colMapping
selectWhereC = Just . foldBinop "and" $
[ isNotNullC, binop "<" (ei timeCol) placeholder ] ++

View File

@ -5,7 +5,6 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PatternSynonyms #-}
module Ringo.Generator.Populate.Fact (factTablePopulateSQL) where
@ -201,7 +200,7 @@ factTablePopulateStmts popMode fact = do
. map (factTableName . fst)
$ allDims
timeCol = eqi fTableName $ head [ cName | DimTimeV cName <- factColumns fact ]
timeCol = eqi fTableName $ head [ cName | FactColumn cName DimTime <- factColumns fact ]
extFactTableName = suffixTableName popMode settingTableNameSuffixTemplate
$ extractedFactTableName settingFactPrefix settingFactInfix (factName fact) settingTimeUnit

View File

@ -3,24 +3,12 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE PatternSynonyms #-}
module Ringo.Types
( ColumnName, ColumnType, TableName
, Nullable(..), Column(..), TableConstraint(..), Table(..)
, TimeUnit(..), timeUnitName, timeUnitToSeconds
, Fact(..), FactColumnType(..), FactColumn(..), factSourceColumnName
, pattern DimTimeV
, pattern NoDimIdV
, pattern TenantIdV
, pattern DimIdV
, pattern DimValV
, pattern FactCountV
, pattern FactCountDistinctV
, pattern FactSumV
, pattern FactAverageV
, pattern FactMaxV
, pattern FactMinV
, Settings(..), defSettings
, ValidationError(..), TypeDefaults
, Env, EnvV(..), envView

View File

@ -3,7 +3,6 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE PatternSynonyms #-}
module Ringo.Types.Internal where
@ -99,18 +98,6 @@ data FactColumnType a where
deriving instance Show (FactColumnType a)
pattern DimTimeV col <- FactColumn col DimTime
pattern NoDimIdV col <- FactColumn col NoDimId
pattern TenantIdV col <- FactColumn col TenantId
pattern DimIdV col <- FactColumn col DimId {..}
pattern DimValV col <- FactColumn col DimVal {..}
pattern FactCountV col <- FactColumn col FactCount {..}
pattern FactCountDistinctV col <- FactColumn col FactCountDistinct {..}
pattern FactSumV col <- FactColumn col FactSum {..}
pattern FactAverageV col <- FactColumn col FactAverage {..}
pattern FactMaxV col <- FactColumn col FactMax {..}
pattern FactMinV col <- FactColumn col FactMin {..}
data FactColumn = forall a. FactColumn
{ factColTargetColumn :: !ColumnName
, factColType :: FactColumnType a }

View File

@ -56,19 +56,19 @@ validateFact Fact {..} = do
parentVs <- concat <$> mapM checkFactParents factParentNames
let colVs = concatMap (checkColumn tables table) factColumns
timeVs = [ MissingTimeColumn factTableName
| null ([ cName | DimTimeV cName <- factColumns ] :: [ColumnName]) ]
| null ([ cName | FactColumn cName DimTime <- factColumns ] :: [ColumnName]) ]
notNullVs = [ MissingNotNullConstraint factTableName cName
| DimTimeV cName <- factColumns
, let col = findColumn cName (tableColumns table)
| FactColumn cName DimTime <- factColumns
, let col = findColumn cName (tableColumns table)
, isJust col
, columnNullable (fromJust col) == Null ]
typeDefaultVs =
[ MissingTypeDefault cType
| cName <- [ c | DimValV c <- factColumns ]
++ [ c | NoDimIdV c <- factColumns ]
++ [ c | TenantIdV c <- factColumns ]
++ [ c | DimIdV c <- factColumns ]
| cName <- [ c | FactColumn c DimVal {..} <- factColumns ]
++ [ c | FactColumn c NoDimId <- factColumns ]
++ [ c | FactColumn c TenantId <- factColumns ]
++ [ c | FactColumn c DimId {..} <- factColumns ]
, let col = findColumn cName (tableColumns table)
, isJust col
, let cType = columnType $ fromJust col

View File

@ -1,7 +1,7 @@
# For more information, see: https://github.com/commercialhaskell/stack/blob/master/doc/yaml_configuration.md
# Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2)
resolver: lts-5.1
resolver: lts-6.4
# Local packages, usually specified by relative directory name
packages: