-- |
-- Module      : Database.Relational.Monad.Trans.JoinState
-- Copyright   : 2013-2017 Kei Hibino
-- License     : BSD3
--
-- Maintainer  : ex8k.hibino@gmail.com
-- Stability   : experimental
-- Portability : unknown
--
-- This module provides state definition for
-- "Database.Relational.Monad.Trans.Join".
--
-- This is not public interface.
module Database.Relational.Monad.Trans.JoinState (
  -- * Join context
  JoinContext, primeJoinContext, updateProduct, joinProduct
  ) where

import Prelude hiding (product)
import Data.DList (DList, toList)

import Database.Relational.Internal.ContextType (Flat)
import Database.Relational.SqlSyntax (JoinProduct, Node, Predicate)
import qualified Database.Relational.SqlSyntax as Product


-- | JoinContext type for QueryJoin.
newtype JoinContext =
  JoinContext
  { JoinContext -> Maybe (Node (DList (Predicate Flat)))
product  :: Maybe (Node (DList (Predicate Flat)))
  }

-- | Initial 'JoinContext'.
primeJoinContext :: JoinContext
primeJoinContext :: JoinContext
primeJoinContext =  Maybe (Node (DList (Predicate Flat))) -> JoinContext
JoinContext forall a. Maybe a
Nothing

-- | Update product of 'JoinContext'.
updateProduct :: (Maybe (Node (DList (Predicate Flat))) -> Node (DList (Predicate Flat)))
              -> JoinContext
              -> JoinContext
updateProduct :: (Maybe (Node (DList (Predicate Flat)))
 -> Node (DList (Predicate Flat)))
-> JoinContext -> JoinContext
updateProduct Maybe (Node (DList (Predicate Flat)))
-> Node (DList (Predicate Flat))
uf JoinContext
ctx = JoinContext
ctx { product :: Maybe (Node (DList (Predicate Flat)))
product = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (Node (DList (Predicate Flat)))
-> Node (DList (Predicate Flat))
uf forall b c a. (b -> c) -> (a -> b) -> a -> c
. JoinContext -> Maybe (Node (DList (Predicate Flat)))
product forall a b. (a -> b) -> a -> b
$ JoinContext
ctx }

-- |  Finalize context to extract accumulated query product.
joinProduct :: JoinContext -> JoinProduct
joinProduct :: JoinContext -> JoinProduct
joinProduct =  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. DList a -> [a]
toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall rs. Node rs -> ProductTree rs
Product.nodeTree) forall b c a. (b -> c) -> (a -> b) -> a -> c
. JoinContext -> Maybe (Node (DList (Predicate Flat)))
product