{-# LANGUAGE Rank2Types #-}
module System.Nix.Store.DB.Query
( queryPathInfoEntity
, queryPathInfo
, queryReferencesEntity
, queryReferences
, queryReferrersEntity
, queryReferrers
, queryValidDerivers
, queryDerivationOutputs
, queryPathFromHashPart
, queryValidPathsEntity
, queryValidPaths
, queryAllRefsEntity
, queryAllRefs
, queryAllDerivationOutputsEntity
, queryAllDerivationOutputs
, queryOneValidDerivationEntity
, queryOneValidDerivation
, queryEverything
) where
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.Logger (MonadLogger)
import Data.Text (Text)
import Database.Esqueleto.Experimental
import System.Nix.StorePath (StoreDir, StorePath, StorePathHashPart)
import System.Nix.Store.DB.Schema
import qualified Data.ByteString.Char8
import qualified Data.Maybe
import qualified Data.Text
import qualified System.Nix.StorePath
import qualified System.Nix.StorePath.Metadata
queryPathInfoEntity
:: ( MonadIO m
, MonadLogger m
)
=> StorePath
-> SqlReadT m (Maybe (Entity ValidPath))
queryPathInfoEntity :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
StorePath -> SqlReadT m (Maybe (Entity ValidPath))
queryPathInfoEntity StorePath
path = do
[Entity ValidPath]
res <- SqlQuery (SqlExpr (Entity ValidPath))
-> ReaderT backend m [Entity ValidPath]
forall a r (m :: * -> *) backend.
(SqlSelect a r, MonadIO m, SqlBackendCanRead backend) =>
SqlQuery a -> ReaderT backend m [r]
select (SqlQuery (SqlExpr (Entity ValidPath))
-> ReaderT backend m [Entity ValidPath])
-> SqlQuery (SqlExpr (Entity ValidPath))
-> ReaderT backend m [Entity ValidPath]
forall a b. (a -> b) -> a -> b
$ do
SqlExpr (Entity ValidPath)
validPaths <- From (SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity ValidPath))
forall a a'. ToFrom a a' => a -> SqlQuery a'
from (From (SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity ValidPath)))
-> From (SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity ValidPath))
forall a b. (a -> b) -> a -> b
$ forall ent. PersistEntity ent => From (SqlExpr (Entity ent))
table @ValidPath
SqlExpr (Value Bool) -> SqlQuery ()
where_ (SqlExpr (Entity ValidPath)
validPaths SqlExpr (Entity ValidPath)
-> EntityField ValidPath StorePath -> SqlExpr (Value StorePath)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField ValidPath StorePath
forall typ. (typ ~ StorePath) => EntityField ValidPath typ
ValidPathPath SqlExpr (Value StorePath)
-> SqlExpr (Value StorePath) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
==. StorePath -> SqlExpr (Value StorePath)
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
val StorePath
path)
SqlExpr (Entity ValidPath) -> SqlQuery (SqlExpr (Entity ValidPath))
forall a. a -> SqlQuery a
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlExpr (Entity ValidPath)
validPaths
Maybe (Entity ValidPath)
-> ReaderT backend m (Maybe (Entity ValidPath))
forall a. a -> ReaderT backend m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (Entity ValidPath)
-> ReaderT backend m (Maybe (Entity ValidPath)))
-> Maybe (Entity ValidPath)
-> ReaderT backend m (Maybe (Entity ValidPath))
forall a b. (a -> b) -> a -> b
$ [Entity ValidPath] -> Maybe (Entity ValidPath)
forall a. [a] -> Maybe a
Data.Maybe.listToMaybe [Entity ValidPath]
res
queryPathInfo
:: ( MonadIO m
, MonadLogger m
)
=> StorePath
-> SqlReadT m (Maybe ValidPath)
queryPathInfo :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
StorePath -> SqlReadT m (Maybe ValidPath)
queryPathInfo StorePath
sp =
StorePath -> SqlReadT m (Maybe (Entity ValidPath))
forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
StorePath -> SqlReadT m (Maybe (Entity ValidPath))
queryPathInfoEntity StorePath
sp ReaderT backend m (Maybe (Entity ValidPath))
-> (Maybe (Entity ValidPath)
-> ReaderT backend m (Maybe ValidPath))
-> ReaderT backend m (Maybe ValidPath)
forall a b.
ReaderT backend m a
-> (a -> ReaderT backend m b) -> ReaderT backend m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe (Entity ValidPath)
Nothing -> Maybe ValidPath -> ReaderT backend m (Maybe ValidPath)
forall a. a -> ReaderT backend m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe ValidPath
forall a. Maybe a
Nothing
Just Entity ValidPath
evp -> Maybe ValidPath -> ReaderT backend m (Maybe ValidPath)
forall a. a -> ReaderT backend m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe ValidPath -> ReaderT backend m (Maybe ValidPath))
-> Maybe ValidPath -> ReaderT backend m (Maybe ValidPath)
forall a b. (a -> b) -> a -> b
$ ValidPath -> Maybe ValidPath
forall a. a -> Maybe a
Just (Entity ValidPath -> ValidPath
forall record. Entity record -> record
entityVal Entity ValidPath
evp)
queryReferencesEntity
:: ( MonadIO m
, MonadLogger m
)
=> Entity ValidPath
-> SqlReadT m [Entity Ref]
queryReferencesEntity :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
Entity ValidPath -> SqlReadT m [Entity Ref]
queryReferencesEntity Entity ValidPath
referrer =
SqlQuery (SqlExpr (Entity Ref)) -> ReaderT backend m [Entity Ref]
forall a r (m :: * -> *) backend.
(SqlSelect a r, MonadIO m, SqlBackendCanRead backend) =>
SqlQuery a -> ReaderT backend m [r]
select (SqlQuery (SqlExpr (Entity Ref)) -> ReaderT backend m [Entity Ref])
-> SqlQuery (SqlExpr (Entity Ref))
-> ReaderT backend m [Entity Ref]
forall a b. (a -> b) -> a -> b
$ do
(SqlExpr (Entity Ref)
refs :& SqlExpr (Entity ValidPath)
_validPaths) <-
From (SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
forall a a'. ToFrom a a' => a -> SqlQuery a'
from (From (SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath)))
-> From (SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
forall a b. (a -> b) -> a -> b
$ forall ent. PersistEntity ent => From (SqlExpr (Entity ent))
table @Ref
From (SqlExpr (Entity Ref))
-> (From (SqlExpr (Entity ValidPath)),
(SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
-> SqlExpr (Value Bool))
-> From (SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
forall a a' b b' rhs.
(ToFrom a a', ToFrom b b', HasOnClause rhs (a' :& b'),
rhs ~ (b, (a' :& b') -> SqlExpr (Value Bool))) =>
a -> rhs -> From (a' :& b')
`innerJoin` forall ent. PersistEntity ent => From (SqlExpr (Entity ent))
table @ValidPath
From (SqlExpr (Entity ValidPath))
-> ((SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
-> SqlExpr (Value Bool))
-> (From (SqlExpr (Entity ValidPath)),
(SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
-> SqlExpr (Value Bool))
forall a b.
ValidOnClause a =>
a -> (b -> SqlExpr (Value Bool)) -> (a, b -> SqlExpr (Value Bool))
`on` (\(SqlExpr (Entity Ref)
refs :& SqlExpr (Entity ValidPath)
validPaths) ->
SqlExpr (Entity Ref)
refs SqlExpr (Entity Ref)
-> EntityField Ref ValidPathId -> SqlExpr (Value ValidPathId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField Ref ValidPathId
forall typ. (typ ~ ValidPathId) => EntityField Ref typ
RefReference SqlExpr (Value ValidPathId)
-> SqlExpr (Value ValidPathId) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
==. SqlExpr (Entity ValidPath)
validPaths SqlExpr (Entity ValidPath)
-> EntityField ValidPath ValidPathId -> SqlExpr (Value ValidPathId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField ValidPath ValidPathId
forall typ. (typ ~ ValidPathId) => EntityField ValidPath typ
ValidPathId)
SqlExpr (Value Bool) -> SqlQuery ()
where_ (SqlExpr (Entity Ref)
refs SqlExpr (Entity Ref)
-> EntityField Ref ValidPathId -> SqlExpr (Value ValidPathId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField Ref ValidPathId
forall typ. (typ ~ ValidPathId) => EntityField Ref typ
RefReferrer SqlExpr (Value ValidPathId)
-> SqlExpr (Value ValidPathId) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
==. ValidPathId -> SqlExpr (Value ValidPathId)
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
val (Entity ValidPath -> ValidPathId
forall record. Entity record -> Key record
entityKey Entity ValidPath
referrer))
SqlExpr (Entity Ref) -> SqlQuery (SqlExpr (Entity Ref))
forall a. a -> SqlQuery a
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlExpr (Entity Ref)
refs
queryReferences
:: ( MonadIO m
, MonadLogger m
)
=> Entity ValidPath
-> SqlReadT m [Ref]
queryReferences :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
Entity ValidPath -> SqlReadT m [Ref]
queryReferences Entity ValidPath
evp = do
Entity ValidPath -> SqlReadT m [Entity Ref]
forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
Entity ValidPath -> SqlReadT m [Entity Ref]
queryReferencesEntity Entity ValidPath
evp ReaderT backend m [Entity Ref]
-> ([Entity Ref] -> ReaderT backend m [Ref])
-> ReaderT backend m [Ref]
forall a b.
ReaderT backend m a
-> (a -> ReaderT backend m b) -> ReaderT backend m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Ref] -> ReaderT backend m [Ref]
forall a. a -> ReaderT backend m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Ref] -> ReaderT backend m [Ref])
-> ([Entity Ref] -> [Ref])
-> [Entity Ref]
-> ReaderT backend m [Ref]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Entity Ref -> Ref) -> [Entity Ref] -> [Ref]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Entity Ref -> Ref
forall record. Entity record -> record
entityVal
queryReferrersEntity
:: ( MonadIO m
, MonadLogger m
)
=> StorePath
-> SqlReadT m [Entity Ref]
queryReferrersEntity :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
StorePath -> SqlReadT m [Entity Ref]
queryReferrersEntity StorePath
path = do
SqlQuery (SqlExpr (Entity Ref)) -> ReaderT backend m [Entity Ref]
forall a r (m :: * -> *) backend.
(SqlSelect a r, MonadIO m, SqlBackendCanRead backend) =>
SqlQuery a -> ReaderT backend m [r]
select (SqlQuery (SqlExpr (Entity Ref)) -> ReaderT backend m [Entity Ref])
-> SqlQuery (SqlExpr (Entity Ref))
-> ReaderT backend m [Entity Ref]
forall a b. (a -> b) -> a -> b
$ do
(SqlExpr (Entity Ref)
refs :& SqlExpr (Entity ValidPath)
_validPaths) <-
From (SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
forall a a'. ToFrom a a' => a -> SqlQuery a'
from (From (SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath)))
-> From (SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
forall a b. (a -> b) -> a -> b
$ forall ent. PersistEntity ent => From (SqlExpr (Entity ent))
table @Ref
From (SqlExpr (Entity Ref))
-> (From (SqlExpr (Entity ValidPath)),
(SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
-> SqlExpr (Value Bool))
-> From (SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
forall a a' b b' rhs.
(ToFrom a a', ToFrom b b', HasOnClause rhs (a' :& b'),
rhs ~ (b, (a' :& b') -> SqlExpr (Value Bool))) =>
a -> rhs -> From (a' :& b')
`innerJoin` forall ent. PersistEntity ent => From (SqlExpr (Entity ent))
table @ValidPath
From (SqlExpr (Entity ValidPath))
-> ((SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
-> SqlExpr (Value Bool))
-> (From (SqlExpr (Entity ValidPath)),
(SqlExpr (Entity Ref) :& SqlExpr (Entity ValidPath))
-> SqlExpr (Value Bool))
forall a b.
ValidOnClause a =>
a -> (b -> SqlExpr (Value Bool)) -> (a, b -> SqlExpr (Value Bool))
`on` (\(SqlExpr (Entity Ref)
refs :& SqlExpr (Entity ValidPath)
validPaths) ->
(SqlExpr (Entity Ref)
refs SqlExpr (Entity Ref)
-> EntityField Ref ValidPathId -> SqlExpr (Value ValidPathId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField Ref ValidPathId
forall typ. (typ ~ ValidPathId) => EntityField Ref typ
RefReference SqlExpr (Value ValidPathId)
-> SqlExpr (Value ValidPathId) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
==. SqlExpr (Entity ValidPath)
validPaths SqlExpr (Entity ValidPath)
-> EntityField ValidPath ValidPathId -> SqlExpr (Value ValidPathId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField ValidPath ValidPathId
forall typ. (typ ~ ValidPathId) => EntityField ValidPath typ
ValidPathId))
SqlExpr (Value Bool) -> SqlQuery ()
where_
(
SqlExpr (Entity Ref)
refs SqlExpr (Entity Ref)
-> EntityField Ref ValidPathId -> SqlExpr (Value ValidPathId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField Ref ValidPathId
forall typ. (typ ~ ValidPathId) => EntityField Ref typ
RefReference
SqlExpr (Value ValidPathId)
-> SqlExpr (ValueList ValidPathId) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ)
-> SqlExpr (ValueList typ) -> SqlExpr (Value Bool)
`in_`
(SqlQuery (SqlExpr (Value ValidPathId))
-> SqlExpr (ValueList ValidPathId)
forall a.
PersistField a =>
SqlQuery (SqlExpr (Value a)) -> SqlExpr (ValueList a)
subList_select (SqlQuery (SqlExpr (Value ValidPathId))
-> SqlExpr (ValueList ValidPathId))
-> SqlQuery (SqlExpr (Value ValidPathId))
-> SqlExpr (ValueList ValidPathId)
forall a b. (a -> b) -> a -> b
$ do
SqlExpr (Entity ValidPath)
validPaths <- From (SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity ValidPath))
forall a a'. ToFrom a a' => a -> SqlQuery a'
from (From (SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity ValidPath)))
-> From (SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity ValidPath))
forall a b. (a -> b) -> a -> b
$ forall ent. PersistEntity ent => From (SqlExpr (Entity ent))
table @ValidPath
SqlExpr (Value Bool) -> SqlQuery ()
where_ (SqlExpr (Entity ValidPath)
validPaths SqlExpr (Entity ValidPath)
-> EntityField ValidPath StorePath -> SqlExpr (Value StorePath)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField ValidPath StorePath
forall typ. (typ ~ StorePath) => EntityField ValidPath typ
ValidPathPath SqlExpr (Value StorePath)
-> SqlExpr (Value StorePath) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
==. StorePath -> SqlExpr (Value StorePath)
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
val StorePath
path)
SqlExpr (Value ValidPathId)
-> SqlQuery (SqlExpr (Value ValidPathId))
forall a. a -> SqlQuery a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlExpr (Value ValidPathId)
-> SqlQuery (SqlExpr (Value ValidPathId)))
-> SqlExpr (Value ValidPathId)
-> SqlQuery (SqlExpr (Value ValidPathId))
forall a b. (a -> b) -> a -> b
$ SqlExpr (Entity ValidPath)
validPaths SqlExpr (Entity ValidPath)
-> EntityField ValidPath ValidPathId -> SqlExpr (Value ValidPathId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField ValidPath ValidPathId
forall typ. (typ ~ ValidPathId) => EntityField ValidPath typ
ValidPathId
)
)
SqlExpr (Entity Ref) -> SqlQuery (SqlExpr (Entity Ref))
forall a. a -> SqlQuery a
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlExpr (Entity Ref)
refs
queryReferrers
:: ( MonadIO m
, MonadLogger m
)
=> StorePath
-> SqlReadT m [Ref]
queryReferrers :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
StorePath -> SqlReadT m [Ref]
queryReferrers StorePath
sp =
StorePath -> SqlReadT m [Entity Ref]
forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
StorePath -> SqlReadT m [Entity Ref]
queryReferrersEntity StorePath
sp
ReaderT backend m [Entity Ref]
-> ([Entity Ref] -> ReaderT backend m [Ref])
-> ReaderT backend m [Ref]
forall a b.
ReaderT backend m a
-> (a -> ReaderT backend m b) -> ReaderT backend m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Ref] -> ReaderT backend m [Ref]
forall a. a -> ReaderT backend m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Ref] -> ReaderT backend m [Ref])
-> ([Entity Ref] -> [Ref])
-> [Entity Ref]
-> ReaderT backend m [Ref]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Entity Ref -> Ref) -> [Entity Ref] -> [Ref]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Entity Ref -> Ref
forall record. Entity record -> record
entityVal)
queryValidDerivers
:: ( MonadIO m
, MonadLogger m
)
=> StorePath
-> SqlReadT m [(Text, StorePath)]
queryValidDerivers :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
StorePath -> SqlReadT m [(Text, StorePath)]
queryValidDerivers StorePath
path = do
[(Value Text, Value StorePath)]
res <- SqlQuery (SqlExpr (Value Text), SqlExpr (Value StorePath))
-> ReaderT backend m [(Value Text, Value StorePath)]
forall a r (m :: * -> *) backend.
(SqlSelect a r, MonadIO m, SqlBackendCanRead backend) =>
SqlQuery a -> ReaderT backend m [r]
select (SqlQuery (SqlExpr (Value Text), SqlExpr (Value StorePath))
-> ReaderT backend m [(Value Text, Value StorePath)])
-> SqlQuery (SqlExpr (Value Text), SqlExpr (Value StorePath))
-> ReaderT backend m [(Value Text, Value StorePath)]
forall a b. (a -> b) -> a -> b
$ do
(SqlExpr (Entity DerivationOutput)
drvOuts :& SqlExpr (Entity ValidPath)
_validPaths) <-
From
(SqlExpr (Entity DerivationOutput) :& SqlExpr (Entity ValidPath))
-> SqlQuery
(SqlExpr (Entity DerivationOutput) :& SqlExpr (Entity ValidPath))
forall a a'. ToFrom a a' => a -> SqlQuery a'
from (From
(SqlExpr (Entity DerivationOutput) :& SqlExpr (Entity ValidPath))
-> SqlQuery
(SqlExpr (Entity DerivationOutput) :& SqlExpr (Entity ValidPath)))
-> From
(SqlExpr (Entity DerivationOutput) :& SqlExpr (Entity ValidPath))
-> SqlQuery
(SqlExpr (Entity DerivationOutput) :& SqlExpr (Entity ValidPath))
forall a b. (a -> b) -> a -> b
$ forall ent. PersistEntity ent => From (SqlExpr (Entity ent))
table @DerivationOutput
From (SqlExpr (Entity DerivationOutput))
-> (From (SqlExpr (Entity ValidPath)),
(SqlExpr (Entity DerivationOutput) :& SqlExpr (Entity ValidPath))
-> SqlExpr (Value Bool))
-> From
(SqlExpr (Entity DerivationOutput) :& SqlExpr (Entity ValidPath))
forall a a' b b' rhs.
(ToFrom a a', ToFrom b b', HasOnClause rhs (a' :& b'),
rhs ~ (b, (a' :& b') -> SqlExpr (Value Bool))) =>
a -> rhs -> From (a' :& b')
`innerJoin` forall ent. PersistEntity ent => From (SqlExpr (Entity ent))
table @ValidPath
From (SqlExpr (Entity ValidPath))
-> ((SqlExpr (Entity DerivationOutput)
:& SqlExpr (Entity ValidPath))
-> SqlExpr (Value Bool))
-> (From (SqlExpr (Entity ValidPath)),
(SqlExpr (Entity DerivationOutput) :& SqlExpr (Entity ValidPath))
-> SqlExpr (Value Bool))
forall a b.
ValidOnClause a =>
a -> (b -> SqlExpr (Value Bool)) -> (a, b -> SqlExpr (Value Bool))
`on` (\(SqlExpr (Entity DerivationOutput)
drvOuts :& SqlExpr (Entity ValidPath)
validPaths) ->
(SqlExpr (Entity DerivationOutput)
drvOuts SqlExpr (Entity DerivationOutput)
-> EntityField DerivationOutput ValidPathId
-> SqlExpr (Value ValidPathId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField DerivationOutput ValidPathId
forall typ. (typ ~ ValidPathId) => EntityField DerivationOutput typ
DerivationOutputDrv SqlExpr (Value ValidPathId)
-> SqlExpr (Value ValidPathId) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
==. SqlExpr (Entity ValidPath)
validPaths SqlExpr (Entity ValidPath)
-> EntityField ValidPath ValidPathId -> SqlExpr (Value ValidPathId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField ValidPath ValidPathId
forall typ. (typ ~ ValidPathId) => EntityField ValidPath typ
ValidPathId))
SqlExpr (Value Bool) -> SqlQuery ()
where_ (SqlExpr (Entity DerivationOutput)
drvOuts SqlExpr (Entity DerivationOutput)
-> EntityField DerivationOutput StorePath
-> SqlExpr (Value StorePath)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField DerivationOutput StorePath
forall typ. (typ ~ StorePath) => EntityField DerivationOutput typ
DerivationOutputPath SqlExpr (Value StorePath)
-> SqlExpr (Value StorePath) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
==. StorePath -> SqlExpr (Value StorePath)
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
val StorePath
path)
(SqlExpr (Value Text), SqlExpr (Value StorePath))
-> SqlQuery (SqlExpr (Value Text), SqlExpr (Value StorePath))
forall a. a -> SqlQuery a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlExpr (Entity DerivationOutput)
drvOuts SqlExpr (Entity DerivationOutput)
-> EntityField DerivationOutput Text -> SqlExpr (Value Text)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField DerivationOutput Text
forall typ. (typ ~ Text) => EntityField DerivationOutput typ
DerivationOutputName, SqlExpr (Entity DerivationOutput)
drvOuts SqlExpr (Entity DerivationOutput)
-> EntityField DerivationOutput StorePath
-> SqlExpr (Value StorePath)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField DerivationOutput StorePath
forall typ. (typ ~ StorePath) => EntityField DerivationOutput typ
DerivationOutputPath)
[(Text, StorePath)] -> ReaderT backend m [(Text, StorePath)]
forall a. a -> ReaderT backend m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, StorePath)] -> ReaderT backend m [(Text, StorePath)])
-> [(Text, StorePath)] -> ReaderT backend m [(Text, StorePath)]
forall a b. (a -> b) -> a -> b
$ (Value Text, Value StorePath) -> (Text, StorePath)
forall a b. (Value a, Value b) -> (a, b)
unValue2 ((Value Text, Value StorePath) -> (Text, StorePath))
-> [(Value Text, Value StorePath)] -> [(Text, StorePath)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Value Text, Value StorePath)]
res
queryDerivationOutputs
:: ( MonadIO m
, MonadLogger m
)
=> Entity ValidPath
-> SqlReadT m [(Text, StorePath)]
queryDerivationOutputs :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
Entity ValidPath -> SqlReadT m [(Text, StorePath)]
queryDerivationOutputs Entity ValidPath
drv = do
[(Value Text, Value StorePath)]
res <- SqlQuery (SqlExpr (Value Text), SqlExpr (Value StorePath))
-> ReaderT backend m [(Value Text, Value StorePath)]
forall a r (m :: * -> *) backend.
(SqlSelect a r, MonadIO m, SqlBackendCanRead backend) =>
SqlQuery a -> ReaderT backend m [r]
select (SqlQuery (SqlExpr (Value Text), SqlExpr (Value StorePath))
-> ReaderT backend m [(Value Text, Value StorePath)])
-> SqlQuery (SqlExpr (Value Text), SqlExpr (Value StorePath))
-> ReaderT backend m [(Value Text, Value StorePath)]
forall a b. (a -> b) -> a -> b
$ do
SqlExpr (Entity DerivationOutput)
drvOuts <- From (SqlExpr (Entity DerivationOutput))
-> SqlQuery (SqlExpr (Entity DerivationOutput))
forall a a'. ToFrom a a' => a -> SqlQuery a'
from (From (SqlExpr (Entity DerivationOutput))
-> SqlQuery (SqlExpr (Entity DerivationOutput)))
-> From (SqlExpr (Entity DerivationOutput))
-> SqlQuery (SqlExpr (Entity DerivationOutput))
forall a b. (a -> b) -> a -> b
$ forall ent. PersistEntity ent => From (SqlExpr (Entity ent))
table @DerivationOutput
SqlExpr (Value Bool) -> SqlQuery ()
where_ (SqlExpr (Entity DerivationOutput)
drvOuts SqlExpr (Entity DerivationOutput)
-> EntityField DerivationOutput ValidPathId
-> SqlExpr (Value ValidPathId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField DerivationOutput ValidPathId
forall typ. (typ ~ ValidPathId) => EntityField DerivationOutput typ
DerivationOutputDrv SqlExpr (Value ValidPathId)
-> SqlExpr (Value ValidPathId) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
==. ValidPathId -> SqlExpr (Value ValidPathId)
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
val (Entity ValidPath -> ValidPathId
forall record. Entity record -> Key record
entityKey Entity ValidPath
drv))
(SqlExpr (Value Text), SqlExpr (Value StorePath))
-> SqlQuery (SqlExpr (Value Text), SqlExpr (Value StorePath))
forall a. a -> SqlQuery a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlExpr (Entity DerivationOutput)
drvOuts SqlExpr (Entity DerivationOutput)
-> EntityField DerivationOutput Text -> SqlExpr (Value Text)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField DerivationOutput Text
forall typ. (typ ~ Text) => EntityField DerivationOutput typ
DerivationOutputName, SqlExpr (Entity DerivationOutput)
drvOuts SqlExpr (Entity DerivationOutput)
-> EntityField DerivationOutput StorePath
-> SqlExpr (Value StorePath)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField DerivationOutput StorePath
forall typ. (typ ~ StorePath) => EntityField DerivationOutput typ
DerivationOutputPath)
[(Text, StorePath)] -> ReaderT backend m [(Text, StorePath)]
forall a. a -> ReaderT backend m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, StorePath)] -> ReaderT backend m [(Text, StorePath)])
-> [(Text, StorePath)] -> ReaderT backend m [(Text, StorePath)]
forall a b. (a -> b) -> a -> b
$ (Value Text, Value StorePath) -> (Text, StorePath)
forall a b. (Value a, Value b) -> (a, b)
unValue2 ((Value Text, Value StorePath) -> (Text, StorePath))
-> [(Value Text, Value StorePath)] -> [(Text, StorePath)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Value Text, Value StorePath)]
res
queryPathFromHashPart
:: ( MonadIO m
, MonadLogger m
)
=> StoreDir
-> StorePathHashPart
-> SqlReadT m (Maybe StorePath)
queryPathFromHashPart :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
StoreDir -> StorePathHashPart -> SqlReadT m (Maybe StorePath)
queryPathFromHashPart StoreDir
storeDir StorePathHashPart
hp =
let hashPart :: Text
hashPart =
( String -> Text
Data.Text.pack
(String -> Text) -> (RawFilePath -> String) -> RawFilePath -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RawFilePath -> String
Data.ByteString.Char8.unpack
(RawFilePath -> Text) -> RawFilePath -> Text
forall a b. (a -> b) -> a -> b
$ StoreDir -> RawFilePath
System.Nix.StorePath.unStoreDir StoreDir
storeDir
)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> StorePathHashPart -> Text
System.Nix.StorePath.storePathHashPartToText StorePathHashPart
hp
in do
[Entity ValidPath]
raw <- Text -> [PersistValue] -> ReaderT backend m [Entity ValidPath]
forall a (m :: * -> *) backend.
(RawSql a, MonadIO m, BackendCompatible SqlBackend backend) =>
Text -> [PersistValue] -> ReaderT backend m [a]
rawSql
Text
"select ?? from ValidPaths where path >= ? limit 1"
[Text -> PersistValue
PersistText Text
hashPart]
Maybe StorePath -> ReaderT backend m (Maybe StorePath)
forall a. a -> ReaderT backend m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Maybe StorePath -> ReaderT backend m (Maybe StorePath))
-> Maybe StorePath -> ReaderT backend m (Maybe StorePath)
forall a b. (a -> b) -> a -> b
$ [StorePath] -> Maybe StorePath
forall a. [a] -> Maybe a
Data.Maybe.listToMaybe
([StorePath] -> Maybe StorePath) -> [StorePath] -> Maybe StorePath
forall a b. (a -> b) -> a -> b
$ ValidPath -> StorePath
validPathPath (ValidPath -> StorePath)
-> (Entity ValidPath -> ValidPath) -> Entity ValidPath -> StorePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Entity ValidPath -> ValidPath
forall record. Entity record -> record
entityVal
(Entity ValidPath -> StorePath)
-> [Entity ValidPath] -> [StorePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Entity ValidPath]
raw
queryValidPathsEntity
:: ( MonadIO m
, MonadLogger m
)
=> SqlReadT m [Entity ValidPath]
queryValidPathsEntity :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT m [Entity ValidPath]
queryValidPathsEntity =
SqlQuery (SqlExpr (Entity ValidPath))
-> ReaderT backend m [Entity ValidPath]
forall a r (m :: * -> *) backend.
(SqlSelect a r, MonadIO m, SqlBackendCanRead backend) =>
SqlQuery a -> ReaderT backend m [r]
select (SqlQuery (SqlExpr (Entity ValidPath))
-> ReaderT backend m [Entity ValidPath])
-> SqlQuery (SqlExpr (Entity ValidPath))
-> ReaderT backend m [Entity ValidPath]
forall a b. (a -> b) -> a -> b
$ From (SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity ValidPath))
forall a a'. ToFrom a a' => a -> SqlQuery a'
from (From (SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity ValidPath)))
-> From (SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity ValidPath))
forall a b. (a -> b) -> a -> b
$ forall ent. PersistEntity ent => From (SqlExpr (Entity ent))
table @ValidPath
queryValidPaths
:: ( MonadIO m
, MonadLogger m
)
=> SqlReadT m [ValidPath]
queryValidPaths :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT m [ValidPath]
queryValidPaths =
ReaderT backend m [Entity ValidPath]
SqlReadT m [Entity ValidPath]
forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT m [Entity ValidPath]
queryValidPathsEntity
ReaderT backend m [Entity ValidPath]
-> ([Entity ValidPath] -> ReaderT backend m [ValidPath])
-> ReaderT backend m [ValidPath]
forall a b.
ReaderT backend m a
-> (a -> ReaderT backend m b) -> ReaderT backend m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [ValidPath] -> ReaderT backend m [ValidPath]
forall a. a -> ReaderT backend m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([ValidPath] -> ReaderT backend m [ValidPath])
-> ([Entity ValidPath] -> [ValidPath])
-> [Entity ValidPath]
-> ReaderT backend m [ValidPath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Entity ValidPath -> ValidPath)
-> [Entity ValidPath] -> [ValidPath]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Entity ValidPath -> ValidPath
forall record. Entity record -> record
entityVal
queryAllRefsEntity
:: ( MonadIO m
, MonadLogger m
)
=> SqlReadT m [Entity Ref]
queryAllRefsEntity :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT m [Entity Ref]
queryAllRefsEntity =
SqlQuery (SqlExpr (Entity Ref)) -> ReaderT backend m [Entity Ref]
forall a r (m :: * -> *) backend.
(SqlSelect a r, MonadIO m, SqlBackendCanRead backend) =>
SqlQuery a -> ReaderT backend m [r]
select (SqlQuery (SqlExpr (Entity Ref)) -> ReaderT backend m [Entity Ref])
-> SqlQuery (SqlExpr (Entity Ref))
-> ReaderT backend m [Entity Ref]
forall a b. (a -> b) -> a -> b
$ From (SqlExpr (Entity Ref)) -> SqlQuery (SqlExpr (Entity Ref))
forall a a'. ToFrom a a' => a -> SqlQuery a'
from (From (SqlExpr (Entity Ref)) -> SqlQuery (SqlExpr (Entity Ref)))
-> From (SqlExpr (Entity Ref)) -> SqlQuery (SqlExpr (Entity Ref))
forall a b. (a -> b) -> a -> b
$ forall ent. PersistEntity ent => From (SqlExpr (Entity ent))
table @Ref
queryAllRefs
:: ( MonadIO m
, MonadLogger m
)
=> SqlReadT m [Ref]
queryAllRefs :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT m [Ref]
queryAllRefs =
ReaderT backend m [Entity Ref]
SqlReadT m [Entity Ref]
forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT m [Entity Ref]
queryAllRefsEntity
ReaderT backend m [Entity Ref]
-> ([Entity Ref] -> ReaderT backend m [Ref])
-> ReaderT backend m [Ref]
forall a b.
ReaderT backend m a
-> (a -> ReaderT backend m b) -> ReaderT backend m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Ref] -> ReaderT backend m [Ref]
forall a. a -> ReaderT backend m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Ref] -> ReaderT backend m [Ref])
-> ([Entity Ref] -> [Ref])
-> [Entity Ref]
-> ReaderT backend m [Ref]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Entity Ref -> Ref) -> [Entity Ref] -> [Ref]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Entity Ref -> Ref
forall record. Entity record -> record
entityVal
queryAllDerivationOutputsEntity
:: ( MonadIO m
, MonadLogger m
)
=> SqlReadT m [Entity DerivationOutput]
queryAllDerivationOutputsEntity :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT m [Entity DerivationOutput]
queryAllDerivationOutputsEntity =
SqlQuery (SqlExpr (Entity DerivationOutput))
-> ReaderT backend m [Entity DerivationOutput]
forall a r (m :: * -> *) backend.
(SqlSelect a r, MonadIO m, SqlBackendCanRead backend) =>
SqlQuery a -> ReaderT backend m [r]
select (SqlQuery (SqlExpr (Entity DerivationOutput))
-> ReaderT backend m [Entity DerivationOutput])
-> SqlQuery (SqlExpr (Entity DerivationOutput))
-> ReaderT backend m [Entity DerivationOutput]
forall a b. (a -> b) -> a -> b
$ From (SqlExpr (Entity DerivationOutput))
-> SqlQuery (SqlExpr (Entity DerivationOutput))
forall a a'. ToFrom a a' => a -> SqlQuery a'
from (From (SqlExpr (Entity DerivationOutput))
-> SqlQuery (SqlExpr (Entity DerivationOutput)))
-> From (SqlExpr (Entity DerivationOutput))
-> SqlQuery (SqlExpr (Entity DerivationOutput))
forall a b. (a -> b) -> a -> b
$ forall ent. PersistEntity ent => From (SqlExpr (Entity ent))
table @DerivationOutput
queryAllDerivationOutputs
:: ( MonadIO m
, MonadLogger m
)
=> SqlReadT m [DerivationOutput]
queryAllDerivationOutputs :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT m [DerivationOutput]
queryAllDerivationOutputs =
ReaderT backend m [Entity DerivationOutput]
SqlReadT m [Entity DerivationOutput]
forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT m [Entity DerivationOutput]
queryAllDerivationOutputsEntity
ReaderT backend m [Entity DerivationOutput]
-> ([Entity DerivationOutput]
-> ReaderT backend m [DerivationOutput])
-> ReaderT backend m [DerivationOutput]
forall a b.
ReaderT backend m a
-> (a -> ReaderT backend m b) -> ReaderT backend m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [DerivationOutput] -> ReaderT backend m [DerivationOutput]
forall a. a -> ReaderT backend m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([DerivationOutput] -> ReaderT backend m [DerivationOutput])
-> ([Entity DerivationOutput] -> [DerivationOutput])
-> [Entity DerivationOutput]
-> ReaderT backend m [DerivationOutput]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Entity DerivationOutput -> DerivationOutput)
-> [Entity DerivationOutput] -> [DerivationOutput]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Entity DerivationOutput -> DerivationOutput
forall record. Entity record -> record
entityVal
queryOneValidDerivationEntity
:: ( MonadIO m
, MonadLogger m
)
=> SqlReadT m (Maybe (Entity ValidPath))
queryOneValidDerivationEntity :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT m (Maybe (Entity ValidPath))
queryOneValidDerivationEntity = do
[Entity ValidPath]
res <- SqlQuery (SqlExpr (Entity ValidPath))
-> ReaderT backend m [Entity ValidPath]
forall a r (m :: * -> *) backend.
(SqlSelect a r, MonadIO m, SqlBackendCanRead backend) =>
SqlQuery a -> ReaderT backend m [r]
select (SqlQuery (SqlExpr (Entity ValidPath))
-> ReaderT backend m [Entity ValidPath])
-> SqlQuery (SqlExpr (Entity ValidPath))
-> ReaderT backend m [Entity ValidPath]
forall a b. (a -> b) -> a -> b
$ do
SqlExpr (Entity ValidPath)
validPath <- From (SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity ValidPath))
forall a a'. ToFrom a a' => a -> SqlQuery a'
from (From (SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity ValidPath)))
-> From (SqlExpr (Entity ValidPath))
-> SqlQuery (SqlExpr (Entity ValidPath))
forall a b. (a -> b) -> a -> b
$ forall ent. PersistEntity ent => From (SqlExpr (Entity ent))
table @ValidPath
SqlExpr (Value Bool) -> SqlQuery ()
where_
(
SqlExpr (Entity ValidPath)
validPath SqlExpr (Entity ValidPath)
-> EntityField ValidPath (Maybe StorePathTrust)
-> SqlExpr (Value (Maybe StorePathTrust))
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
^. EntityField ValidPath (Maybe StorePathTrust)
forall typ.
(typ ~ Maybe StorePathTrust) =>
EntityField ValidPath typ
ValidPathUltimate
SqlExpr (Value (Maybe StorePathTrust))
-> SqlExpr (Value (Maybe StorePathTrust)) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
==. (Maybe StorePathTrust -> SqlExpr (Value (Maybe StorePathTrust))
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
val (Maybe StorePathTrust -> SqlExpr (Value (Maybe StorePathTrust)))
-> Maybe StorePathTrust -> SqlExpr (Value (Maybe StorePathTrust))
forall a b. (a -> b) -> a -> b
$ StorePathTrust -> Maybe StorePathTrust
forall a. a -> Maybe a
Just StorePathTrust
System.Nix.StorePath.Metadata.BuiltLocally)
)
Int64 -> SqlQuery ()
offset Int64
100
Int64 -> SqlQuery ()
limit Int64
1
SqlExpr (Entity ValidPath) -> SqlQuery (SqlExpr (Entity ValidPath))
forall a. a -> SqlQuery a
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlExpr (Entity ValidPath)
validPath
Maybe (Entity ValidPath)
-> ReaderT backend m (Maybe (Entity ValidPath))
forall a. a -> ReaderT backend m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (Entity ValidPath)
-> ReaderT backend m (Maybe (Entity ValidPath)))
-> Maybe (Entity ValidPath)
-> ReaderT backend m (Maybe (Entity ValidPath))
forall a b. (a -> b) -> a -> b
$ [Entity ValidPath] -> Maybe (Entity ValidPath)
forall a. [a] -> Maybe a
Data.Maybe.listToMaybe [Entity ValidPath]
res
queryOneValidDerivation
:: ( MonadIO m
, MonadLogger m
)
=> SqlReadT m (Maybe ValidPath)
queryOneValidDerivation :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT m (Maybe ValidPath)
queryOneValidDerivation =
ReaderT backend m (Maybe (Entity ValidPath))
SqlReadT m (Maybe (Entity ValidPath))
forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT m (Maybe (Entity ValidPath))
queryOneValidDerivationEntity
ReaderT backend m (Maybe (Entity ValidPath))
-> (Maybe (Entity ValidPath)
-> ReaderT backend m (Maybe ValidPath))
-> ReaderT backend m (Maybe ValidPath)
forall a b.
ReaderT backend m a
-> (a -> ReaderT backend m b) -> ReaderT backend m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe ValidPath -> ReaderT backend m (Maybe ValidPath)
forall a. a -> ReaderT backend m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe ValidPath -> ReaderT backend m (Maybe ValidPath))
-> (Maybe (Entity ValidPath) -> Maybe ValidPath)
-> Maybe (Entity ValidPath)
-> ReaderT backend m (Maybe ValidPath)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Entity ValidPath -> ValidPath)
-> Maybe (Entity ValidPath) -> Maybe ValidPath
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Entity ValidPath -> ValidPath
forall record. Entity record -> record
entityVal
queryEverything
:: ( MonadIO m
, MonadLogger m
)
=> SqlReadT m
( [Entity ValidPath]
, [Entity Ref]
, [Entity DerivationOutput]
)
queryEverything :: forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT
m ([Entity ValidPath], [Entity Ref], [Entity DerivationOutput])
queryEverything = (,,)
([Entity ValidPath]
-> [Entity Ref]
-> [Entity DerivationOutput]
-> ([Entity ValidPath], [Entity Ref], [Entity DerivationOutput]))
-> ReaderT backend m [Entity ValidPath]
-> ReaderT
backend
m
([Entity Ref]
-> [Entity DerivationOutput]
-> ([Entity ValidPath], [Entity Ref], [Entity DerivationOutput]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT backend m [Entity ValidPath]
SqlReadT m [Entity ValidPath]
forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT m [Entity ValidPath]
queryValidPathsEntity
ReaderT
backend
m
([Entity Ref]
-> [Entity DerivationOutput]
-> ([Entity ValidPath], [Entity Ref], [Entity DerivationOutput]))
-> ReaderT backend m [Entity Ref]
-> ReaderT
backend
m
([Entity DerivationOutput]
-> ([Entity ValidPath], [Entity Ref], [Entity DerivationOutput]))
forall a b.
ReaderT backend m (a -> b)
-> ReaderT backend m a -> ReaderT backend m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT backend m [Entity Ref]
SqlReadT m [Entity Ref]
forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT m [Entity Ref]
queryAllRefsEntity
ReaderT
backend
m
([Entity DerivationOutput]
-> ([Entity ValidPath], [Entity Ref], [Entity DerivationOutput]))
-> ReaderT backend m [Entity DerivationOutput]
-> ReaderT
backend
m
([Entity ValidPath], [Entity Ref], [Entity DerivationOutput])
forall a b.
ReaderT backend m (a -> b)
-> ReaderT backend m a -> ReaderT backend m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT backend m [Entity DerivationOutput]
SqlReadT m [Entity DerivationOutput]
forall (m :: * -> *).
(MonadIO m, MonadLogger m) =>
SqlReadT m [Entity DerivationOutput]
queryAllDerivationOutputsEntity
unValue2 :: (Value a, Value b) -> (a, b)
unValue2 :: forall a b. (Value a, Value b) -> (a, b)
unValue2 (Value a
a, Value b
b) = (Value a -> a
forall a. Value a -> a
unValue Value a
a, Value b -> b
forall a. Value a -> a
unValue Value b
b)