{-# LANGUAGE DeriveGeneric     #-}
{-# LANGUAGE DeriveAnyClass    #-}


module Nix.NarInfo.Types
    ( -- * Types
      NarInfo(..)
    , SimpleNarInfo
    ) where

import Data.Set (Set)
import Data.Text (Text)
import GHC.Generics

-- NarInfo URL includes storePath hash and .narinfo suffix
-- Note: storePath is with prefix but references are shortRefs (without /nix/store prefix)
--
-- Both `parseNarInfoWith` and `buildNarInfoWith` need
-- a path parser/printer which takes an argument
-- whether the path is prefixed or not.
--
data NarInfo fp txt hash = NarInfo
  { -- | Absolute path of the derivation in nix store.
    forall fp txt hash. NarInfo fp txt hash -> fp
storePath   :: fp
  , -- | Relative url (to current domain) to download nar file.
    forall fp txt hash. NarInfo fp txt hash -> txt
url         :: txt
  , -- | Name of the compression algorithm, eg. xz.
    forall fp txt hash. NarInfo fp txt hash -> txt
compression :: txt
  , -- | Hash of the compressed nar file.
    -- NOTE: to compute use "nix-hash --type sha256 --flat"
    -- (srk) this isn't fixed to sha256 but a prefix indicates the type e.g.: sha256:1a6lzf...
    -- default is sha256 thought
    forall fp txt hash. NarInfo fp txt hash -> hash
fileHash    :: hash
  , -- | File size of compressed nar file.
    -- NOTE: du -b
    forall fp txt hash. NarInfo fp txt hash -> Integer
fileSize    :: Integer
  , -- | Hash of the decompressed nar file.
    -- NOTE: to compute use "nix-hash --type sha256 --flat --base32"
    -- (srk) this isn't fixed to sha256 but a prefix indicates the type e.g.: sha256:1a6lzf...
    -- default is sha256 thought
    forall fp txt hash. NarInfo fp txt hash -> hash
narHash     :: hash
  , -- | File size of decompressed nar file.
    -- NOTE: du -b
    forall fp txt hash. NarInfo fp txt hash -> Integer
narSize     :: Integer
  , -- | Immediate dependencies of the storePath.
    -- NOTE: nix-store -q --references
    forall fp txt hash. NarInfo fp txt hash -> Set fp
references  :: Set fp
  , -- | Relative store path (to nix store root) of the deriver.
    -- NOTE: nix-store -q --deriver
    forall fp txt hash. NarInfo fp txt hash -> Maybe txt
deriver     :: Maybe txt
  , -- | System
    forall fp txt hash. NarInfo fp txt hash -> Maybe txt
system      :: Maybe txt
  , -- | Signature of fields: storePath, narHash, narSize, refs.
    forall fp txt hash. NarInfo fp txt hash -> Maybe txt
sig         :: Maybe txt
  , -- | Content-addressed
    -- Store path is computed from a cryptographic hash
    -- of the contents of the path, plus some other bits of data like
    -- the "name" part of the path.
    forall fp txt hash. NarInfo fp txt hash -> Maybe txt
ca          :: Maybe txt
  }
  deriving (NarInfo fp txt hash -> NarInfo fp txt hash -> Bool
(NarInfo fp txt hash -> NarInfo fp txt hash -> Bool)
-> (NarInfo fp txt hash -> NarInfo fp txt hash -> Bool)
-> Eq (NarInfo fp txt hash)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall fp txt hash.
(Eq fp, Eq txt, Eq hash) =>
NarInfo fp txt hash -> NarInfo fp txt hash -> Bool
$c== :: forall fp txt hash.
(Eq fp, Eq txt, Eq hash) =>
NarInfo fp txt hash -> NarInfo fp txt hash -> Bool
== :: NarInfo fp txt hash -> NarInfo fp txt hash -> Bool
$c/= :: forall fp txt hash.
(Eq fp, Eq txt, Eq hash) =>
NarInfo fp txt hash -> NarInfo fp txt hash -> Bool
/= :: NarInfo fp txt hash -> NarInfo fp txt hash -> Bool
Eq, (forall x. NarInfo fp txt hash -> Rep (NarInfo fp txt hash) x)
-> (forall x. Rep (NarInfo fp txt hash) x -> NarInfo fp txt hash)
-> Generic (NarInfo fp txt hash)
forall x. Rep (NarInfo fp txt hash) x -> NarInfo fp txt hash
forall x. NarInfo fp txt hash -> Rep (NarInfo fp txt hash) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall fp txt hash x.
Rep (NarInfo fp txt hash) x -> NarInfo fp txt hash
forall fp txt hash x.
NarInfo fp txt hash -> Rep (NarInfo fp txt hash) x
$cfrom :: forall fp txt hash x.
NarInfo fp txt hash -> Rep (NarInfo fp txt hash) x
from :: forall x. NarInfo fp txt hash -> Rep (NarInfo fp txt hash) x
$cto :: forall fp txt hash x.
Rep (NarInfo fp txt hash) x -> NarInfo fp txt hash
to :: forall x. Rep (NarInfo fp txt hash) x -> NarInfo fp txt hash
Generic, Int -> NarInfo fp txt hash -> ShowS
[NarInfo fp txt hash] -> ShowS
NarInfo fp txt hash -> String
(Int -> NarInfo fp txt hash -> ShowS)
-> (NarInfo fp txt hash -> String)
-> ([NarInfo fp txt hash] -> ShowS)
-> Show (NarInfo fp txt hash)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall fp txt hash.
(Show fp, Show txt, Show hash) =>
Int -> NarInfo fp txt hash -> ShowS
forall fp txt hash.
(Show fp, Show txt, Show hash) =>
[NarInfo fp txt hash] -> ShowS
forall fp txt hash.
(Show fp, Show txt, Show hash) =>
NarInfo fp txt hash -> String
$cshowsPrec :: forall fp txt hash.
(Show fp, Show txt, Show hash) =>
Int -> NarInfo fp txt hash -> ShowS
showsPrec :: Int -> NarInfo fp txt hash -> ShowS
$cshow :: forall fp txt hash.
(Show fp, Show txt, Show hash) =>
NarInfo fp txt hash -> String
show :: NarInfo fp txt hash -> String
$cshowList :: forall fp txt hash.
(Show fp, Show txt, Show hash) =>
[NarInfo fp txt hash] -> ShowS
showList :: [NarInfo fp txt hash] -> ShowS
Show)

type SimpleNarInfo = NarInfo FilePath Text Text