Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- unzip :: Functor f => f (a, b) -> (f a, f b)
- newtype Status = Status {}
- data Diffed = Diffed {}
- newtype Diff a = Diff {}
- data DiffContext = DiffContext {}
- data Orientation
- derivationName :: StorePath -> Text
- groupByName :: Map StorePath a -> Map Text (Map StorePath a)
- buildProductName :: StorePath -> Text
- groupSetsByName :: Set StorePath -> Map Text (Set StorePath)
- readFileUtf8Lenient :: FilePath -> IO Text
- storepathParser :: Parser StorePath
- readDerivation :: StorePath -> Diff (Derivation StorePath Text)
- readInput :: StorePath -> Diff (Derivation StorePath Text)
- innerJoin :: Ord k => Map k a -> Map k b -> Map k (a, b)
- getGroupedDiff :: Ord a => [a] -> [a] -> [Item [a]]
- diffOutput :: Text -> DerivationOutput StorePath Text -> DerivationOutput StorePath Text -> Maybe OutputDiff
- diffOutputs :: Map Text (DerivationOutput StorePath Text) -> Map Text (DerivationOutput StorePath Text) -> OutputsDiff
- decomposeOn :: (Char -> Bool) -> Text -> [Text]
- lineBoundary :: Char -> Bool
- wordBoundary :: Char -> Bool
- diffText :: Text -> Text -> Diff TextDiff
- diffEnv :: OutputNames -> OutputNames -> Map Text Text -> Map Text Text -> Diff EnvironmentDiff
- diffSrcs :: Set StorePath -> Set StorePath -> Diff SourcesDiff
- diffPlatform :: Text -> Text -> Maybe (Changed Platform)
- diffBuilder :: Text -> Text -> Maybe (Changed Builder)
- diffArgs :: Vector Text -> Vector Text -> Maybe ArgumentsDiff
- diff :: Bool -> StorePath -> OutputNames -> StorePath -> OutputNames -> Diff DerivationDiff
Documentation
Instances
MonadFail Diff Source # | |
MonadIO Diff Source # | |
Applicative Diff Source # | |
Functor Diff Source # | |
Monad Diff Source # | |
MonadReader DiffContext Diff Source # | |
Defined in Nix.Diff ask :: Diff DiffContext # local :: (DiffContext -> DiffContext) -> Diff a -> Diff a # reader :: (DiffContext -> a) -> Diff a # | |
MonadState Status Diff Source # | |
data DiffContext Source #
Instances
MonadReader DiffContext Diff Source # | |
Defined in Nix.Diff ask :: Diff DiffContext # local :: (DiffContext -> DiffContext) -> Diff a -> Diff a # reader :: (DiffContext -> a) -> Diff a # |
derivationName :: StorePath -> 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
buildProductName :: StorePath -> 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 :: StorePath -> Diff (Derivation StorePath Text) Source #
Read and parse a derivation from a file
readInput :: StorePath -> Diff (Derivation StorePath 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.
getGroupedDiff :: Ord a => [a] -> [a] -> [Item [a]] Source #
:: Text | Output name |
-> DerivationOutput StorePath Text | Left derivation outputs |
-> DerivationOutput StorePath Text | Right derivation outputs |
-> Maybe OutputDiff |
Diff two outputs
:: Map Text (DerivationOutput StorePath Text) | Left derivation outputs |
-> Map Text (DerivationOutput StorePath Text) | Right derivation outputs |
-> OutputsDiff |
Diff two sets of outputs
lineBoundary :: Char -> Bool Source #
wordBoundary :: Char -> Bool Source #
:: Text | Left value to compare |
-> Text | Right value to compare |
-> Diff TextDiff | List of blocks of diffed text |
Diff two Text
values
:: OutputNames | Left derivation outputs |
-> OutputNames | Right derivation outputs |
-> Map Text Text | Left environment to compare |
-> Map Text Text | Right environment to compare |
-> Diff EnvironmentDiff |
Diff two environments
Diff input sources
:: Bool | Is this the top-level call for a comparison? If so, the diff will be more detailed. |
-> StorePath | Store path of left derivation. |
-> OutputNames | Output names of left derivation. |
-> StorePath | Store path of right derivation. |
-> OutputNames | Output names of right derivation. |
-> Diff DerivationDiff | Description of how the two derivations differ. |