{-# LANGUAGE DeriveAnyClass #-}

module Hercules.Agent.WorkerProtocol.Command.Eval where

import Data.Binary
import Hercules.API.Agent.Evaluate.EvaluateTask qualified as EvaluateTask
import Hercules.API.Agent.Evaluate.ImmutableGitInput (ImmutableGitInput)
import Hercules.Agent.NixFile.GitSource (GitSource)
import Hercules.Agent.WorkerProtocol.Orphans ()
import Hercules.Agent.WorkerProtocol.ViaJSON (ViaJSON)
import Protolude

data Eval = Eval
  { Eval -> FilePath
cwd :: FilePath,
    Eval -> Text
file :: Text,
    Eval -> Map Text Arg
autoArguments :: Map Text Arg,
    -- TODO: Also set at worker start, so remove this here to avoid ambiguity?
    Eval -> [(Text, Text)]
extraNixOptions :: [(Text, Text)],
    Eval -> ViaJSON GitSource
gitSource :: ViaJSON GitSource,
    Eval -> Maybe (ViaJSON ImmutableGitInput)
srcInput :: Maybe (ViaJSON ImmutableGitInput),
    Eval -> Text
apiBaseUrl :: Text,
    Eval -> ViaJSON Selector
selector :: ViaJSON EvaluateTask.Selector,
    Eval -> Bool
isFlakeJob :: Bool,
    Eval -> Maybe (Map Text ())
ciSystems :: Maybe (Map Text ()),
    Eval -> Bool
allowInsecureBuiltinFetchers :: Bool,
    Eval -> [ByteString]
allowedPaths :: [ByteString]
  }
  deriving ((forall x. Eval -> Rep Eval x)
-> (forall x. Rep Eval x -> Eval) -> Generic Eval
forall x. Rep Eval x -> Eval
forall x. Eval -> Rep Eval x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Eval -> Rep Eval x
from :: forall x. Eval -> Rep Eval x
$cto :: forall x. Rep Eval x -> Eval
to :: forall x. Rep Eval x -> Eval
Generic, Get Eval
[Eval] -> Put
Eval -> Put
(Eval -> Put) -> Get Eval -> ([Eval] -> Put) -> Binary Eval
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
$cput :: Eval -> Put
put :: Eval -> Put
$cget :: Get Eval
get :: Get Eval
$cputList :: [Eval] -> Put
putList :: [Eval] -> Put
Binary, Int -> Eval -> ShowS
[Eval] -> ShowS
Eval -> FilePath
(Int -> Eval -> ShowS)
-> (Eval -> FilePath) -> ([Eval] -> ShowS) -> Show Eval
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Eval -> ShowS
showsPrec :: Int -> Eval -> ShowS
$cshow :: Eval -> FilePath
show :: Eval -> FilePath
$cshowList :: [Eval] -> ShowS
showList :: [Eval] -> ShowS
Show, Eval -> Eval -> Bool
(Eval -> Eval -> Bool) -> (Eval -> Eval -> Bool) -> Eq Eval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Eval -> Eval -> Bool
== :: Eval -> Eval -> Bool
$c/= :: Eval -> Eval -> Bool
/= :: Eval -> Eval -> Bool
Eq)

data Arg
  = LiteralArg ByteString
  | ExprArg ByteString
  deriving ((forall x. Arg -> Rep Arg x)
-> (forall x. Rep Arg x -> Arg) -> Generic Arg
forall x. Rep Arg x -> Arg
forall x. Arg -> Rep Arg x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Arg -> Rep Arg x
from :: forall x. Arg -> Rep Arg x
$cto :: forall x. Rep Arg x -> Arg
to :: forall x. Rep Arg x -> Arg
Generic, Get Arg
[Arg] -> Put
Arg -> Put
(Arg -> Put) -> Get Arg -> ([Arg] -> Put) -> Binary Arg
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
$cput :: Arg -> Put
put :: Arg -> Put
$cget :: Get Arg
get :: Get Arg
$cputList :: [Arg] -> Put
putList :: [Arg] -> Put
Binary, Int -> Arg -> ShowS
[Arg] -> ShowS
Arg -> FilePath
(Int -> Arg -> ShowS)
-> (Arg -> FilePath) -> ([Arg] -> ShowS) -> Show Arg
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Arg -> ShowS
showsPrec :: Int -> Arg -> ShowS
$cshow :: Arg -> FilePath
show :: Arg -> FilePath
$cshowList :: [Arg] -> ShowS
showList :: [Arg] -> ShowS
Show, Arg -> Arg -> Bool
(Arg -> Arg -> Bool) -> (Arg -> Arg -> Bool) -> Eq Arg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Arg -> Arg -> Bool
== :: Arg -> Arg -> Bool
$c/= :: Arg -> Arg -> Bool
/= :: Arg -> Arg -> Bool
Eq)