nix-diff-1.0.20: Explain why two Nix derivations differ
Safe HaskellSafe-Inferred
LanguageHaskell2010

Nix.Diff

Synopsis

Documentation

newtype Status Source #

Constructors

Status 

Fields

Instances

Instances details
MonadState Status Diff Source # 
Instance details

Defined in Nix.Diff

Methods

get :: Diff Status #

put :: Status -> Diff () #

state :: (Status -> (a, Status)) -> Diff a #

data Diffed Source #

Instances

Instances details
Eq Diffed Source # 
Instance details

Defined in Nix.Diff

Methods

(==) :: Diffed -> Diffed -> Bool #

(/=) :: Diffed -> Diffed -> Bool #

Ord Diffed Source # 
Instance details

Defined in Nix.Diff

newtype Diff a Source #

Constructors

Diff 

Instances

Instances details
MonadFail Diff Source # 
Instance details

Defined in Nix.Diff

Methods

fail :: String -> Diff a #

MonadIO Diff Source # 
Instance details

Defined in Nix.Diff

Methods

liftIO :: IO a -> Diff a #

Applicative Diff Source # 
Instance details

Defined in Nix.Diff

Methods

pure :: a -> Diff a #

(<*>) :: Diff (a -> b) -> Diff a -> Diff b #

liftA2 :: (a -> b -> c) -> Diff a -> Diff b -> Diff c #

(*>) :: Diff a -> Diff b -> Diff b #

(<*) :: Diff a -> Diff b -> Diff a #

Functor Diff Source # 
Instance details

Defined in Nix.Diff

Methods

fmap :: (a -> b) -> Diff a -> Diff b #

(<$) :: a -> Diff b -> Diff a #

Monad Diff Source # 
Instance details

Defined in Nix.Diff

Methods

(>>=) :: Diff a -> (a -> Diff b) -> Diff b #

(>>) :: Diff a -> Diff b -> Diff b #

return :: a -> Diff a #

MonadReader DiffContext Diff Source # 
Instance details

Defined in Nix.Diff

Methods

ask :: Diff DiffContext #

local :: (DiffContext -> DiffContext) -> Diff a -> Diff a #

reader :: (DiffContext -> a) -> Diff a #

MonadState Status Diff Source # 
Instance details

Defined in Nix.Diff

Methods

get :: Diff Status #

put :: Status -> Diff () #

state :: (Status -> (a, Status)) -> Diff a #

data DiffContext Source #

Constructors

DiffContext 

Instances

Instances details
MonadReader DiffContext Diff Source # 
Instance details

Defined in Nix.Diff

Methods

ask :: Diff DiffContext #

local :: (DiffContext -> DiffContext) -> Diff a -> Diff a #

reader :: (DiffContext -> a) -> Diff a #

data Orientation Source #

Constructors

Character 
Word 
Line 

derivationName :: FilePath -> Text Source #

Extract the name of a derivation (i.e. the part after the hash)

This is used to guess which derivations are related to one another, even though their hash might differ

Note that this assumes that the path name is:

/nix/store/${32_CHARACTER_HASH}-${NAME}.drv

Nix technically does not require that the Nix store is actually stored underneath `nixstore`, but this is the overwhelmingly common use case

groupByName :: Map FilePath a -> Map Text (Map FilePath a) Source #

Group paths by their name

buildProductName :: FilePath -> Text Source #

Extract the name of a build product

Similar to derivationName, this assumes that the path name is:

/nix/store/${32_CHARACTER_HASH}-${NAME}.drv

readFileUtf8Lenient :: FilePath -> IO Text Source #

Read a file as utf-8 encoded string, replacing non-utf-8 characters with the unicode replacement character. This is necessary since derivations (and nix source code!) can in principle contain arbitrary bytes, but `nix-derivation` can only parse from Text.

readDerivation :: FilePath -> Diff (Derivation FilePath Text) Source #

Read and parse a derivation from a file

readInput :: FilePath -> Diff (Derivation FilePath Text) Source #

Read and parse a derivation from a store path that can be a derivation (.drv) or a realized path, in which case the corresponding derivation is queried.

innerJoin :: Ord k => Map k a -> Map k b -> Map k (a, b) Source #

Join two Maps on shared keys, discarding keys which are not present in both Maps

getGroupedDiff :: Ord a => [a] -> [a] -> [Item [a]] Source #

diffOutput Source #

Arguments

:: Text

Output name

-> DerivationOutput FilePath Text

Left derivation outputs

-> DerivationOutput FilePath Text

Right derivation outputs

-> Maybe OutputDiff 

Diff two outputs

diffOutputs Source #

Arguments

:: Map Text (DerivationOutput FilePath Text)

Left derivation outputs

-> Map Text (DerivationOutput FilePath Text)

Right derivation outputs

-> OutputsDiff 

Diff two sets of outputs

decomposeOn :: (Char -> Bool) -> Text -> [Text] Source #

Split Text into spans of Text that alternatively fail and satisfy the given predicate

The first span (if present) does not satisfy the predicate (even if the span is empty)

>>> decomposeOn (== 'b') "aabbaa"
["aa","bb","aa"]
>>> decomposeOn (== 'b') "bbaa"
["","bb","aa"]
>>> decomposeOn (== 'b') ""
[]

diffText Source #

Arguments

:: Text

Left value to compare

-> Text

Right value to compare

-> Diff TextDiff

List of blocks of diffed text

Diff two Text values

diffEnv Source #

Arguments

:: Set Text

Left derivation outputs

-> Set Text

Right derivation outputs

-> Map Text Text

Left environment to compare

-> Map Text Text

Right environment to compare

-> Diff EnvironmentDiff 

Diff two environments

diffSrcs Source #

Arguments

:: Set FilePath

Left input sources

-> Set FilePath

Right inputSources

-> Diff SourcesDiff 

Diff input sources