Expose the new functions and fix the mysql test compilation error (type inference was wonky with Union replaced with union_
This commit is contained in:
parent
dd8814e678
commit
75619fecb7
@ -19,8 +19,10 @@ module Database.Esqueleto.Experimental
|
||||
-- * Documentation
|
||||
|
||||
Table(..)
|
||||
, table
|
||||
, from
|
||||
, SubQuery(..)
|
||||
, selectQuery
|
||||
, (:&)(..)
|
||||
, on
|
||||
|
||||
@ -40,6 +42,15 @@ module Database.Esqueleto.Experimental
|
||||
, with
|
||||
, withRecursive
|
||||
|
||||
, innerJoin
|
||||
, innerJoinLateral
|
||||
, leftJoin
|
||||
, leftJoinLateral
|
||||
, rightJoin
|
||||
, fullOuterJoin
|
||||
, crossJoin
|
||||
, crossJoinLateral
|
||||
|
||||
-- * Internals
|
||||
, From(..)
|
||||
, ToMaybe(..)
|
||||
|
||||
@ -583,18 +583,6 @@ withNonNull field f = do
|
||||
where_ $ not_ $ isNothing field
|
||||
f $ veryUnsafeCoerceSqlExprValue field
|
||||
|
||||
class (PersistEntity ent, PersistField val)
|
||||
=> MaybeHasSqlField entity ent value val
|
||||
| entity val -> value
|
||||
, entity value -> val
|
||||
, entity -> ent
|
||||
, value ent val -> entity where
|
||||
instance (PersistEntity ent, PersistField val)
|
||||
=> MaybeHasSqlField (Maybe (Entity ent)) ent (Maybe val) val
|
||||
|
||||
class WithMaybe noMaybe withMaybe | withMaybe -> noMaybe
|
||||
instance WithMaybe a (Maybe a)
|
||||
|
||||
-- | Project a field of an entity that may be null.
|
||||
(?.) :: ( PersistEntity val , PersistField typ)
|
||||
=> SqlExpr (Maybe (Entity val))
|
||||
|
||||
@ -1,27 +1,28 @@
|
||||
{-# LANGUAGE ScopedTypeVariables
|
||||
, FlexibleContexts
|
||||
, RankNTypes
|
||||
, TypeFamilies
|
||||
, TypeApplications
|
||||
#-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
|
||||
module Main (main) where
|
||||
|
||||
import Control.Monad (void)
|
||||
import Control.Monad.IO.Class (MonadIO(liftIO))
|
||||
import Control.Monad.Logger (runStderrLoggingT, runNoLoggingT)
|
||||
import Control.Monad.Logger (runNoLoggingT, runStderrLoggingT)
|
||||
import Control.Monad.Trans.Reader (ReaderT)
|
||||
import Database.Persist.MySQL ( withMySQLConn
|
||||
, connectHost
|
||||
, connectDatabase
|
||||
, connectUser
|
||||
, connectPassword
|
||||
, connectPort
|
||||
, defaultConnectInfo)
|
||||
import qualified Control.Monad.Trans.Resource as R
|
||||
import Database.Esqueleto
|
||||
import Database.Esqueleto.Experimental hiding (from, on)
|
||||
import qualified Database.Esqueleto.Experimental as Experimental
|
||||
import qualified Control.Monad.Trans.Resource as R
|
||||
import Database.Persist.MySQL
|
||||
( connectDatabase
|
||||
, connectHost
|
||||
, connectPassword
|
||||
, connectPort
|
||||
, connectUser
|
||||
, defaultConnectInfo
|
||||
, withMySQLConn
|
||||
)
|
||||
import Test.Hspec
|
||||
|
||||
import Common.Test
|
||||
@ -187,7 +188,7 @@ testMysqlUnionWithLimits = do
|
||||
pure $ foo ^. FooName
|
||||
|
||||
|
||||
ret <- select $ Experimental.from $ SelectQuery q1 `Union` SelectQuery q2
|
||||
ret <- select $ Experimental.from $ q1 `union_` q2
|
||||
liftIO $ ret `shouldMatchList` [Value 1, Value 2, Value 4, Value 5]
|
||||
|
||||
|
||||
|
||||
Loading…
Reference in New Issue
Block a user