Reorganize Experimental folder. Move Subquery into core Experimental.From module.

This commit is contained in:
belevy 2020-11-08 21:03:37 -06:00
parent a8f8c87000
commit 7b59829f3e
7 changed files with 66 additions and 81 deletions

View File

@ -41,11 +41,10 @@ library
other-modules:
Database.Esqueleto.Internal.PersistentImport
Database.Esqueleto.PostgreSQL.JSON.Instances
Database.Esqueleto.Experimental.CommonTableExpression
Database.Esqueleto.Experimental.Internal
Database.Esqueleto.Experimental.Join
Database.Esqueleto.Experimental.SqlSetOperation
Database.Esqueleto.Experimental.SubQuery
Database.Esqueleto.Experimental.From
Database.Esqueleto.Experimental.From.CommonTableExpression
Database.Esqueleto.Experimental.From.Join
Database.Esqueleto.Experimental.From.SqlSetOperation
Database.Esqueleto.Experimental.ToAlias
Database.Esqueleto.Experimental.ToAliasReference
Database.Esqueleto.Experimental.ToMaybe

View File

@ -207,11 +207,10 @@ module Database.Esqueleto.Experimental
import Database.Esqueleto.Internal.Internal hiding (From, from, on)
import Database.Esqueleto.Internal.PersistentImport
import Database.Esqueleto.Experimental.CommonTableExpression
import Database.Esqueleto.Experimental.Internal
import Database.Esqueleto.Experimental.Join
import Database.Esqueleto.Experimental.SqlSetOperation
import Database.Esqueleto.Experimental.SubQuery
import Database.Esqueleto.Experimental.From.CommonTableExpression
import Database.Esqueleto.Experimental.From
import Database.Esqueleto.Experimental.From.Join
import Database.Esqueleto.Experimental.From.SqlSetOperation
import Database.Esqueleto.Experimental.ToAlias
import Database.Esqueleto.Experimental.ToAliasReference
import Database.Esqueleto.Experimental.ToMaybe

View File

@ -1,17 +1,63 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Database.Esqueleto.Experimental.SubQuery
module Database.Esqueleto.Experimental.From
where
import qualified Control.Monad.Trans.Writer as W
import Database.Esqueleto.Experimental.Internal
import Data.Proxy
import Database.Esqueleto.Internal.Internal hiding (From(..), from, on)
import Database.Esqueleto.Internal.PersistentImport
import Database.Esqueleto.Experimental.ToAlias
import Database.Esqueleto.Experimental.ToAliasReference
import Database.Esqueleto.Internal.Internal hiding (From(..), from, on)
import Database.Esqueleto.Internal.PersistentImport (DBName(..))
-- | 'FROM' clause, used to bring entities into scope.
--
-- Internally, this function uses the `From` datatype and the
-- `From` typeclass. Unlike the old `Database.Esqueleto.from`,
-- this does not take a function as a parameter, but rather
-- a value that represents a 'JOIN' tree constructed out of
-- instances of `From`. This implementation eliminates certain
-- types of runtime errors by preventing the construction of
-- invalid SQL (e.g. illegal nested-@from@).
from :: From a => a -> SqlQuery (FromT a)
from parts = do
(a, clause) <- runFrom parts
Q $ W.tell mempty{sdFromClause=[clause]}
pure a
class From a where
type FromT a
runFrom :: a -> SqlQuery (FromT a, FromClause)
-- | Data type for bringing a Table into scope in a JOIN tree
--
-- @
-- select $ from $ Table \@People
-- @
data Table a = Table
instance PersistEntity a => From (Table a) where
type FromT (Table a) = SqlExpr (Entity a)
runFrom e@Table = do
let ed = entityDef $ getVal e
ident <- newIdentFor (entityDB ed)
let entity = EEntity ident
pure $ (entity, FromStart ident ed)
where
getVal :: Table ent -> Proxy ent
getVal = const Proxy
{-# DEPRECATED SubQuery "/Since: 3.4.0.0/ - It is no longer necessary to tag 'SqlQuery' values with @SubQuery@" #-}
newtype SubQuery a = SubQuery a

View File

@ -2,13 +2,13 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
module Database.Esqueleto.Experimental.CommonTableExpression
module Database.Esqueleto.Experimental.From.CommonTableExpression
where
import qualified Control.Monad.Trans.Writer as W
import qualified Data.Text.Lazy.Builder as TLB
import Database.Esqueleto.Experimental.Internal
import Database.Esqueleto.Experimental.SqlSetOperation
import Database.Esqueleto.Experimental.From
import Database.Esqueleto.Experimental.From.SqlSetOperation
import Database.Esqueleto.Experimental.ToAlias
import Database.Esqueleto.Experimental.ToAliasReference
import Database.Esqueleto.Internal.Internal hiding (From(..), from, on)

View File

@ -5,14 +5,13 @@
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Database.Esqueleto.Experimental.Join
module Database.Esqueleto.Experimental.From.Join
where
import Data.Kind (Constraint)
import Data.Proxy
import Database.Esqueleto.Experimental.Internal
import Database.Esqueleto.Experimental.SqlSetOperation
import Database.Esqueleto.Experimental.SubQuery
import Database.Esqueleto.Experimental.From
import Database.Esqueleto.Experimental.From.SqlSetOperation
import Database.Esqueleto.Experimental.ToAlias
import Database.Esqueleto.Experimental.ToAliasReference
import Database.Esqueleto.Experimental.ToMaybe

View File

@ -7,14 +7,13 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Database.Esqueleto.Experimental.SqlSetOperation
module Database.Esqueleto.Experimental.From.SqlSetOperation
where
import Control.Monad.Trans.Class (lift)
import qualified Control.Monad.Trans.State as S
import qualified Control.Monad.Trans.Writer as W
import Database.Esqueleto.Experimental.Internal
import Database.Esqueleto.Experimental.SubQuery
import Database.Esqueleto.Experimental.From
import Database.Esqueleto.Experimental.ToAlias
import Database.Esqueleto.Experimental.ToAliasReference
import Database.Esqueleto.Internal.Internal hiding (From(..), from, on)

View File

@ -1,57 +0,0 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Database.Esqueleto.Experimental.Internal
where
import qualified Control.Monad.Trans.Writer as W
import Data.Proxy
import Database.Esqueleto.Internal.Internal hiding (From(..), from, on)
import Database.Esqueleto.Internal.PersistentImport
-- | 'FROM' clause, used to bring entities into scope.
--
-- Internally, this function uses the `From` datatype and the
-- `From` typeclass. Unlike the old `Database.Esqueleto.from`,
-- this does not take a function as a parameter, but rather
-- a value that represents a 'JOIN' tree constructed out of
-- instances of `From`. This implementation eliminates certain
-- types of runtime errors by preventing the construction of
-- invalid SQL (e.g. illegal nested-@from@).
from :: From a => a -> SqlQuery (FromT a)
from parts = do
(a, clause) <- runFrom parts
Q $ W.tell mempty{sdFromClause=[clause]}
pure a
class From a where
type FromT a
runFrom :: a -> SqlQuery (FromT a, FromClause)
-- | Data type for bringing a Table into scope in a JOIN tree
--
-- @
-- select $ from $ Table \@People
-- @
data Table a = Table
instance PersistEntity a => From (Table a) where
type FromT (Table a) = SqlExpr (Entity a)
runFrom e@Table = do
let ed = entityDef $ getVal e
ident <- newIdentFor (entityDB ed)
let entity = EEntity ident
pure $ (entity, FromStart ident ed)
where
getVal :: Table ent -> Proxy ent
getVal = const Proxy