{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RecordWildCards #-}
module Nix.Derivation.Types
(
Derivation(..)
, DerivationOutput(..)
) where
import Control.DeepSeq (NFData)
import Data.Bifunctor (Bifunctor(bimap))
import Data.Map (Map)
import Data.Set (Set)
import Data.Vector (Vector)
import GHC.Generics (Generic)
data Derivation fp txt = Derivation
{ forall fp txt.
Derivation fp txt -> Map txt (DerivationOutput fp txt)
outputs :: Map txt (DerivationOutput fp txt)
, forall fp txt. Derivation fp txt -> Map fp (Set txt)
inputDrvs :: Map fp (Set txt)
, forall fp txt. Derivation fp txt -> Set fp
inputSrcs :: Set fp
, forall fp txt. Derivation fp txt -> txt
platform :: txt
, forall fp txt. Derivation fp txt -> txt
builder :: txt
, forall fp txt. Derivation fp txt -> Vector txt
args :: Vector txt
, forall fp txt. Derivation fp txt -> Map txt txt
env :: Map txt txt
} deriving (Derivation fp txt -> Derivation fp txt -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall fp txt.
(Eq txt, Eq fp) =>
Derivation fp txt -> Derivation fp txt -> Bool
/= :: Derivation fp txt -> Derivation fp txt -> Bool
$c/= :: forall fp txt.
(Eq txt, Eq fp) =>
Derivation fp txt -> Derivation fp txt -> Bool
== :: Derivation fp txt -> Derivation fp txt -> Bool
$c== :: forall fp txt.
(Eq txt, Eq fp) =>
Derivation fp txt -> Derivation fp txt -> Bool
Eq, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall fp txt x. Rep (Derivation fp txt) x -> Derivation fp txt
forall fp txt x. Derivation fp txt -> Rep (Derivation fp txt) x
$cto :: forall fp txt x. Rep (Derivation fp txt) x -> Derivation fp txt
$cfrom :: forall fp txt x. Derivation fp txt -> Rep (Derivation fp txt) x
Generic, Derivation fp txt -> Derivation fp txt -> Bool
Derivation fp txt -> Derivation fp txt -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {fp} {txt}. (Ord txt, Ord fp) => Eq (Derivation fp txt)
forall fp txt.
(Ord txt, Ord fp) =>
Derivation fp txt -> Derivation fp txt -> Bool
forall fp txt.
(Ord txt, Ord fp) =>
Derivation fp txt -> Derivation fp txt -> Ordering
forall fp txt.
(Ord txt, Ord fp) =>
Derivation fp txt -> Derivation fp txt -> Derivation fp txt
min :: Derivation fp txt -> Derivation fp txt -> Derivation fp txt
$cmin :: forall fp txt.
(Ord txt, Ord fp) =>
Derivation fp txt -> Derivation fp txt -> Derivation fp txt
max :: Derivation fp txt -> Derivation fp txt -> Derivation fp txt
$cmax :: forall fp txt.
(Ord txt, Ord fp) =>
Derivation fp txt -> Derivation fp txt -> Derivation fp txt
>= :: Derivation fp txt -> Derivation fp txt -> Bool
$c>= :: forall fp txt.
(Ord txt, Ord fp) =>
Derivation fp txt -> Derivation fp txt -> Bool
> :: Derivation fp txt -> Derivation fp txt -> Bool
$c> :: forall fp txt.
(Ord txt, Ord fp) =>
Derivation fp txt -> Derivation fp txt -> Bool
<= :: Derivation fp txt -> Derivation fp txt -> Bool
$c<= :: forall fp txt.
(Ord txt, Ord fp) =>
Derivation fp txt -> Derivation fp txt -> Bool
< :: Derivation fp txt -> Derivation fp txt -> Bool
$c< :: forall fp txt.
(Ord txt, Ord fp) =>
Derivation fp txt -> Derivation fp txt -> Bool
compare :: Derivation fp txt -> Derivation fp txt -> Ordering
$ccompare :: forall fp txt.
(Ord txt, Ord fp) =>
Derivation fp txt -> Derivation fp txt -> Ordering
Ord, Int -> Derivation fp txt -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall fp txt.
(Show txt, Show fp) =>
Int -> Derivation fp txt -> ShowS
forall fp txt. (Show txt, Show fp) => [Derivation fp txt] -> ShowS
forall fp txt. (Show txt, Show fp) => Derivation fp txt -> String
showList :: [Derivation fp txt] -> ShowS
$cshowList :: forall fp txt. (Show txt, Show fp) => [Derivation fp txt] -> ShowS
show :: Derivation fp txt -> String
$cshow :: forall fp txt. (Show txt, Show fp) => Derivation fp txt -> String
showsPrec :: Int -> Derivation fp txt -> ShowS
$cshowsPrec :: forall fp txt.
(Show txt, Show fp) =>
Int -> Derivation fp txt -> ShowS
Show)
instance (NFData a, NFData b) => NFData (Derivation a b)
data DerivationOutput fp txt = DerivationOutput
{ forall fp txt. DerivationOutput fp txt -> fp
path :: fp
, forall fp txt. DerivationOutput fp txt -> txt
hashAlgo :: txt
, forall fp txt. DerivationOutput fp txt -> txt
hash :: txt
} deriving (DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall fp txt.
(Eq fp, Eq txt) =>
DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
/= :: DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
$c/= :: forall fp txt.
(Eq fp, Eq txt) =>
DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
== :: DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
$c== :: forall fp txt.
(Eq fp, Eq txt) =>
DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
Eq, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall fp txt x.
Rep (DerivationOutput fp txt) x -> DerivationOutput fp txt
forall fp txt x.
DerivationOutput fp txt -> Rep (DerivationOutput fp txt) x
$cto :: forall fp txt x.
Rep (DerivationOutput fp txt) x -> DerivationOutput fp txt
$cfrom :: forall fp txt x.
DerivationOutput fp txt -> Rep (DerivationOutput fp txt) x
Generic, DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
DerivationOutput fp txt -> DerivationOutput fp txt -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {fp} {txt}.
(Ord fp, Ord txt) =>
Eq (DerivationOutput fp txt)
forall fp txt.
(Ord fp, Ord txt) =>
DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
forall fp txt.
(Ord fp, Ord txt) =>
DerivationOutput fp txt -> DerivationOutput fp txt -> Ordering
forall fp txt.
(Ord fp, Ord txt) =>
DerivationOutput fp txt
-> DerivationOutput fp txt -> DerivationOutput fp txt
min :: DerivationOutput fp txt
-> DerivationOutput fp txt -> DerivationOutput fp txt
$cmin :: forall fp txt.
(Ord fp, Ord txt) =>
DerivationOutput fp txt
-> DerivationOutput fp txt -> DerivationOutput fp txt
max :: DerivationOutput fp txt
-> DerivationOutput fp txt -> DerivationOutput fp txt
$cmax :: forall fp txt.
(Ord fp, Ord txt) =>
DerivationOutput fp txt
-> DerivationOutput fp txt -> DerivationOutput fp txt
>= :: DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
$c>= :: forall fp txt.
(Ord fp, Ord txt) =>
DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
> :: DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
$c> :: forall fp txt.
(Ord fp, Ord txt) =>
DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
<= :: DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
$c<= :: forall fp txt.
(Ord fp, Ord txt) =>
DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
< :: DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
$c< :: forall fp txt.
(Ord fp, Ord txt) =>
DerivationOutput fp txt -> DerivationOutput fp txt -> Bool
compare :: DerivationOutput fp txt -> DerivationOutput fp txt -> Ordering
$ccompare :: forall fp txt.
(Ord fp, Ord txt) =>
DerivationOutput fp txt -> DerivationOutput fp txt -> Ordering
Ord, Int -> DerivationOutput fp txt -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall fp txt.
(Show fp, Show txt) =>
Int -> DerivationOutput fp txt -> ShowS
forall fp txt.
(Show fp, Show txt) =>
[DerivationOutput fp txt] -> ShowS
forall fp txt.
(Show fp, Show txt) =>
DerivationOutput fp txt -> String
showList :: [DerivationOutput fp txt] -> ShowS
$cshowList :: forall fp txt.
(Show fp, Show txt) =>
[DerivationOutput fp txt] -> ShowS
show :: DerivationOutput fp txt -> String
$cshow :: forall fp txt.
(Show fp, Show txt) =>
DerivationOutput fp txt -> String
showsPrec :: Int -> DerivationOutput fp txt -> ShowS
$cshowsPrec :: forall fp txt.
(Show fp, Show txt) =>
Int -> DerivationOutput fp txt -> ShowS
Show)
instance (NFData a, NFData b) => NFData (DerivationOutput a b)
instance Functor (DerivationOutput fp) where
fmap :: forall a b.
(a -> b) -> DerivationOutput fp a -> DerivationOutput fp b
fmap a -> b
f DerivationOutput{fp
a
hash :: a
hashAlgo :: a
path :: fp
hash :: forall fp txt. DerivationOutput fp txt -> txt
hashAlgo :: forall fp txt. DerivationOutput fp txt -> txt
path :: forall fp txt. DerivationOutput fp txt -> fp
..} = DerivationOutput
{ path :: fp
path = fp
path
, hashAlgo :: b
hashAlgo = a -> b
f a
hashAlgo
, hash :: b
hash = a -> b
f a
hash
}
instance Bifunctor DerivationOutput where
bimap :: forall a b c d.
(a -> b)
-> (c -> d) -> DerivationOutput a c -> DerivationOutput b d
bimap a -> b
f c -> d
g DerivationOutput{a
c
hash :: c
hashAlgo :: c
path :: a
hash :: forall fp txt. DerivationOutput fp txt -> txt
hashAlgo :: forall fp txt. DerivationOutput fp txt -> txt
path :: forall fp txt. DerivationOutput fp txt -> fp
..} = DerivationOutput
{ path :: b
path = a -> b
f a
path
, hashAlgo :: d
hashAlgo = c -> d
g c
hashAlgo
, hash :: d
hash = c -> d
g c
hash
}