{-# LANGUAGE UndecidableInstances #-}
module Hasura.Backends.MySQL.DataLoader.Execute
( OutputValue (..),
RecordSet (..),
ExecuteProblem (..),
execute,
runExecute,
joinObjectRows,
leftObjectJoin,
)
where
import Control.Monad.IO.Class
import Data.Aeson hiding (Value)
import Data.Aeson qualified as J
import Data.Bifunctor
import Data.Foldable
import Data.Graph
import Data.HashMap.Strict.InsOrd qualified as OMap
import Data.IORef
import Data.Vector (Vector)
import Data.Vector qualified as V
import GHC.TypeLits qualified
import Hasura.Backends.MySQL.Connection (runQueryYieldingRows)
import Hasura.Backends.MySQL.DataLoader.Plan
( Action (..),
FieldName (..),
HeadAndTail (..),
Join
( joinFieldName,
joinRhsOffset,
joinRhsTop,
joinType,
leftRecordSet,
rightRecordSet
),
PlannedAction (..),
Ref,
selectQuery,
toFieldName,
)
import Hasura.Backends.MySQL.DataLoader.Plan qualified as DataLoaderPlan
import Hasura.Backends.MySQL.DataLoader.Plan qualified as Plan
import Hasura.Backends.MySQL.ToQuery (fromSelect, toQueryFlat)
import Hasura.Backends.MySQL.Types hiding
( FieldName,
ScalarValue,
selectWhere,
)
import Hasura.GraphQL.Parser ()
import Hasura.Prelude hiding
( concatMap,
elem,
head,
map,
mapMaybe,
tail,
toList,
)
data RecordSet = RecordSet
{ RecordSet -> Maybe PlannedAction
origin :: Maybe PlannedAction,
RecordSet -> Vector (InsOrdHashMap FieldName OutputValue)
rows :: Vector (InsOrdHashMap FieldName OutputValue),
RecordSet -> Maybe [Text]
wantedFields :: Maybe [Text]
}
deriving (Int -> RecordSet -> ShowS
[RecordSet] -> ShowS
RecordSet -> String
(Int -> RecordSet -> ShowS)
-> (RecordSet -> String)
-> ([RecordSet] -> ShowS)
-> Show RecordSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecordSet] -> ShowS
$cshowList :: [RecordSet] -> ShowS
show :: RecordSet -> String
$cshow :: RecordSet -> String
showsPrec :: Int -> RecordSet -> ShowS
$cshowsPrec :: Int -> RecordSet -> ShowS
Show)
instance GHC.TypeLits.TypeError ('GHC.TypeLits.Text "Aeson loses key order, so you can't use this instance.") => ToJSON RecordSet where
toJSON :: RecordSet -> Value
toJSON RecordSet {} = String -> Value
forall a. HasCallStack => String -> a
error String
"RecordSet.toJSON: do not use."
data ExecuteReader = ExecuteReader
{ ExecuteReader -> IORef (InsOrdHashMap Ref RecordSet)
recordSets :: IORef (InsOrdHashMap Ref RecordSet),
ExecuteReader -> SourceConfig
credentials :: SourceConfig
}
data ExecuteProblem
= GetJobDecodeProblem String
| CreateQueryJobDecodeProblem String
| JoinProblem ExecuteProblem
| UnsupportedJoinBug JoinType
| MissingRecordSetBug Ref
| BrokenJoinInvariant [DataLoaderPlan.FieldName]
deriving (Int -> ExecuteProblem -> ShowS
[ExecuteProblem] -> ShowS
ExecuteProblem -> String
(Int -> ExecuteProblem -> ShowS)
-> (ExecuteProblem -> String)
-> ([ExecuteProblem] -> ShowS)
-> Show ExecuteProblem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExecuteProblem] -> ShowS
$cshowList :: [ExecuteProblem] -> ShowS
show :: ExecuteProblem -> String
$cshow :: ExecuteProblem -> String
showsPrec :: Int -> ExecuteProblem -> ShowS
$cshowsPrec :: Int -> ExecuteProblem -> ShowS
Show)
newtype Execute a = Execute
{Execute a -> ReaderT ExecuteReader (ExceptT ExecuteProblem IO) a
unExecute :: ReaderT ExecuteReader (ExceptT ExecuteProblem IO) a}
deriving
( a -> Execute b -> Execute a
(a -> b) -> Execute a -> Execute b
(forall a b. (a -> b) -> Execute a -> Execute b)
-> (forall a b. a -> Execute b -> Execute a) -> Functor Execute
forall a b. a -> Execute b -> Execute a
forall a b. (a -> b) -> Execute a -> Execute b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Execute b -> Execute a
$c<$ :: forall a b. a -> Execute b -> Execute a
fmap :: (a -> b) -> Execute a -> Execute b
$cfmap :: forall a b. (a -> b) -> Execute a -> Execute b
Functor,
Functor Execute
a -> Execute a
Functor Execute
-> (forall a. a -> Execute a)
-> (forall a b. Execute (a -> b) -> Execute a -> Execute b)
-> (forall a b c.
(a -> b -> c) -> Execute a -> Execute b -> Execute c)
-> (forall a b. Execute a -> Execute b -> Execute b)
-> (forall a b. Execute a -> Execute b -> Execute a)
-> Applicative Execute
Execute a -> Execute b -> Execute b
Execute a -> Execute b -> Execute a
Execute (a -> b) -> Execute a -> Execute b
(a -> b -> c) -> Execute a -> Execute b -> Execute c
forall a. a -> Execute a
forall a b. Execute a -> Execute b -> Execute a
forall a b. Execute a -> Execute b -> Execute b
forall a b. Execute (a -> b) -> Execute a -> Execute b
forall a b c. (a -> b -> c) -> Execute a -> Execute b -> Execute c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: Execute a -> Execute b -> Execute a
$c<* :: forall a b. Execute a -> Execute b -> Execute a
*> :: Execute a -> Execute b -> Execute b
$c*> :: forall a b. Execute a -> Execute b -> Execute b
liftA2 :: (a -> b -> c) -> Execute a -> Execute b -> Execute c
$cliftA2 :: forall a b c. (a -> b -> c) -> Execute a -> Execute b -> Execute c
<*> :: Execute (a -> b) -> Execute a -> Execute b
$c<*> :: forall a b. Execute (a -> b) -> Execute a -> Execute b
pure :: a -> Execute a
$cpure :: forall a. a -> Execute a
$cp1Applicative :: Functor Execute
Applicative,
Applicative Execute
a -> Execute a
Applicative Execute
-> (forall a b. Execute a -> (a -> Execute b) -> Execute b)
-> (forall a b. Execute a -> Execute b -> Execute b)
-> (forall a. a -> Execute a)
-> Monad Execute
Execute a -> (a -> Execute b) -> Execute b
Execute a -> Execute b -> Execute b
forall a. a -> Execute a
forall a b. Execute a -> Execute b -> Execute b
forall a b. Execute a -> (a -> Execute b) -> Execute b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> Execute a
$creturn :: forall a. a -> Execute a
>> :: Execute a -> Execute b -> Execute b
$c>> :: forall a b. Execute a -> Execute b -> Execute b
>>= :: Execute a -> (a -> Execute b) -> Execute b
$c>>= :: forall a b. Execute a -> (a -> Execute b) -> Execute b
$cp1Monad :: Applicative Execute
Monad,
MonadReader ExecuteReader,
Monad Execute
Monad Execute -> (forall a. IO a -> Execute a) -> MonadIO Execute
IO a -> Execute a
forall a. IO a -> Execute a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> Execute a
$cliftIO :: forall a. IO a -> Execute a
$cp1MonadIO :: Monad Execute
MonadIO,
MonadError ExecuteProblem
)
data OutputValue
= ArrayOutputValue (Vector OutputValue)
| RecordOutputValue (InsOrdHashMap DataLoaderPlan.FieldName OutputValue)
| ScalarOutputValue J.Value
| NullOutputValue
deriving (Int -> OutputValue -> ShowS
[OutputValue] -> ShowS
OutputValue -> String
(Int -> OutputValue -> ShowS)
-> (OutputValue -> String)
-> ([OutputValue] -> ShowS)
-> Show OutputValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OutputValue] -> ShowS
$cshowList :: [OutputValue] -> ShowS
show :: OutputValue -> String
$cshow :: OutputValue -> String
showsPrec :: Int -> OutputValue -> ShowS
$cshowsPrec :: Int -> OutputValue -> ShowS
Show, OutputValue -> OutputValue -> Bool
(OutputValue -> OutputValue -> Bool)
-> (OutputValue -> OutputValue -> Bool) -> Eq OutputValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutputValue -> OutputValue -> Bool
$c/= :: OutputValue -> OutputValue -> Bool
== :: OutputValue -> OutputValue -> Bool
$c== :: OutputValue -> OutputValue -> Bool
Eq, (forall x. OutputValue -> Rep OutputValue x)
-> (forall x. Rep OutputValue x -> OutputValue)
-> Generic OutputValue
forall x. Rep OutputValue x -> OutputValue
forall x. OutputValue -> Rep OutputValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OutputValue x -> OutputValue
$cfrom :: forall x. OutputValue -> Rep OutputValue x
Generic)
instance Hashable OutputValue
runExecute ::
MonadIO m =>
SourceConfig ->
HeadAndTail ->
Execute a ->
m (Either ExecuteProblem RecordSet)
runExecute :: SourceConfig
-> HeadAndTail -> Execute a -> m (Either ExecuteProblem RecordSet)
runExecute SourceConfig
credentials HeadAndTail
headAndTail Execute a
action = do
IORef (InsOrdHashMap Ref RecordSet)
recordSets <- IO (IORef (InsOrdHashMap Ref RecordSet))
-> m (IORef (InsOrdHashMap Ref RecordSet))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (InsOrdHashMap Ref RecordSet
-> IO (IORef (InsOrdHashMap Ref RecordSet))
forall a. a -> IO (IORef a)
newIORef InsOrdHashMap Ref RecordSet
forall a. Monoid a => a
mempty)
IO (Either ExecuteProblem RecordSet)
-> m (Either ExecuteProblem RecordSet)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either ExecuteProblem RecordSet)
-> m (Either ExecuteProblem RecordSet))
-> IO (Either ExecuteProblem RecordSet)
-> m (Either ExecuteProblem RecordSet)
forall a b. (a -> b) -> a -> b
$
ExceptT ExecuteProblem IO RecordSet
-> IO (Either ExecuteProblem RecordSet)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT ExecuteProblem IO RecordSet
-> IO (Either ExecuteProblem RecordSet))
-> ExceptT ExecuteProblem IO RecordSet
-> IO (Either ExecuteProblem RecordSet)
forall a b. (a -> b) -> a -> b
$
ReaderT ExecuteReader (ExceptT ExecuteProblem IO) RecordSet
-> ExecuteReader -> ExceptT ExecuteProblem IO RecordSet
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT
(Execute RecordSet
-> ReaderT ExecuteReader (ExceptT ExecuteProblem IO) RecordSet
forall a.
Execute a -> ReaderT ExecuteReader (ExceptT ExecuteProblem IO) a
unExecute (Execute a
action Execute a -> Execute RecordSet -> Execute RecordSet
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> HeadAndTail -> Execute RecordSet
getFinalRecordSet HeadAndTail
headAndTail))
(ExecuteReader :: IORef (InsOrdHashMap Ref RecordSet)
-> SourceConfig -> ExecuteReader
ExecuteReader {SourceConfig
credentials :: SourceConfig
credentials :: SourceConfig
credentials, IORef (InsOrdHashMap Ref RecordSet)
recordSets :: IORef (InsOrdHashMap Ref RecordSet)
recordSets :: IORef (InsOrdHashMap Ref RecordSet)
recordSets})
execute :: Forest PlannedAction -> Execute ()
execute :: Forest PlannedAction -> Execute ()
execute = (Tree PlannedAction -> Execute ())
-> Forest PlannedAction -> Execute ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ ((PlannedAction -> Execute ()) -> Tree PlannedAction -> Execute ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ PlannedAction -> Execute ()
executePlannedAction)
executePlannedAction :: PlannedAction -> Execute ()
executePlannedAction :: PlannedAction -> Execute ()
executePlannedAction PlannedAction {Ref
$sel:ref:PlannedAction :: PlannedAction -> Ref
ref :: Ref
ref, Action
$sel:action:PlannedAction :: PlannedAction -> Action
action :: Action
action} =
Action -> Execute RecordSet
fetchRecordSetForAction Action
action Execute RecordSet -> (RecordSet -> Execute ()) -> Execute ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ref -> RecordSet -> Execute ()
saveRecordSet Ref
ref
fetchRecordSetForAction :: Action -> Execute RecordSet
fetchRecordSetForAction :: Action -> Execute RecordSet
fetchRecordSetForAction =
\case
SelectAction Select
select -> do
RecordSet
recordSet <- do
SourceConfig {Pool Connection
scConnectionPool :: SourceConfig -> Pool Connection
scConnectionPool :: Pool Connection
scConnectionPool} <- (ExecuteReader -> SourceConfig) -> Execute SourceConfig
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ExecuteReader -> SourceConfig
credentials
Either ExecuteProblem (Vector (InsOrdHashMap FieldName Value))
result <-
IO (Either ExecuteProblem (Vector (InsOrdHashMap FieldName Value)))
-> Execute
(Either ExecuteProblem (Vector (InsOrdHashMap FieldName Value)))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
(Either ExecuteProblem (Vector (InsOrdHashMap FieldName Value)))
-> Execute
(Either ExecuteProblem (Vector (InsOrdHashMap FieldName Value))))
-> IO
(Either ExecuteProblem (Vector (InsOrdHashMap FieldName Value)))
-> Execute
(Either ExecuteProblem (Vector (InsOrdHashMap FieldName Value)))
forall a b. (a -> b) -> a -> b
$
ExceptT ExecuteProblem IO (Vector (InsOrdHashMap FieldName Value))
-> IO
(Either ExecuteProblem (Vector (InsOrdHashMap FieldName Value)))
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT ExecuteProblem IO (Vector (InsOrdHashMap FieldName Value))
-> IO
(Either ExecuteProblem (Vector (InsOrdHashMap FieldName Value))))
-> ExceptT
ExecuteProblem IO (Vector (InsOrdHashMap FieldName Value))
-> IO
(Either ExecuteProblem (Vector (InsOrdHashMap FieldName Value)))
forall a b. (a -> b) -> a -> b
$
Pool Connection
-> Query
-> ExceptT
ExecuteProblem IO (Vector (InsOrdHashMap FieldName Value))
forall (m :: * -> *).
MonadIO m =>
Pool Connection
-> Query -> m (Vector (InsOrdHashMap FieldName Value))
runQueryYieldingRows
Pool Connection
scConnectionPool
(Printer -> Query
toQueryFlat (Select -> Printer
fromSelect (Select -> Select
selectQuery Select
select)))
case Either ExecuteProblem (Vector (InsOrdHashMap FieldName Value))
result of
Left ExecuteProblem
problem -> ExecuteProblem -> Execute RecordSet
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (ExecuteProblem -> ExecuteProblem
JoinProblem ExecuteProblem
problem)
Right Vector (InsOrdHashMap FieldName Value)
rows -> RecordSet -> Execute RecordSet
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Vector (InsOrdHashMap FieldName Value) -> RecordSet
makeRecordSet Vector (InsOrdHashMap FieldName Value)
rows)
RecordSet -> Execute RecordSet
forall (f :: * -> *) a. Applicative f => a -> f a
pure RecordSet
recordSet {wantedFields :: Maybe [Text]
wantedFields = Select -> Maybe [Text]
Plan.selectWantedFields Select
select}
JoinAction Plan.Join {$sel:joinType:Join :: Join -> JoinType
joinType = JoinType
joinType', $sel:joinFieldName:Join :: Join -> Text
joinFieldName = Text
fieldName, Maybe Int
Maybe [Text]
Top
Ref
$sel:wantedFields:Join :: Join -> Maybe [Text]
wantedFields :: Maybe [Text]
joinRhsOffset :: Maybe Int
joinRhsTop :: Top
rightRecordSet :: Ref
leftRecordSet :: Ref
$sel:rightRecordSet:Join :: Join -> Ref
$sel:leftRecordSet:Join :: Join -> Ref
$sel:joinRhsTop:Join :: Join -> Top
$sel:joinRhsOffset:Join :: Join -> Maybe Int
..} -> do
RecordSet
left <- Ref -> Execute RecordSet
getRecordSet Ref
leftRecordSet
RecordSet
right <- Ref -> Execute RecordSet
getRecordSet Ref
rightRecordSet
case JoinType
joinType' of
ArrayJoin [(FieldName, FieldName)]
fields ->
Maybe [Text]
-> Text
-> [(FieldName, FieldName)]
-> Top
-> Maybe Int
-> RecordSet
-> RecordSet
-> Either ExecuteProblem RecordSet
leftArrayJoin
Maybe [Text]
wantedFields
Text
fieldName
([(FieldName, FieldName)] -> [(FieldName, FieldName)]
toFieldNames [(FieldName, FieldName)]
fields)
Top
joinRhsTop
Maybe Int
joinRhsOffset
RecordSet
left
RecordSet
right
Either ExecuteProblem RecordSet
-> (ExecuteProblem -> Execute RecordSet) -> Execute RecordSet
forall (m :: * -> *) e a.
Applicative m =>
Either e a -> (e -> m a) -> m a
`onLeft` (ExecuteProblem -> Execute RecordSet
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (ExecuteProblem -> Execute RecordSet)
-> (ExecuteProblem -> ExecuteProblem)
-> ExecuteProblem
-> Execute RecordSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExecuteProblem -> ExecuteProblem
JoinProblem)
ObjectJoin [(FieldName, FieldName)]
fields ->
Maybe [Text]
-> Text
-> [(FieldName, FieldName)]
-> RecordSet
-> RecordSet
-> Either ExecuteProblem RecordSet
leftObjectJoin
Maybe [Text]
wantedFields
Text
fieldName
([(FieldName, FieldName)] -> [(FieldName, FieldName)]
toFieldNames [(FieldName, FieldName)]
fields)
RecordSet
left
RecordSet
right
Either ExecuteProblem RecordSet
-> (ExecuteProblem -> Execute RecordSet) -> Execute RecordSet
forall (m :: * -> *) e a.
Applicative m =>
Either e a -> (e -> m a) -> m a
`onLeft` (ExecuteProblem -> Execute RecordSet
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (ExecuteProblem -> Execute RecordSet)
-> (ExecuteProblem -> ExecuteProblem)
-> ExecuteProblem
-> Execute RecordSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExecuteProblem -> ExecuteProblem
JoinProblem)
JoinType
_ -> ExecuteProblem -> Execute RecordSet
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (JoinType -> ExecuteProblem
UnsupportedJoinBug JoinType
joinType')
where
toFieldNames :: [(FieldName, FieldName)] -> [(FieldName, FieldName)]
toFieldNames = ((FieldName, FieldName) -> (FieldName, FieldName))
-> [(FieldName, FieldName)] -> [(FieldName, FieldName)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((FieldName -> FieldName)
-> (FieldName -> FieldName)
-> (FieldName, FieldName)
-> (FieldName, FieldName)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap FieldName -> FieldName
toFieldName FieldName -> FieldName
toFieldName)
makeRecordSet :: Vector (InsOrdHashMap FieldName J.Value) -> RecordSet
makeRecordSet :: Vector (InsOrdHashMap FieldName Value) -> RecordSet
makeRecordSet Vector (InsOrdHashMap FieldName Value)
rows =
RecordSet :: Maybe PlannedAction
-> Vector (InsOrdHashMap FieldName OutputValue)
-> Maybe [Text]
-> RecordSet
RecordSet
{ origin :: Maybe PlannedAction
origin = Maybe PlannedAction
forall a. Maybe a
Nothing,
rows :: Vector (InsOrdHashMap FieldName OutputValue)
rows = (InsOrdHashMap FieldName Value
-> InsOrdHashMap FieldName OutputValue)
-> Vector (InsOrdHashMap FieldName Value)
-> Vector (InsOrdHashMap FieldName OutputValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Value -> OutputValue)
-> InsOrdHashMap FieldName Value
-> InsOrdHashMap FieldName OutputValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> OutputValue
ScalarOutputValue) Vector (InsOrdHashMap FieldName Value)
rows,
wantedFields :: Maybe [Text]
wantedFields = Maybe [Text]
forall a. Maybe a
Nothing
}
saveRecordSet :: Ref -> RecordSet -> Execute ()
saveRecordSet :: Ref -> RecordSet -> Execute ()
saveRecordSet Ref
ref RecordSet
recordSet = do
IORef (InsOrdHashMap Ref RecordSet)
recordSetsRef <- (ExecuteReader -> IORef (InsOrdHashMap Ref RecordSet))
-> Execute (IORef (InsOrdHashMap Ref RecordSet))
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ExecuteReader -> IORef (InsOrdHashMap Ref RecordSet)
recordSets
IO () -> Execute ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IORef (InsOrdHashMap Ref RecordSet)
-> (InsOrdHashMap Ref RecordSet -> InsOrdHashMap Ref RecordSet)
-> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' IORef (InsOrdHashMap Ref RecordSet)
recordSetsRef (Ref
-> RecordSet
-> InsOrdHashMap Ref RecordSet
-> InsOrdHashMap Ref RecordSet
forall k v.
(Eq k, Hashable k) =>
k -> v -> InsOrdHashMap k v -> InsOrdHashMap k v
OMap.insert Ref
ref RecordSet
recordSet))
getRecordSet :: Ref -> Execute RecordSet
getRecordSet :: Ref -> Execute RecordSet
getRecordSet Ref
ref = do
IORef (InsOrdHashMap Ref RecordSet)
recordSetsRef <- (ExecuteReader -> IORef (InsOrdHashMap Ref RecordSet))
-> Execute (IORef (InsOrdHashMap Ref RecordSet))
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ExecuteReader -> IORef (InsOrdHashMap Ref RecordSet)
recordSets
InsOrdHashMap Ref RecordSet
hash <- IO (InsOrdHashMap Ref RecordSet)
-> Execute (InsOrdHashMap Ref RecordSet)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IORef (InsOrdHashMap Ref RecordSet)
-> IO (InsOrdHashMap Ref RecordSet)
forall a. IORef a -> IO a
readIORef IORef (InsOrdHashMap Ref RecordSet)
recordSetsRef)
Ref -> InsOrdHashMap Ref RecordSet -> Maybe RecordSet
forall k v. (Eq k, Hashable k) => k -> InsOrdHashMap k v -> Maybe v
OMap.lookup Ref
ref InsOrdHashMap Ref RecordSet
hash Maybe RecordSet -> Execute RecordSet -> Execute RecordSet
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` ExecuteProblem -> Execute RecordSet
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Ref -> ExecuteProblem
MissingRecordSetBug Ref
ref)
getFinalRecordSet :: HeadAndTail -> Execute RecordSet
getFinalRecordSet :: HeadAndTail -> Execute RecordSet
getFinalRecordSet HeadAndTail {Ref
$sel:tail:HeadAndTail :: HeadAndTail -> Ref
$sel:head:HeadAndTail :: HeadAndTail -> Ref
tail :: Ref
head :: Ref
..} = do
RecordSet
headSet <- Ref -> Execute RecordSet
getRecordSet Ref
head
RecordSet
tailSet <-
if Ref
tail Ref -> Ref -> Bool
forall a. Eq a => a -> a -> Bool
/= Ref
head
then Ref -> Execute RecordSet
getRecordSet Ref
tail
else RecordSet -> Execute RecordSet
forall (f :: * -> *) a. Applicative f => a -> f a
pure RecordSet
headSet
RecordSet -> Execute RecordSet
forall (f :: * -> *) a. Applicative f => a -> f a
pure
RecordSet
tailSet
{ rows :: Vector (InsOrdHashMap FieldName OutputValue)
rows =
(InsOrdHashMap FieldName OutputValue
-> InsOrdHashMap FieldName OutputValue)
-> Vector (InsOrdHashMap FieldName OutputValue)
-> Vector (InsOrdHashMap FieldName OutputValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
( (FieldName -> OutputValue -> Bool)
-> InsOrdHashMap FieldName OutputValue
-> InsOrdHashMap FieldName OutputValue
forall k v.
(k -> v -> Bool) -> InsOrdHashMap k v -> InsOrdHashMap k v
OMap.filterWithKey
( \(FieldName Text
k) OutputValue
_ ->
Bool -> ([Text] -> Bool) -> Maybe [Text] -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True (Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem Text
k) (RecordSet -> Maybe [Text]
wantedFields RecordSet
headSet)
)
)
(RecordSet -> Vector (InsOrdHashMap FieldName OutputValue)
rows RecordSet
tailSet)
}
leftObjectJoin ::
Maybe [Text] ->
Text ->
[(DataLoaderPlan.FieldName, DataLoaderPlan.FieldName)] ->
RecordSet ->
RecordSet ->
Either ExecuteProblem RecordSet
leftObjectJoin :: Maybe [Text]
-> Text
-> [(FieldName, FieldName)]
-> RecordSet
-> RecordSet
-> Either ExecuteProblem RecordSet
leftObjectJoin Maybe [Text]
wantedFields Text
joinAlias [(FieldName, FieldName)]
joinFields RecordSet
left RecordSet
right = do
Vector (InsOrdHashMap FieldName OutputValue)
rows' <- ([InsOrdHashMap FieldName OutputValue]
-> Vector (InsOrdHashMap FieldName OutputValue))
-> Either ExecuteProblem [InsOrdHashMap FieldName OutputValue]
-> Either
ExecuteProblem (Vector (InsOrdHashMap FieldName OutputValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [InsOrdHashMap FieldName OutputValue]
-> Vector (InsOrdHashMap FieldName OutputValue)
forall a. [a] -> Vector a
V.fromList (Either ExecuteProblem [InsOrdHashMap FieldName OutputValue]
-> Either
ExecuteProblem (Vector (InsOrdHashMap FieldName OutputValue)))
-> (Vector (InsOrdHashMap FieldName OutputValue)
-> Either ExecuteProblem [InsOrdHashMap FieldName OutputValue])
-> Vector (InsOrdHashMap FieldName OutputValue)
-> Either
ExecuteProblem (Vector (InsOrdHashMap FieldName OutputValue))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (InsOrdHashMap FieldName OutputValue
-> Either ExecuteProblem (InsOrdHashMap FieldName OutputValue))
-> [InsOrdHashMap FieldName OutputValue]
-> Either ExecuteProblem [InsOrdHashMap FieldName OutputValue]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse InsOrdHashMap FieldName OutputValue
-> Either ExecuteProblem (InsOrdHashMap FieldName OutputValue)
makeRows ([InsOrdHashMap FieldName OutputValue]
-> Either ExecuteProblem [InsOrdHashMap FieldName OutputValue])
-> (Vector (InsOrdHashMap FieldName OutputValue)
-> [InsOrdHashMap FieldName OutputValue])
-> Vector (InsOrdHashMap FieldName OutputValue)
-> Either ExecuteProblem [InsOrdHashMap FieldName OutputValue]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector (InsOrdHashMap FieldName OutputValue)
-> [InsOrdHashMap FieldName OutputValue]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (Vector (InsOrdHashMap FieldName OutputValue)
-> Either
ExecuteProblem (Vector (InsOrdHashMap FieldName OutputValue)))
-> Vector (InsOrdHashMap FieldName OutputValue)
-> Either
ExecuteProblem (Vector (InsOrdHashMap FieldName OutputValue))
forall a b. (a -> b) -> a -> b
$ RecordSet -> Vector (InsOrdHashMap FieldName OutputValue)
rows RecordSet
left
RecordSet -> Either ExecuteProblem RecordSet
forall (f :: * -> *) a. Applicative f => a -> f a
pure
RecordSet :: Maybe PlannedAction
-> Vector (InsOrdHashMap FieldName OutputValue)
-> Maybe [Text]
-> RecordSet
RecordSet
{ origin :: Maybe PlannedAction
origin = Maybe PlannedAction
forall a. Maybe a
Nothing,
wantedFields :: Maybe [Text]
wantedFields = Maybe [Text]
forall a. Maybe a
Nothing,
rows :: Vector (InsOrdHashMap FieldName OutputValue)
rows = Vector (InsOrdHashMap FieldName OutputValue)
rows'
}
where
makeRows :: InsOrdHashMap FieldName OutputValue -> Either ExecuteProblem (InsOrdHashMap FieldName OutputValue)
makeRows :: InsOrdHashMap FieldName OutputValue
-> Either ExecuteProblem (InsOrdHashMap FieldName OutputValue)
makeRows InsOrdHashMap FieldName OutputValue
leftRow =
let rightRows :: Vector (InsOrdHashMap FieldName OutputValue)
rightRows =
[InsOrdHashMap FieldName OutputValue]
-> Vector (InsOrdHashMap FieldName OutputValue)
forall a. [a] -> Vector a
V.fromList
[ InsOrdHashMap FieldName OutputValue
rightRow
| Bool -> Bool
not ([(FieldName, FieldName)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(FieldName, FieldName)]
joinFields),
InsOrdHashMap FieldName OutputValue
rightRow <- Vector (InsOrdHashMap FieldName OutputValue)
-> [InsOrdHashMap FieldName OutputValue]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (RecordSet -> Vector (InsOrdHashMap FieldName OutputValue)
rows RecordSet
right),
((FieldName, FieldName) -> Bool)
-> [(FieldName, FieldName)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all
( \(FieldName
rightField, FieldName
leftField) ->
Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== ( do
OutputValue
leftValue <- FieldName
-> InsOrdHashMap FieldName OutputValue -> Maybe OutputValue
forall k v. (Eq k, Hashable k) => k -> InsOrdHashMap k v -> Maybe v
OMap.lookup FieldName
leftField InsOrdHashMap FieldName OutputValue
leftRow
OutputValue
rightValue <- FieldName
-> InsOrdHashMap FieldName OutputValue -> Maybe OutputValue
forall k v. (Eq k, Hashable k) => k -> InsOrdHashMap k v -> Maybe v
OMap.lookup FieldName
rightField InsOrdHashMap FieldName OutputValue
rightRow
Bool -> Maybe Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (OutputValue
leftValue OutputValue -> OutputValue -> Bool
forall a. Eq a => a -> a -> Bool
== OutputValue
rightValue)
)
)
[(FieldName, FieldName)]
joinFields
]
in
Maybe [Text]
-> Text
-> InsOrdHashMap FieldName OutputValue
-> Vector (InsOrdHashMap FieldName OutputValue)
-> Either ExecuteProblem (InsOrdHashMap FieldName OutputValue)
joinObjectRows Maybe [Text]
wantedFields Text
joinAlias InsOrdHashMap FieldName OutputValue
leftRow Vector (InsOrdHashMap FieldName OutputValue)
rightRows
leftArrayJoin ::
Maybe [Text] ->
Text ->
[(DataLoaderPlan.FieldName, DataLoaderPlan.FieldName)] ->
Top ->
Maybe Int ->
RecordSet ->
RecordSet ->
Either ExecuteProblem RecordSet
leftArrayJoin :: Maybe [Text]
-> Text
-> [(FieldName, FieldName)]
-> Top
-> Maybe Int
-> RecordSet
-> RecordSet
-> Either ExecuteProblem RecordSet
leftArrayJoin Maybe [Text]
wantedFields Text
joinAlias [(FieldName, FieldName)]
joinFields Top
rhsTop Maybe Int
rhsOffset RecordSet
left RecordSet
right =
RecordSet -> Either ExecuteProblem RecordSet
forall (f :: * -> *) a. Applicative f => a -> f a
pure
RecordSet :: Maybe PlannedAction
-> Vector (InsOrdHashMap FieldName OutputValue)
-> Maybe [Text]
-> RecordSet
RecordSet
{ origin :: Maybe PlannedAction
origin = Maybe PlannedAction
forall a. Maybe a
Nothing,
wantedFields :: Maybe [Text]
wantedFields = Maybe [Text]
forall a. Maybe a
Nothing,
rows :: Vector (InsOrdHashMap FieldName OutputValue)
rows =
[InsOrdHashMap FieldName OutputValue]
-> Vector (InsOrdHashMap FieldName OutputValue)
forall a. [a] -> Vector a
V.fromList
[ Maybe [Text]
-> Text
-> InsOrdHashMap FieldName OutputValue
-> Vector (InsOrdHashMap FieldName OutputValue)
-> InsOrdHashMap FieldName OutputValue
joinArrayRows Maybe [Text]
wantedFields Text
joinAlias InsOrdHashMap FieldName OutputValue
leftRow Vector (InsOrdHashMap FieldName OutputValue)
rightRows
| InsOrdHashMap FieldName OutputValue
leftRow <- Vector (InsOrdHashMap FieldName OutputValue)
-> [InsOrdHashMap FieldName OutputValue]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (RecordSet -> Vector (InsOrdHashMap FieldName OutputValue)
rows RecordSet
left),
let rightRows :: Vector (InsOrdHashMap FieldName OutputValue)
rightRows =
[InsOrdHashMap FieldName OutputValue]
-> Vector (InsOrdHashMap FieldName OutputValue)
forall a. [a] -> Vector a
V.fromList
( [InsOrdHashMap FieldName OutputValue]
-> [InsOrdHashMap FieldName OutputValue]
limit
( [InsOrdHashMap FieldName OutputValue]
-> [InsOrdHashMap FieldName OutputValue]
offset
[ InsOrdHashMap FieldName OutputValue
rightRow
| Bool -> Bool
not ([(FieldName, FieldName)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(FieldName, FieldName)]
joinFields),
InsOrdHashMap FieldName OutputValue
rightRow <- Vector (InsOrdHashMap FieldName OutputValue)
-> [InsOrdHashMap FieldName OutputValue]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (RecordSet -> Vector (InsOrdHashMap FieldName OutputValue)
rows RecordSet
right),
((FieldName, FieldName) -> Bool)
-> [(FieldName, FieldName)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all
( \(FieldName
rightField, FieldName
leftField) ->
Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== ( do
OutputValue
leftValue <- FieldName
-> InsOrdHashMap FieldName OutputValue -> Maybe OutputValue
forall k v. (Eq k, Hashable k) => k -> InsOrdHashMap k v -> Maybe v
OMap.lookup FieldName
leftField InsOrdHashMap FieldName OutputValue
leftRow
OutputValue
rightValue <- FieldName
-> InsOrdHashMap FieldName OutputValue -> Maybe OutputValue
forall k v. (Eq k, Hashable k) => k -> InsOrdHashMap k v -> Maybe v
OMap.lookup FieldName
rightField InsOrdHashMap FieldName OutputValue
rightRow
Bool -> Maybe Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (OutputValue
leftValue OutputValue -> OutputValue -> Bool
forall a. Eq a => a -> a -> Bool
== OutputValue
rightValue)
)
)
[(FieldName, FieldName)]
joinFields
]
)
)
]
}
where
offset :: [InsOrdHashMap FieldName OutputValue]
-> [InsOrdHashMap FieldName OutputValue]
offset = ([InsOrdHashMap FieldName OutputValue]
-> [InsOrdHashMap FieldName OutputValue])
-> (Int
-> [InsOrdHashMap FieldName OutputValue]
-> [InsOrdHashMap FieldName OutputValue])
-> Maybe Int
-> [InsOrdHashMap FieldName OutputValue]
-> [InsOrdHashMap FieldName OutputValue]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [InsOrdHashMap FieldName OutputValue]
-> [InsOrdHashMap FieldName OutputValue]
forall a. a -> a
id Int
-> [InsOrdHashMap FieldName OutputValue]
-> [InsOrdHashMap FieldName OutputValue]
forall a. Int -> [a] -> [a]
drop Maybe Int
rhsOffset
limit :: [InsOrdHashMap FieldName OutputValue]
-> [InsOrdHashMap FieldName OutputValue]
limit =
case Top
rhsTop of
Top
NoTop -> [InsOrdHashMap FieldName OutputValue]
-> [InsOrdHashMap FieldName OutputValue]
forall a. a -> a
id
Top Int
n -> Int
-> [InsOrdHashMap FieldName OutputValue]
-> [InsOrdHashMap FieldName OutputValue]
forall a. Int -> [a] -> [a]
take Int
n
joinArrayRows ::
Maybe [Text] ->
Text ->
InsOrdHashMap DataLoaderPlan.FieldName OutputValue ->
Vector (InsOrdHashMap DataLoaderPlan.FieldName OutputValue) ->
InsOrdHashMap DataLoaderPlan.FieldName OutputValue
joinArrayRows :: Maybe [Text]
-> Text
-> InsOrdHashMap FieldName OutputValue
-> Vector (InsOrdHashMap FieldName OutputValue)
-> InsOrdHashMap FieldName OutputValue
joinArrayRows Maybe [Text]
wantedFields Text
fieldName InsOrdHashMap FieldName OutputValue
leftRow Vector (InsOrdHashMap FieldName OutputValue)
rightRow =
FieldName
-> OutputValue
-> InsOrdHashMap FieldName OutputValue
-> InsOrdHashMap FieldName OutputValue
forall k v.
(Eq k, Hashable k) =>
k -> v -> InsOrdHashMap k v -> InsOrdHashMap k v
OMap.insert
(Text -> FieldName
DataLoaderPlan.FieldName Text
fieldName)
( Vector OutputValue -> OutputValue
ArrayOutputValue
( (InsOrdHashMap FieldName OutputValue -> OutputValue)
-> Vector (InsOrdHashMap FieldName OutputValue)
-> Vector OutputValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
( InsOrdHashMap FieldName OutputValue -> OutputValue
RecordOutputValue
(InsOrdHashMap FieldName OutputValue -> OutputValue)
-> (InsOrdHashMap FieldName OutputValue
-> InsOrdHashMap FieldName OutputValue)
-> InsOrdHashMap FieldName OutputValue
-> OutputValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FieldName -> OutputValue -> Bool)
-> InsOrdHashMap FieldName OutputValue
-> InsOrdHashMap FieldName OutputValue
forall k v.
(k -> v -> Bool) -> InsOrdHashMap k v -> InsOrdHashMap k v
OMap.filterWithKey
( \(DataLoaderPlan.FieldName Text
k) OutputValue
_ ->
Bool -> ([Text] -> Bool) -> Maybe [Text] -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True (Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem Text
k) Maybe [Text]
wantedFields
)
)
Vector (InsOrdHashMap FieldName OutputValue)
rightRow
)
)
InsOrdHashMap FieldName OutputValue
leftRow
joinObjectRows ::
Maybe [Text] ->
Text ->
InsOrdHashMap DataLoaderPlan.FieldName OutputValue ->
Vector (InsOrdHashMap DataLoaderPlan.FieldName OutputValue) ->
Either ExecuteProblem (InsOrdHashMap DataLoaderPlan.FieldName OutputValue)
joinObjectRows :: Maybe [Text]
-> Text
-> InsOrdHashMap FieldName OutputValue
-> Vector (InsOrdHashMap FieldName OutputValue)
-> Either ExecuteProblem (InsOrdHashMap FieldName OutputValue)
joinObjectRows Maybe [Text]
wantedFields Text
fieldName InsOrdHashMap FieldName OutputValue
leftRow Vector (InsOrdHashMap FieldName OutputValue)
rightRows
| Vector (InsOrdHashMap FieldName OutputValue) -> Int
forall a. Vector a -> Int
V.length Vector (InsOrdHashMap FieldName OutputValue)
rightRows Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
1 = ExecuteProblem
-> Either ExecuteProblem (InsOrdHashMap FieldName OutputValue)
forall a b. a -> Either a b
Left (ExecuteProblem
-> Either ExecuteProblem (InsOrdHashMap FieldName OutputValue))
-> (Vector (InsOrdHashMap FieldName OutputValue) -> ExecuteProblem)
-> Vector (InsOrdHashMap FieldName OutputValue)
-> Either ExecuteProblem (InsOrdHashMap FieldName OutputValue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FieldName] -> ExecuteProblem
BrokenJoinInvariant ([FieldName] -> ExecuteProblem)
-> (Vector (InsOrdHashMap FieldName OutputValue) -> [FieldName])
-> Vector (InsOrdHashMap FieldName OutputValue)
-> ExecuteProblem
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (InsOrdHashMap FieldName OutputValue -> [FieldName])
-> Vector (InsOrdHashMap FieldName OutputValue) -> [FieldName]
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap InsOrdHashMap FieldName OutputValue -> [FieldName]
forall k v. InsOrdHashMap k v -> [k]
OMap.keys (Vector (InsOrdHashMap FieldName OutputValue)
-> Either ExecuteProblem (InsOrdHashMap FieldName OutputValue))
-> Vector (InsOrdHashMap FieldName OutputValue)
-> Either ExecuteProblem (InsOrdHashMap FieldName OutputValue)
forall a b. (a -> b) -> a -> b
$ Vector (InsOrdHashMap FieldName OutputValue)
rightRows
| Bool
otherwise =
let row :: InsOrdHashMap FieldName OutputValue
row = Vector (InsOrdHashMap FieldName OutputValue)
-> InsOrdHashMap FieldName OutputValue
forall a. Vector a -> a
V.head Vector (InsOrdHashMap FieldName OutputValue)
rightRows
in InsOrdHashMap FieldName OutputValue
-> Either ExecuteProblem (InsOrdHashMap FieldName OutputValue)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InsOrdHashMap FieldName OutputValue
-> Either ExecuteProblem (InsOrdHashMap FieldName OutputValue))
-> InsOrdHashMap FieldName OutputValue
-> Either ExecuteProblem (InsOrdHashMap FieldName OutputValue)
forall a b. (a -> b) -> a -> b
$
FieldName
-> OutputValue
-> InsOrdHashMap FieldName OutputValue
-> InsOrdHashMap FieldName OutputValue
forall k v.
(Eq k, Hashable k) =>
k -> v -> InsOrdHashMap k v -> InsOrdHashMap k v
OMap.insert
(Text -> FieldName
DataLoaderPlan.FieldName Text
fieldName)
( InsOrdHashMap FieldName OutputValue -> OutputValue
RecordOutputValue
( (FieldName -> OutputValue -> Bool)
-> InsOrdHashMap FieldName OutputValue
-> InsOrdHashMap FieldName OutputValue
forall k v.
(k -> v -> Bool) -> InsOrdHashMap k v -> InsOrdHashMap k v
OMap.filterWithKey
(\(DataLoaderPlan.FieldName Text
k) OutputValue
_ -> Bool -> ([Text] -> Bool) -> Maybe [Text] -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True (Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem Text
k) Maybe [Text]
wantedFields)
InsOrdHashMap FieldName OutputValue
row
)
)
InsOrdHashMap FieldName OutputValue
leftRow