{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE OverloadedLabels #-}

module Hercules.Agent.NixFile
  ( -- * Schemas
    HomeSchema,
    HerculesCISchema,
    OnPushSchema,
    ExtraInputsSchema,
    InputDeclSchema,
    InputsSchema,
    InputSchema,
    OutputsSchema,

    -- * Loading
    findNixFile,
    loadNixFile,
    HomeExpr (..),
    homeExprRawValue,
    getHerculesCI,
    loadDefaultHerculesCI,

    -- * @onPush@
    getOnPushOutputValueByPath,
    parseExtraInputs,
  )
where

import Control.Monad.Trans.Maybe (MaybeT (MaybeT), runMaybeT)
import Hercules.API.Agent.Evaluate.EvaluateEvent.InputDeclaration (InputDeclaration (SiblingInput), SiblingInput (MkSiblingInput))
import qualified Hercules.API.Agent.Evaluate.EvaluateEvent.InputDeclaration
import Hercules.Agent.NixFile.CiNixArgs (CiNixArgs (CiNixArgs))
import qualified Hercules.Agent.NixFile.CiNixArgs
import Hercules.Agent.NixFile.GitSource (GitSource)
import Hercules.Agent.NixFile.HerculesCIArgs (HerculesCIArgs)
import qualified Hercules.Agent.NixFile.HerculesCIArgs as HerculesCIArgs
import Hercules.CNix.Expr
  ( EvalState,
    Match (IsAttrs),
    NixAttrs,
    Value (Value, rtValue),
    addAllowedPath,
    assertType,
    autoCallFunction,
    evalFile,
    getAttr,
    getLocalFlake,
    match',
    toRawValue,
    unsafeAssertType,
    valueFromExpressionString,
  )
import Hercules.CNix.Expr.Raw (RawValue)
import Hercules.CNix.Expr.Schema (Attrs, Dictionary, MonadEval, PSObject (PSObject), Provenance (Other), StringWithoutContext, basicAttrsWithProvenance, dictionaryToMap, fromPSObject, toPSObject, (#.), (#?), ($?), (.$), (>>$.), type (->.), type (->?), type (::.), type (::?))
import qualified Hercules.CNix.Expr.Schema as Schema
import Hercules.Error (escalateAs)
import Paths_hercules_ci_agent (getDataFileName)
import Protolude hiding (evalState)
import qualified System.Directory as Dir
import System.FilePath (takeFileName, (</>))

type Ambiguity = [FilePath]

searchPath :: [Ambiguity]
searchPath :: [Ambiguity]
searchPath = [[FilePath
"nix/ci.nix", FilePath
"ci.nix"], [FilePath
"flake.nix"], [FilePath
"default.nix"]]

findNixFile :: FilePath -> IO (Either Text FilePath)
findNixFile :: FilePath -> IO (Either Text FilePath)
findNixFile FilePath
projectDir = do
  [[Maybe (FilePath, FilePath)]]
searchResult <-
    [Ambiguity]
-> (Ambiguity -> IO [Maybe (FilePath, FilePath)])
-> IO [[Maybe (FilePath, FilePath)]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [Ambiguity]
searchPath ((Ambiguity -> IO [Maybe (FilePath, FilePath)])
 -> IO [[Maybe (FilePath, FilePath)]])
-> (Ambiguity -> IO [Maybe (FilePath, FilePath)])
-> IO [[Maybe (FilePath, FilePath)]]
forall a b. (a -> b) -> a -> b
$
      (FilePath -> IO (Maybe (FilePath, FilePath)))
-> Ambiguity -> IO [Maybe (FilePath, FilePath)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((FilePath -> IO (Maybe (FilePath, FilePath)))
 -> Ambiguity -> IO [Maybe (FilePath, FilePath)])
-> (FilePath -> IO (Maybe (FilePath, FilePath)))
-> Ambiguity
-> IO [Maybe (FilePath, FilePath)]
forall a b. (a -> b) -> a -> b
$ \FilePath
relPath ->
        let path :: FilePath
path = FilePath
projectDir FilePath -> FilePath -> FilePath
</> FilePath
relPath
         in FilePath -> IO Bool
Dir.doesFileExist FilePath
path IO Bool
-> (Bool -> IO (Maybe (FilePath, FilePath)))
-> IO (Maybe (FilePath, FilePath))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
              Bool
True -> Maybe (FilePath, FilePath) -> IO (Maybe (FilePath, FilePath))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (FilePath, FilePath) -> IO (Maybe (FilePath, FilePath)))
-> Maybe (FilePath, FilePath) -> IO (Maybe (FilePath, FilePath))
forall a b. (a -> b) -> a -> b
$ (FilePath, FilePath) -> Maybe (FilePath, FilePath)
forall a. a -> Maybe a
Just (FilePath
relPath, FilePath
path)
              Bool
False -> Maybe (FilePath, FilePath) -> IO (Maybe (FilePath, FilePath))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (FilePath, FilePath)
forall a. Maybe a
Nothing
  Either Text FilePath -> IO (Either Text FilePath)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either Text FilePath -> IO (Either Text FilePath))
-> Either Text FilePath -> IO (Either Text FilePath)
forall a b. (a -> b) -> a -> b
$ case ([(FilePath, FilePath)] -> Bool)
-> [[(FilePath, FilePath)]] -> [[(FilePath, FilePath)]]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> ([(FilePath, FilePath)] -> Bool)
-> [(FilePath, FilePath)]
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(FilePath, FilePath)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) ([[(FilePath, FilePath)]] -> [[(FilePath, FilePath)]])
-> [[(FilePath, FilePath)]] -> [[(FilePath, FilePath)]]
forall a b. (a -> b) -> a -> b
$ ([Maybe (FilePath, FilePath)] -> [(FilePath, FilePath)])
-> [[Maybe (FilePath, FilePath)]] -> [[(FilePath, FilePath)]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
map [Maybe (FilePath, FilePath)] -> [(FilePath, FilePath)]
forall a. [Maybe a] -> [a]
catMaybes [[Maybe (FilePath, FilePath)]]
searchResult of
    [(FilePath
_relPath, FilePath
unambiguous)] : [[(FilePath, FilePath)]]
_ -> FilePath -> Either Text FilePath
forall (f :: * -> *) a. Applicative f => a -> f a
pure FilePath
unambiguous
    [(FilePath, FilePath)]
ambiguous : [[(FilePath, FilePath)]]
_ ->
      Text -> Either Text FilePath
forall a b. a -> Either a b
Left (Text -> Either Text FilePath) -> Text -> Either Text FilePath
forall a b. (a -> b) -> a -> b
$
        Text
"Don't know what to do, expecting only one of "
          Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
Schema.englishOr (((FilePath, FilePath) -> Text) -> [(FilePath, FilePath)] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
map (FilePath -> Text
forall a b. ConvertText a b => a -> b
toS (FilePath -> Text)
-> ((FilePath, FilePath) -> FilePath)
-> (FilePath, FilePath)
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath, FilePath) -> FilePath
forall a b. (a, b) -> a
fst) [(FilePath, FilePath)]
ambiguous)
    [] ->
      Text -> Either Text FilePath
forall a b. a -> Either a b
Left (Text -> Either Text FilePath) -> Text -> Either Text FilePath
forall a b. (a -> b) -> a -> b
$
        Text
"Please provide a Nix expression to build. Could not find any of "
          Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
Schema.englishOr ((Ambiguity -> [Text]) -> [Ambiguity] -> [Text]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((FilePath -> Text) -> Ambiguity -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
map FilePath -> Text
forall a b. ConvertText a b => a -> b
toS) [Ambiguity]
searchPath)
          Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" in your source"

-- | Expression containing the bulk of the project
data HomeExpr
  = Flake (Value NixAttrs)
  | CiNix FilePath RawValue

homeExprRawValue :: HomeExpr -> RawValue
homeExprRawValue :: HomeExpr -> RawValue
homeExprRawValue (Flake (Value RawValue
r)) = RawValue
r
homeExprRawValue (CiNix FilePath
_ RawValue
r) = RawValue
r

loadNixFile :: Ptr EvalState -> FilePath -> GitSource -> IO (Either Text HomeExpr)
loadNixFile :: Ptr EvalState -> FilePath -> GitSource -> IO (Either Text HomeExpr)
loadNixFile Ptr EvalState
evalState FilePath
projectPath GitSource
src = ExceptT Text IO HomeExpr -> IO (Either Text HomeExpr)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT do
  FilePath
nixFile <- IO (Either Text FilePath) -> ExceptT Text IO FilePath
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (IO (Either Text FilePath) -> ExceptT Text IO FilePath)
-> IO (Either Text FilePath) -> ExceptT Text IO FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> IO (Either Text FilePath)
findNixFile FilePath
projectPath
  if FilePath -> FilePath
takeFileName FilePath
nixFile FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"flake.nix"
    then do
      Value NixAttrs
val <- IO (Value NixAttrs) -> ExceptT Text IO (Value NixAttrs)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Value NixAttrs) -> ExceptT Text IO (Value NixAttrs))
-> IO (Value NixAttrs) -> ExceptT Text IO (Value NixAttrs)
forall a b. (a -> b) -> a -> b
$ Ptr EvalState -> Text -> IO RawValue
getLocalFlake Ptr EvalState
evalState (FilePath -> Text
forall a b. ConvertText a b => a -> b
toS FilePath
projectPath) IO RawValue
-> (RawValue -> IO (Value NixAttrs)) -> IO (Value NixAttrs)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr EvalState -> RawValue -> IO (Value NixAttrs)
forall (m :: * -> *) t.
(HasCallStack, MonadIO m, CheckType t) =>
Ptr EvalState -> RawValue -> m (Value t)
assertType Ptr EvalState
evalState
      HomeExpr -> ExceptT Text IO HomeExpr
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value NixAttrs -> HomeExpr
Flake Value NixAttrs
val)
    else do
      RawValue
rootValueOrFunction <- IO RawValue -> ExceptT Text IO RawValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RawValue -> ExceptT Text IO RawValue)
-> IO RawValue -> ExceptT Text IO RawValue
forall a b. (a -> b) -> a -> b
$ Ptr EvalState -> FilePath -> IO RawValue
evalFile Ptr EvalState
evalState FilePath
nixFile
      Value NixAttrs
args <- forall a. RawValue -> Value a
unsafeAssertType @NixAttrs (RawValue -> Value NixAttrs)
-> ExceptT Text IO RawValue -> ExceptT Text IO (Value NixAttrs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO RawValue -> ExceptT Text IO RawValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Ptr EvalState -> CiNixArgs -> IO RawValue
forall a. ToRawValue a => Ptr EvalState -> a -> IO RawValue
toRawValue Ptr EvalState
evalState CiNixArgs :: GitSource -> CiNixArgs
CiNixArgs {src :: GitSource
src = GitSource
src})
      RawValue
homeExpr <- IO RawValue -> ExceptT Text IO RawValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RawValue -> ExceptT Text IO RawValue)
-> IO RawValue -> ExceptT Text IO RawValue
forall a b. (a -> b) -> a -> b
$ Ptr EvalState -> RawValue -> Value NixAttrs -> IO RawValue
autoCallFunction Ptr EvalState
evalState RawValue
rootValueOrFunction Value NixAttrs
args
      HomeExpr -> ExceptT Text IO HomeExpr
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilePath -> RawValue -> HomeExpr
CiNix FilePath
nixFile RawValue
homeExpr)

getHomeExprObject :: MonadEval m => HomeExpr -> m (PSObject HomeSchema)
getHomeExprObject :: forall (m :: * -> *).
MonadEval m =>
HomeExpr -> m (PSObject HomeSchema)
getHomeExprObject (Flake Value NixAttrs
attrs) = PSObject HomeSchema -> m (PSObject HomeSchema)
forall (f :: * -> *) a. Applicative f => a -> f a
pure PSObject :: forall a. Provenance -> RawValue -> PSObject a
PSObject {value :: RawValue
value = Value NixAttrs -> RawValue
forall a. Value a -> RawValue
rtValue Value NixAttrs
attrs, provenance :: Provenance
provenance = FilePath -> Provenance
Schema.File FilePath
"flake.nix"}
getHomeExprObject (CiNix FilePath
f RawValue
obj) = PSObject HomeSchema -> m (PSObject HomeSchema)
forall (f :: * -> *) a. Applicative f => a -> f a
pure PSObject :: forall a. Provenance -> RawValue -> PSObject a
PSObject {value :: RawValue
value = RawValue
obj, provenance :: Provenance
provenance = FilePath -> Provenance
Schema.File FilePath
f}

type HomeSchema = Attrs '["herculesCI" ::? Attrs '[] ->? HerculesCISchema]

type HerculesCISchema = Attrs '["onPush" ::? Dictionary OnPushSchema]

type OnPushSchema =
  Attrs
    '[ "extraInputs" ::? ExtraInputsSchema,
       "outputs" ::. InputsSchema ->? OutputsSchema,
       "enable" ::? Bool
     ]

type ExtraInputsSchema = Dictionary InputDeclSchema

type InputDeclSchema =
  Attrs
    '[ "project" ::. StringWithoutContext,
       "ref" ::? StringWithoutContext
     ]

type InputsSchema = Dictionary InputSchema

type InputSchema = Dictionary RawValue

type OutputsSchema = Dictionary RawValue

type DefaultHerculesCIHelperSchema =
  Attrs
    '[ "addDefaults" ::. Attrs '[] ->. Attrs '[] ->. HerculesCISchema
     ]

exprString :: forall a m. MonadEval m => ByteString -> m (PSObject a)
exprString :: forall a (m :: * -> *). MonadEval m => ByteString -> m (PSObject a)
exprString ByteString
bs = do
  Ptr EvalState
evalState <- m (Ptr EvalState)
forall r (m :: * -> *). MonadReader r m => m r
ask
  RawValue
value <- IO RawValue -> m RawValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RawValue -> m RawValue) -> IO RawValue -> m RawValue
forall a b. (a -> b) -> a -> b
$ Ptr EvalState -> ByteString -> ByteString -> IO RawValue
valueFromExpressionString Ptr EvalState
evalState ByteString
bs ByteString
"/var/lib/empty/hercules-ci-agent-builtin"
  PSObject a -> m (PSObject a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure PSObject :: forall a. Provenance -> RawValue -> PSObject a
PSObject {value :: RawValue
value = RawValue
value, provenance :: Provenance
provenance = Text -> Provenance
Schema.Other Text
"hercules-ci-agent built-in expression"}

getHerculesCI :: MonadEval m => HomeExpr -> HerculesCIArgs -> m (Maybe (PSObject HerculesCISchema))
getHerculesCI :: forall (m :: * -> *).
MonadEval m =>
HomeExpr -> HerculesCIArgs -> m (Maybe (PSObject HerculesCISchema))
getHerculesCI HomeExpr
homeExpr HerculesCIArgs
args = do
  PSObject HomeSchema
home <- HomeExpr -> m (PSObject HomeSchema)
forall (m :: * -> *).
MonadEval m =>
HomeExpr -> m (PSObject HomeSchema)
getHomeExprObject HomeExpr
homeExpr
  PSObject (Attrs '[])
args' <- PSObject (NixTypeFor HerculesCIArgs) -> PSObject (Attrs '[])
forall a b. PSObject a -> PSObject b
Schema.uncheckedCast (PSObject (NixTypeFor HerculesCIArgs) -> PSObject (Attrs '[]))
-> m (PSObject (NixTypeFor HerculesCIArgs))
-> m (PSObject (Attrs '[]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HerculesCIArgs -> m (PSObject (NixTypeFor HerculesCIArgs))
forall (m :: * -> *) a.
(MonadEval m, ToRawValue a) =>
a -> m (PSObject (NixTypeFor a))
toPSObject HerculesCIArgs
args
  case HomeExpr
homeExpr of
    CiNix {} ->
      PSObject HomeSchema
home PSObject HomeSchema
-> AttrLabel "herculesCI"
-> m (Maybe (PSObject (Attrs '[] ->? HerculesCISchema)))
forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, OptionalAttrType as s ~ b, MonadEval m) =>
PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject b))
#? IsLabel "herculesCI" (AttrLabel "herculesCI")
AttrLabel "herculesCI"
#herculesCI
        m (Maybe (PSObject (Attrs '[] ->? HerculesCISchema)))
-> (Maybe (PSObject (Attrs '[] ->? HerculesCISchema))
    -> m (Maybe (PSObject HerculesCISchema)))
-> m (Maybe (PSObject HerculesCISchema))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse @Maybe \PSObject (Attrs '[] ->? HerculesCISchema)
herculesCI ->
          PSObject (Attrs '[] ->? HerculesCISchema)
herculesCI PSObject (Attrs '[] ->? HerculesCISchema)
-> PSObject (Attrs '[]) -> m (PSObject HerculesCISchema)
forall (m :: * -> *) a b.
(MonadEval m, PossibleTypesForSchema a,
 PossibleTypesForSchema b) =>
PSObject (a ->? b) -> PSObject a -> m (PSObject b)
$? PSObject (Attrs '[])
args'
    Flake Value NixAttrs
flake ->
      PSObject HerculesCISchema -> Maybe (PSObject HerculesCISchema)
forall a. a -> Maybe a
Just (PSObject HerculesCISchema -> Maybe (PSObject HerculesCISchema))
-> m (PSObject HerculesCISchema)
-> m (Maybe (PSObject HerculesCISchema))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
        -- fixup primaryRepo.outPath, which we didn't set to the right value for
        -- flakes earlier, because we don't have a local checkout.
        PSObject (Attrs '[])
args'' <-
          forall a (m :: * -> *). MonadEval m => ByteString -> m (PSObject a)
exprString @(Attrs _ ->. HomeSchema ->. Attrs _)
            ByteString
"args': flake: args' // { primaryRepo = args'.primaryRepo // { outPath = flake.outPath; }; }"
            m (PSObject (Attrs '[] ->. (HomeSchema ->. Attrs '[])))
-> m (PSObject (Attrs '[]))
-> m (PSObject (HomeSchema ->. Attrs '[]))
forall (m :: * -> *) a b.
(MonadEval m, PossibleTypesForSchema a,
 PossibleTypesForSchema b) =>
m (PSObject (a ->. b)) -> m (PSObject a) -> m (PSObject b)
>>$. PSObject (Attrs '[]) -> m (PSObject (Attrs '[]))
forall (f :: * -> *) a. Applicative f => a -> f a
pure PSObject (Attrs '[])
args'
            m (PSObject (HomeSchema ->. Attrs '[]))
-> m (PSObject HomeSchema) -> m (PSObject (Attrs '[]))
forall (m :: * -> *) a b.
(MonadEval m, PossibleTypesForSchema a,
 PossibleTypesForSchema b) =>
m (PSObject (a ->. b)) -> m (PSObject a) -> m (PSObject b)
>>$. PSObject HomeSchema -> m (PSObject HomeSchema)
forall (f :: * -> *) a. Applicative f => a -> f a
pure PSObject HomeSchema
home

        PSObject DefaultHerculesCIHelperSchema
dh <- m (PSObject DefaultHerculesCIHelperSchema)
forall (m :: * -> *).
MonadEval m =>
m (PSObject DefaultHerculesCIHelperSchema)
loadDefaultHerculesCI
        PSObject (Attrs '[] ->. (Attrs '[] ->. HerculesCISchema))
fn <- PSObject DefaultHerculesCIHelperSchema
dh PSObject DefaultHerculesCIHelperSchema
-> AttrLabel "addDefaults"
-> m (PSObject (Attrs '[] ->. (Attrs '[] ->. HerculesCISchema)))
forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, AttrType as s ~ b, MonadEval m) =>
PSObject (Attrs' as w) -> AttrLabel s -> m (PSObject b)
#. IsLabel "addDefaults" (AttrLabel "addDefaults")
AttrLabel "addDefaults"
#addDefaults
        let flakeObj :: PSObject (Attrs '[])
flakeObj = Value NixAttrs -> Provenance -> PSObject (Attrs '[])
basicAttrsWithProvenance Value NixAttrs
flake (Provenance -> PSObject (Attrs '[]))
-> Provenance -> PSObject (Attrs '[])
forall a b. (a -> b) -> a -> b
$ Text -> Provenance
Schema.Other Text
"your flake"
        PSObject HerculesCISchema
hci <- PSObject (Attrs '[] ->. (Attrs '[] ->. HerculesCISchema))
fn PSObject (Attrs '[] ->. (Attrs '[] ->. HerculesCISchema))
-> PSObject (Attrs '[])
-> m (PSObject (Attrs '[] ->. HerculesCISchema))
forall (m :: * -> *) a b.
MonadIO m =>
PSObject (a ->. b) -> PSObject a -> m (PSObject b)
.$ PSObject (Attrs '[])
flakeObj m (PSObject (Attrs '[] ->. HerculesCISchema))
-> m (PSObject (Attrs '[])) -> m (PSObject HerculesCISchema)
forall (m :: * -> *) a b.
(MonadEval m, PossibleTypesForSchema a,
 PossibleTypesForSchema b) =>
m (PSObject (a ->. b)) -> m (PSObject a) -> m (PSObject b)
>>$. PSObject (Attrs '[]) -> m (PSObject (Attrs '[]))
forall (f :: * -> *) a. Applicative f => a -> f a
pure PSObject (Attrs '[])
args''
        PSObject HerculesCISchema -> m (PSObject HerculesCISchema)
forall (f :: * -> *) a. Applicative f => a -> f a
pure PSObject HerculesCISchema
hci {provenance :: Provenance
Schema.provenance = Text -> Provenance
Other Text
"the herculesCI attribute of your flake (after adding defaults)"}

parseExtraInputs :: MonadEval m => PSObject ExtraInputsSchema -> m (Map ByteString InputDeclaration)
parseExtraInputs :: forall (m :: * -> *).
MonadEval m =>
PSObject ExtraInputsSchema -> m (Map ByteString InputDeclaration)
parseExtraInputs PSObject ExtraInputsSchema
eis = PSObject ExtraInputsSchema
-> m (Map ByteString (PSObject InputDeclSchema))
forall (m :: * -> *) w.
MonadEval m =>
PSObject (Dictionary w) -> m (Map ByteString (PSObject w))
dictionaryToMap PSObject ExtraInputsSchema
eis m (Map ByteString (PSObject InputDeclSchema))
-> (Map ByteString (PSObject InputDeclSchema)
    -> m (Map ByteString InputDeclaration))
-> m (Map ByteString InputDeclaration)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (PSObject InputDeclSchema -> m InputDeclaration)
-> Map ByteString (PSObject InputDeclSchema)
-> m (Map ByteString InputDeclaration)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse PSObject InputDeclSchema -> m InputDeclaration
forall (m :: * -> *).
MonadEval m =>
PSObject InputDeclSchema -> m InputDeclaration
parseInputDecl

parseInputDecl :: MonadEval m => PSObject InputDeclSchema -> m InputDeclaration
parseInputDecl :: forall (m :: * -> *).
MonadEval m =>
PSObject InputDeclSchema -> m InputDeclaration
parseInputDecl PSObject InputDeclSchema
d = do
  Text
project <- PSObject InputDeclSchema
d PSObject InputDeclSchema
-> AttrLabel "project" -> m (PSObject StringWithoutContext)
forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, AttrType as s ~ b, MonadEval m) =>
PSObject (Attrs' as w) -> AttrLabel s -> m (PSObject b)
#. IsLabel "project" (AttrLabel "project")
AttrLabel "project"
#project m (PSObject StringWithoutContext)
-> (PSObject StringWithoutContext -> m Text) -> m Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= PSObject StringWithoutContext -> m Text
forall schema a (m :: * -> *).
(FromPSObject schema a, MonadEval m) =>
PSObject schema -> m a
fromPSObject
  Maybe Text
ref <- PSObject InputDeclSchema
d PSObject InputDeclSchema
-> AttrLabel "ref" -> m (Maybe (PSObject StringWithoutContext))
forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, OptionalAttrType as s ~ b, MonadEval m) =>
PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject b))
#? IsLabel "ref" (AttrLabel "ref")
AttrLabel "ref"
#ref m (Maybe (PSObject StringWithoutContext))
-> (Maybe (PSObject StringWithoutContext) -> m (Maybe Text))
-> m (Maybe Text)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (PSObject StringWithoutContext -> m Text)
-> Maybe (PSObject StringWithoutContext) -> m (Maybe Text)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse PSObject StringWithoutContext -> m Text
forall schema a (m :: * -> *).
(FromPSObject schema a, MonadEval m) =>
PSObject schema -> m a
fromPSObject
  InputDeclaration -> m InputDeclaration
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InputDeclaration -> m InputDeclaration)
-> InputDeclaration -> m InputDeclaration
forall a b. (a -> b) -> a -> b
$ SiblingInput -> InputDeclaration
SiblingInput (SiblingInput -> InputDeclaration)
-> SiblingInput -> InputDeclaration
forall a b. (a -> b) -> a -> b
$ MkSiblingInput :: Text -> Maybe Text -> SiblingInput
MkSiblingInput {project :: Text
project = Text
project, ref :: Maybe Text
ref = Maybe Text
ref}

-- | Given a path, return the onPush output or legacy ci.nix value
--
-- @@@
-- e.g.  ["a" "b"]  => ((import file).herculesCI args).onPush.a.outputs.b
--       or falling back to
--       ["a" "b"]  => (import file legacyArgs).a.b
-- @@@
getOnPushOutputValueByPath ::
  Ptr EvalState ->
  FilePath ->
  HerculesCIArgs ->
  -- | Resolve inputs to an attrset of fetched/fetchable stuff
  (Map ByteString InputDeclaration -> IO (Value NixAttrs)) ->
  [ByteString] ->
  IO (Maybe RawValue)
getOnPushOutputValueByPath :: Ptr EvalState
-> FilePath
-> HerculesCIArgs
-> (Map ByteString InputDeclaration -> IO (Value NixAttrs))
-> [ByteString]
-> IO (Maybe RawValue)
getOnPushOutputValueByPath Ptr EvalState
evalState FilePath
filePath HerculesCIArgs
args Map ByteString InputDeclaration -> IO (Value NixAttrs)
resolveInputs [ByteString]
attrPath = do
  HomeExpr
homeExpr <- (Text -> FatalError) -> Either Text HomeExpr -> IO HomeExpr
forall exc (m :: * -> *) l a.
(Exception exc, MonadThrow m) =>
(l -> exc) -> Either l a -> m a
escalateAs Text -> FatalError
FatalError (Either Text HomeExpr -> IO HomeExpr)
-> IO (Either Text HomeExpr) -> IO HomeExpr
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr EvalState -> FilePath -> GitSource -> IO (Either Text HomeExpr)
loadNixFile Ptr EvalState
evalState FilePath
filePath (HerculesCIArgs -> GitSource
HerculesCIArgs.primaryRepo HerculesCIArgs
args)
  Maybe (PSObject (Dictionary OnPushSchema))
onPush <- (ReaderT
   (Ptr EvalState) IO (Maybe (PSObject (Dictionary OnPushSchema)))
 -> Ptr EvalState
 -> IO (Maybe (PSObject (Dictionary OnPushSchema))))
-> Ptr EvalState
-> ReaderT
     (Ptr EvalState) IO (Maybe (PSObject (Dictionary OnPushSchema)))
-> IO (Maybe (PSObject (Dictionary OnPushSchema)))
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT
  (Ptr EvalState) IO (Maybe (PSObject (Dictionary OnPushSchema)))
-> Ptr EvalState -> IO (Maybe (PSObject (Dictionary OnPushSchema)))
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT Ptr EvalState
evalState (ReaderT
   (Ptr EvalState) IO (Maybe (PSObject (Dictionary OnPushSchema)))
 -> IO (Maybe (PSObject (Dictionary OnPushSchema))))
-> ReaderT
     (Ptr EvalState) IO (Maybe (PSObject (Dictionary OnPushSchema)))
-> IO (Maybe (PSObject (Dictionary OnPushSchema)))
forall a b. (a -> b) -> a -> b
$ MaybeT
  (ReaderT (Ptr EvalState) IO) (PSObject (Dictionary OnPushSchema))
-> ReaderT
     (Ptr EvalState) IO (Maybe (PSObject (Dictionary OnPushSchema)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
    PSObject HerculesCISchema
herculesCI <- ReaderT (Ptr EvalState) IO (Maybe (PSObject HerculesCISchema))
-> MaybeT (ReaderT (Ptr EvalState) IO) (PSObject HerculesCISchema)
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (ReaderT (Ptr EvalState) IO (Maybe (PSObject HerculesCISchema))
 -> MaybeT (ReaderT (Ptr EvalState) IO) (PSObject HerculesCISchema))
-> ReaderT (Ptr EvalState) IO (Maybe (PSObject HerculesCISchema))
-> MaybeT (ReaderT (Ptr EvalState) IO) (PSObject HerculesCISchema)
forall a b. (a -> b) -> a -> b
$ HomeExpr
-> HerculesCIArgs
-> ReaderT (Ptr EvalState) IO (Maybe (PSObject HerculesCISchema))
forall (m :: * -> *).
MonadEval m =>
HomeExpr -> HerculesCIArgs -> m (Maybe (PSObject HerculesCISchema))
getHerculesCI HomeExpr
homeExpr HerculesCIArgs
args
    ReaderT
  (Ptr EvalState) IO (Maybe (PSObject (Dictionary OnPushSchema)))
-> MaybeT
     (ReaderT (Ptr EvalState) IO) (PSObject (Dictionary OnPushSchema))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (ReaderT
   (Ptr EvalState) IO (Maybe (PSObject (Dictionary OnPushSchema)))
 -> MaybeT
      (ReaderT (Ptr EvalState) IO) (PSObject (Dictionary OnPushSchema)))
-> ReaderT
     (Ptr EvalState) IO (Maybe (PSObject (Dictionary OnPushSchema)))
-> MaybeT
     (ReaderT (Ptr EvalState) IO) (PSObject (Dictionary OnPushSchema))
forall a b. (a -> b) -> a -> b
$ PSObject HerculesCISchema
herculesCI PSObject HerculesCISchema
-> AttrLabel "onPush"
-> ReaderT
     (Ptr EvalState) IO (Maybe (PSObject (Dictionary OnPushSchema)))
forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, OptionalAttrType as s ~ b, MonadEval m) =>
PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject b))
#? IsLabel "onPush" (AttrLabel "onPush")
AttrLabel "onPush"
#onPush

  -- No backtracking. It's either legacy or not...
  case Maybe (PSObject (Dictionary OnPushSchema))
onPush of
    Just PSObject (Dictionary OnPushSchema)
jobs -> (ReaderT (Ptr EvalState) IO (Maybe RawValue)
 -> Ptr EvalState -> IO (Maybe RawValue))
-> Ptr EvalState
-> ReaderT (Ptr EvalState) IO (Maybe RawValue)
-> IO (Maybe RawValue)
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT (Ptr EvalState) IO (Maybe RawValue)
-> Ptr EvalState -> IO (Maybe RawValue)
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT Ptr EvalState
evalState (ReaderT (Ptr EvalState) IO (Maybe RawValue)
 -> IO (Maybe RawValue))
-> ReaderT (Ptr EvalState) IO (Maybe RawValue)
-> IO (Maybe RawValue)
forall a b. (a -> b) -> a -> b
$ do
      case [ByteString]
attrPath of
        [] -> Maybe RawValue -> ReaderT (Ptr EvalState) IO (Maybe RawValue)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe RawValue -> ReaderT (Ptr EvalState) IO (Maybe RawValue))
-> Maybe RawValue -> ReaderT (Ptr EvalState) IO (Maybe RawValue)
forall a b. (a -> b) -> a -> b
$ RawValue -> Maybe RawValue
forall a. a -> Maybe a
Just (RawValue -> Maybe RawValue) -> RawValue -> Maybe RawValue
forall a b. (a -> b) -> a -> b
$ PSObject (Dictionary OnPushSchema) -> RawValue
forall a. PSObject a -> RawValue
Schema.value PSObject (Dictionary OnPushSchema)
jobs -- Technically mapAttrs .outputs, meh
        (ByteString
jobName : [ByteString]
attrPath') -> do
          ByteString
-> PSObject (Dictionary OnPushSchema)
-> ReaderT (Ptr EvalState) IO (Maybe (PSObject OnPushSchema))
forall (m :: * -> *) (as :: [Attr]) w.
MonadEval m =>
ByteString -> PSObject (Attrs' as w) -> m (Maybe (PSObject w))
Schema.lookupDictBS ByteString
jobName PSObject (Dictionary OnPushSchema)
jobs ReaderT (Ptr EvalState) IO (Maybe (PSObject OnPushSchema))
-> (Maybe (PSObject OnPushSchema)
    -> ReaderT (Ptr EvalState) IO (Maybe RawValue))
-> ReaderT (Ptr EvalState) IO (Maybe RawValue)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            Just PSObject OnPushSchema
selectedJob -> do
              PSObject OutputsSchema
outputs <- PSObject OnPushSchema
-> (Map ByteString InputDeclaration
    -> ReaderT (Ptr EvalState) IO (Value NixAttrs))
-> ReaderT (Ptr EvalState) IO (PSObject OutputsSchema)
forall (m :: * -> *).
MonadEval m =>
PSObject OnPushSchema
-> (Map ByteString InputDeclaration -> m (Value NixAttrs))
-> m (PSObject OutputsSchema)
resolveAndInvokeOutputs PSObject OnPushSchema
selectedJob (IO (Value NixAttrs) -> ReaderT (Ptr EvalState) IO (Value NixAttrs)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Value NixAttrs)
 -> ReaderT (Ptr EvalState) IO (Value NixAttrs))
-> (Map ByteString InputDeclaration -> IO (Value NixAttrs))
-> Map ByteString InputDeclaration
-> ReaderT (Ptr EvalState) IO (Value NixAttrs)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map ByteString InputDeclaration -> IO (Value NixAttrs)
resolveInputs)
              Value NixAttrs
outputAttrs <- PSObject OutputsSchema
-> ReaderT
     (Ptr EvalState) IO (Value (NixTypeForSchema OutputsSchema))
forall schema (m :: * -> *).
(CheckType (NixTypeForSchema schema),
 HasRawValueType (NixTypeForSchema schema), MonadEval m) =>
PSObject schema -> m (Value (NixTypeForSchema schema))
Schema.check PSObject OutputsSchema
outputs
              IO (Maybe RawValue) -> ReaderT (Ptr EvalState) IO (Maybe RawValue)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe RawValue)
 -> ReaderT (Ptr EvalState) IO (Maybe RawValue))
-> IO (Maybe RawValue)
-> ReaderT (Ptr EvalState) IO (Maybe RawValue)
forall a b. (a -> b) -> a -> b
$ Ptr EvalState -> RawValue -> [ByteString] -> IO (Maybe RawValue)
attrByPath Ptr EvalState
evalState (Value NixAttrs -> RawValue
forall a. Value a -> RawValue
rtValue Value NixAttrs
outputAttrs) [ByteString]
attrPath'
            Maybe (PSObject OnPushSchema)
Nothing -> Maybe RawValue -> ReaderT (Ptr EvalState) IO (Maybe RawValue)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe RawValue
forall a. Maybe a
Nothing
    Maybe (PSObject (Dictionary OnPushSchema))
Nothing -> do
      Ptr EvalState -> RawValue -> [ByteString] -> IO (Maybe RawValue)
attrByPath Ptr EvalState
evalState (HomeExpr -> RawValue
homeExprRawValue HomeExpr
homeExpr) [ByteString]
attrPath

resolveAndInvokeOutputs :: MonadEval m => PSObject OnPushSchema -> (Map ByteString InputDeclaration -> m (Value NixAttrs)) -> m (PSObject OutputsSchema)
resolveAndInvokeOutputs :: forall (m :: * -> *).
MonadEval m =>
PSObject OnPushSchema
-> (Map ByteString InputDeclaration -> m (Value NixAttrs))
-> m (PSObject OutputsSchema)
resolveAndInvokeOutputs PSObject OnPushSchema
job Map ByteString InputDeclaration -> m (Value NixAttrs)
resolveInputs = do
  Maybe (Map ByteString InputDeclaration)
inputs <- PSObject OnPushSchema
job PSObject OnPushSchema
-> AttrLabel "extraInputs"
-> m (Maybe (PSObject ExtraInputsSchema))
forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, OptionalAttrType as s ~ b, MonadEval m) =>
PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject b))
#? IsLabel "extraInputs" (AttrLabel "extraInputs")
AttrLabel "extraInputs"
#extraInputs m (Maybe (PSObject ExtraInputsSchema))
-> (Maybe (PSObject ExtraInputsSchema)
    -> m (Maybe (Map ByteString InputDeclaration)))
-> m (Maybe (Map ByteString InputDeclaration))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (PSObject ExtraInputsSchema -> m (Map ByteString InputDeclaration))
-> Maybe (PSObject ExtraInputsSchema)
-> m (Maybe (Map ByteString InputDeclaration))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse PSObject ExtraInputsSchema -> m (Map ByteString InputDeclaration)
forall (m :: * -> *).
MonadEval m =>
PSObject ExtraInputsSchema -> m (Map ByteString InputDeclaration)
parseExtraInputs
  Value NixAttrs
resolved <- Map ByteString InputDeclaration -> m (Value NixAttrs)
resolveInputs (Map ByteString InputDeclaration
-> Maybe (Map ByteString InputDeclaration)
-> Map ByteString InputDeclaration
forall a. a -> Maybe a -> a
fromMaybe Map ByteString InputDeclaration
forall a. Monoid a => a
mempty Maybe (Map ByteString InputDeclaration)
inputs)
  PSObject (InputsSchema ->? OutputsSchema)
f <- PSObject OnPushSchema
job PSObject OnPushSchema
-> AttrLabel "outputs"
-> m (PSObject (InputsSchema ->? OutputsSchema))
forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, AttrType as s ~ b, MonadEval m) =>
PSObject (Attrs' as w) -> AttrLabel s -> m (PSObject b)
#. IsLabel "outputs" (AttrLabel "outputs")
AttrLabel "outputs"
#outputs
  PSObject (InputsSchema ->? OutputsSchema)
f PSObject (InputsSchema ->? OutputsSchema)
-> PSObject InputsSchema -> m (PSObject OutputsSchema)
forall (m :: * -> *) a b.
(MonadEval m, PossibleTypesForSchema a,
 PossibleTypesForSchema b) =>
PSObject (a ->? b) -> PSObject a -> m (PSObject b)
$? (PSObject :: forall a. Provenance -> RawValue -> PSObject a
PSObject {provenance :: Provenance
provenance = Provenance
Schema.Data, value :: RawValue
value = Value NixAttrs -> RawValue
forall a. Value a -> RawValue
rtValue Value NixAttrs
resolved})

attrByPath :: Ptr EvalState -> RawValue -> [ByteString] -> IO (Maybe RawValue)
attrByPath :: Ptr EvalState -> RawValue -> [ByteString] -> IO (Maybe RawValue)
attrByPath Ptr EvalState
_ RawValue
v [] = Maybe RawValue -> IO (Maybe RawValue)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RawValue -> Maybe RawValue
forall a. a -> Maybe a
Just RawValue
v)
attrByPath Ptr EvalState
evalState RawValue
v (ByteString
a : [ByteString]
as) = do
  Ptr EvalState -> RawValue -> IO Match
match' Ptr EvalState
evalState RawValue
v IO Match -> (Match -> IO (Maybe RawValue)) -> IO (Maybe RawValue)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    IsAttrs Value NixAttrs
attrs ->
      Ptr EvalState
-> Value NixAttrs -> ByteString -> IO (Maybe RawValue)
getAttr Ptr EvalState
evalState Value NixAttrs
attrs ByteString
a
        IO (Maybe RawValue)
-> (Maybe RawValue -> IO (Maybe (Maybe RawValue)))
-> IO (Maybe (Maybe RawValue))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (RawValue -> IO (Maybe RawValue))
-> Maybe RawValue -> IO (Maybe (Maybe RawValue))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\RawValue
attrValue -> Ptr EvalState -> RawValue -> [ByteString] -> IO (Maybe RawValue)
attrByPath Ptr EvalState
evalState RawValue
attrValue [ByteString]
as)
        IO (Maybe (Maybe RawValue))
-> (IO (Maybe (Maybe RawValue)) -> IO (Maybe RawValue))
-> IO (Maybe RawValue)
forall a b. a -> (a -> b) -> b
& (Maybe (Maybe RawValue) -> Maybe RawValue)
-> IO (Maybe (Maybe RawValue)) -> IO (Maybe RawValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe (Maybe RawValue) -> Maybe RawValue
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join
    Match
_ -> Maybe RawValue -> IO (Maybe RawValue)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe RawValue
forall a. Maybe a
Nothing

loadDefaultHerculesCI :: (MonadEval m) => m (PSObject DefaultHerculesCIHelperSchema)
loadDefaultHerculesCI :: forall (m :: * -> *).
MonadEval m =>
m (PSObject DefaultHerculesCIHelperSchema)
loadDefaultHerculesCI = do
  FilePath
fname <- IO FilePath -> m FilePath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FilePath -> m FilePath) -> IO FilePath -> m FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
getDataFileName FilePath
"data/default-herculesCI-for-flake.nix"
  Ptr EvalState
evalState <- m (Ptr EvalState)
forall r (m :: * -> *). MonadReader r m => m r
ask
  IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Ptr EvalState -> ByteString -> IO ()
addAllowedPath Ptr EvalState
evalState (ByteString -> IO ())
-> (FilePath -> ByteString) -> FilePath -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 (Text -> ByteString)
-> (FilePath -> Text) -> FilePath -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Text
forall a b. ConvertText a b => a -> b
toS (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
fname
  RawValue
v <- IO RawValue -> m RawValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RawValue -> m RawValue) -> IO RawValue -> m RawValue
forall a b. (a -> b) -> a -> b
$ Ptr EvalState -> FilePath -> IO RawValue
evalFile Ptr EvalState
evalState FilePath
fname
  PSObject DefaultHerculesCIHelperSchema
-> m (PSObject DefaultHerculesCIHelperSchema)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PSObject :: forall a. Provenance -> RawValue -> PSObject a
PSObject {value :: RawValue
value = RawValue
v, provenance :: Provenance
provenance = Text -> Provenance
Other Text
"<default herculesCI helper shim>"})