{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}


{- |

 Columns can be required or optional and, independently, nullable or
 non-nullable.

 A required non-nullable @SqlInt4@ (for example) is created with
 'required' and gives rise to a

 @
 TableFields (Column SqlInt4) (Column SqlInt4)
 @

 The leftmost argument is the type of writes. When you insert or
 update into this column you must give it a @Column SqlInt4@ (which you
 can create with @sqlInt4 :: Int -> Column SqlInt4@).

 A required nullable @SqlInt4@ is created with 'required' and gives rise
 to a

 @
 TableFields (Column (Nullable SqlInt4)) (Column (Nullable SqlInt4))
 @

 When you insert or update into this column you must give it a @Column
 (Nullable SqlInt4)@, which you can create either with @sqlInt4@ and
 @toNullable :: Column a -> Column (Nullable a)@, or with @null ::
 Column (Nullable a)@.

 An optional non-nullable @SqlInt4@ is created with 'optional' and gives
 rise to a

 @
 TableFields (Maybe (Column SqlInt4)) (Column SqlInt4)
 @

 Optional columns are those that can be omitted on writes, such as
 those that have @DEFAULT@s or those that are @SERIAL@.
 When you insert or update into this column you must give it a @Maybe
 (Column SqlInt4)@. If you provide @Nothing@ then the column will be
 omitted from the query and the default value will be used. Otherwise
 you have to provide a @Just@ containing a @Column SqlInt4@.

 An optional nullable @SqlInt4@ is created with 'optional' and gives
 rise to a

 @
 TableFields (Maybe (Column (Nullable SqlInt4))) (Column (Nullable SqlInt4))
 @

 Optional columns are those that can be omitted on writes, such as
 those that have @DEFAULT@s or those that are @SERIAL@.
 When you insert or update into this column you must give it a @Maybe
 (Column (Nullable SqlInt4))@. If you provide @Nothing@ then the default
 value will be used. Otherwise you have to provide a @Just@ containing
 a @Column (Nullable SqlInt4)@ (which can be null).

-}

module Opaleye.Table (-- * Creating tables
                      table,
                      tableWithSchema,
                      T.Table,
                      T.tableColumn,
                      T.tableField,
                      T.optional,
                      T.required,
                      -- * Querying tables
                      selectTable,
                      -- * Other
                      T.TableColumns,
                      TableFields,
                      -- * Deprecated
                      View,
                      Writer,
                      T.Table(T.Table, T.TableWithSchema),
                      -- * Module reexport
                      module Opaleye.Table) where

import qualified Opaleye.Internal.QueryArr as Q
import qualified Opaleye.Internal.Table as T
import           Opaleye.Internal.Table (View, Table, Writer,
                                         TableFields)

import qualified Opaleye.Internal.Tag as Tag
import qualified Opaleye.Internal.Unpackspec as U

import qualified Opaleye.Select                  as S

import qualified Data.Profunctor.Product.Default as D

-- | Example type specialization:
--
-- @
-- selectTable :: Table w (Column a, Column b)
--             -> Select (Column a, Column b)
-- @
--
-- Assuming the @makeAdaptorAndInstance@ splice has been run for the
-- product type @Foo@:
--
-- @
-- selectTable :: Table w (Foo (Column a) (Column b) (Column c))
--             -> Select (Foo (Column a) (Column b) (Column c))
-- @
selectTable :: D.Default U.Unpackspec fields fields
            => Table a fields
            -- ^
            -> S.Select fields
selectTable = selectTableExplicit D.def

-- | Create a table with unqualified names.
table :: String
      -- ^ Table name
      -> TableFields writeFields viewFields
      -> Table writeFields viewFields
table = T.Table

-- | Create a table.
tableWithSchema :: String
                -- ^ Schema name
                -> String
                -- ^ Table name
                -> TableFields writeFields viewFields
                -> Table writeFields viewFields
tableWithSchema = T.TableWithSchema

-- * Explicit versions

selectTableExplicit :: U.Unpackspec tablefields fields
                    -- ^
                    -> Table a tablefields
                    -- ^
                    -> S.Select fields
selectTableExplicit cm table' = Q.simpleQueryArr f where
  f ((), t0) = (retwires, primQ, Tag.next t0) where
    (retwires, primQ) = T.queryTable cm table' t0

-- * Deprecated versions

-- | Use 'selectTable' instead.  Will be deprecated in version 0.7.
queryTable :: D.Default U.Unpackspec fields fields =>
              Table a fields -> S.Select fields
queryTable = selectTable

-- | Use 'selectTableExplicit' instead.  Will be deprecated in version
-- 0.7.
queryTableExplicit :: U.Unpackspec tablefields fields ->
                     Table a tablefields -> S.Select fields
queryTableExplicit = selectTableExplicit