hnix-0.14.0.1: Haskell implementation of the Nix language
Safe HaskellNone
LanguageHaskell2010

Nix.Expr.Shorthands

Description

A bunch of shorthands for making nix expressions.

Functions with an F suffix return a more general type without the outer Fix wrapper.

Synopsis

Documentation

mkInt :: Integer -> NExpr Source #

Make an integer literal expression.

mkFloat :: Float -> NExpr Source #

Make an floating point literal expression.

mkStr :: Text -> NExpr Source #

Make a regular (double-quoted) string.

mkIndentedStr :: Int -> Text -> NExpr Source #

Make an indented string.

mkPath :: Bool -> FilePath -> NExpr Source #

Make a path. Use True if the path should be read from the environment, else False.

mkEnvPath :: FilePath -> NExpr Source #

Make a path expression which pulls from the NIX_PATH env variable.

mkRelPath :: FilePath -> NExpr Source #

Make a path expression which references a relative path.

mkSym :: Text -> NExpr Source #

Make a variable (symbol)

inherit :: [NKeyName e] -> SourcePos -> Binding e Source #

An inherit clause without an expression to pull from.

inheritFrom :: e -> [NKeyName e] -> SourcePos -> Binding e Source #

An inherit clause with an expression to pull from.

bindTo :: Text -> NExpr -> Binding NExpr Source #

Shorthand for producing a binding of a name to an expression: @=

($=) :: Text -> NExpr -> Binding NExpr infixr 2 Source #

Infix version of bindTo: =

appendBindings :: [Binding NExpr] -> NExpr -> NExpr Source #

Append a list of bindings to a set or let expression. For example, adding `[a = 1, b = 2]` to `let c = 3; in 4` produces `let a = 1; b = 2; c = 3; in 4`.

modifyFunctionBody :: (NExpr -> NExpr) -> NExpr -> NExpr Source #

Applies a transformation to the body of a nix function.

letsE :: [(Text, NExpr)] -> NExpr -> NExpr Source #

A let statement with multiple assignments.

letE :: Text -> NExpr -> NExpr -> NExpr Source #

Wrapper for a single-variable let.

attrsE :: [(Text, NExpr)] -> NExpr Source #

Make an attribute set (non-recursive).

recAttrsE :: [(Text, NExpr)] -> NExpr Source #

Make an attribute set (recursive).

mkNot :: NExpr -> NExpr Source #

Logical negation.

Nix binary operators

mkBinop :: NBinaryOp -> NExpr -> NExpr -> NExpr Source #

Nix binary operator builder.

(@@) :: NExpr -> NExpr -> NExpr infixl 1 Source #

Function application (' ' in f x)

($==) :: NExpr -> NExpr -> NExpr Source #

Equality: ==

($!=) :: NExpr -> NExpr -> NExpr Source #

Inequality: !=

($<) :: NExpr -> NExpr -> NExpr Source #

Less than: <

($<=) :: NExpr -> NExpr -> NExpr Source #

Less than OR equal: <=

($>) :: NExpr -> NExpr -> NExpr Source #

Greater than: >

($>=) :: NExpr -> NExpr -> NExpr Source #

Greater than OR equal: >=

($&&) :: NExpr -> NExpr -> NExpr Source #

AND: &&

($||) :: NExpr -> NExpr -> NExpr Source #

OR: ||

($->) :: NExpr -> NExpr -> NExpr Source #

Logical implication: ->

($//) :: NExpr -> NExpr -> NExpr Source #

Extendoverride the left attr set, with the right one: @/@

($+) :: NExpr -> NExpr -> NExpr Source #

Addition: +

($-) :: NExpr -> NExpr -> NExpr Source #

Subtraction: -

($*) :: NExpr -> NExpr -> NExpr Source #

Multiplication: *

($/) :: NExpr -> NExpr -> NExpr Source #

Division: /

($++) :: NExpr -> NExpr -> NExpr Source #

List concatenation: ++

(==>) :: Params NExpr -> NExpr -> NExpr infixr 1 Source #

Lambda function. > x ==> x Haskell: > \ x -> x Nix: > x: x

(@.) :: NExpr -> Text -> NExpr infixl 2 Source #

Dot-reference into an attribute set: attrSet.k