{-# LANGUAGE DeriveAnyClass #-}

module Hercules.Agent.WorkerProtocol.OutputInfo where

import Data.Binary
import Protolude

data OutputInfo = OutputInfo
  { -- | e.g. out, dev
    OutputInfo -> ByteString
name :: ByteString,
    -- | store path
    OutputInfo -> ByteString
path :: ByteString,
    -- | typically sha256:...
    OutputInfo -> ByteString
hash :: ByteString,
    -- | nar size in bytes
    OutputInfo -> Int64
size :: Int64,
    -- | references, in store path basename format
    OutputInfo -> [ByteString]
references :: [ByteString]
  }
  deriving ((forall x. OutputInfo -> Rep OutputInfo x)
-> (forall x. Rep OutputInfo x -> OutputInfo) -> Generic OutputInfo
forall x. Rep OutputInfo x -> OutputInfo
forall x. OutputInfo -> Rep OutputInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OutputInfo -> Rep OutputInfo x
from :: forall x. OutputInfo -> Rep OutputInfo x
$cto :: forall x. Rep OutputInfo x -> OutputInfo
to :: forall x. Rep OutputInfo x -> OutputInfo
Generic, Get OutputInfo
[OutputInfo] -> Put
OutputInfo -> Put
(OutputInfo -> Put)
-> Get OutputInfo -> ([OutputInfo] -> Put) -> Binary OutputInfo
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
$cput :: OutputInfo -> Put
put :: OutputInfo -> Put
$cget :: Get OutputInfo
get :: Get OutputInfo
$cputList :: [OutputInfo] -> Put
putList :: [OutputInfo] -> Put
Binary, Int -> OutputInfo -> ShowS
[OutputInfo] -> ShowS
OutputInfo -> String
(Int -> OutputInfo -> ShowS)
-> (OutputInfo -> String)
-> ([OutputInfo] -> ShowS)
-> Show OutputInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OutputInfo -> ShowS
showsPrec :: Int -> OutputInfo -> ShowS
$cshow :: OutputInfo -> String
show :: OutputInfo -> String
$cshowList :: [OutputInfo] -> ShowS
showList :: [OutputInfo] -> ShowS
Show, OutputInfo -> OutputInfo -> Bool
(OutputInfo -> OutputInfo -> Bool)
-> (OutputInfo -> OutputInfo -> Bool) -> Eq OutputInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OutputInfo -> OutputInfo -> Bool
== :: OutputInfo -> OutputInfo -> Bool
$c/= :: OutputInfo -> OutputInfo -> Bool
/= :: OutputInfo -> OutputInfo -> Bool
Eq)