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

Nix.Expr.Shorthands

Description

Shorthands for making Nix expressions.

Functions with an F suffix return a more general type (base functor F a) without the outer Fix wrapper that creates a.

Synopsis

Basic expression builders

mkConst :: NAtom -> NExpr Source #

Put NAtom as expression

mkNull :: NExpr Source #

Put null.

mkBool :: Bool -> NExpr Source #

Put boolean.

mkInt :: Integer -> NExpr Source #

Put integer.

mkFloat :: Float -> NExpr Source #

Put floating point number.

mkStr :: Text -> NExpr Source #

Put a regular (double-quoted) string.

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

Put an indented string.

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

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

mkEnvPath :: FilePath -> NExpr Source #

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

mkRelPath :: FilePath -> NExpr Source #

Put a path which references a relative path.

mkSym :: Text -> NExpr Source #

Put a variable (symbol).

mkSynHole :: Text -> NExpr Source #

Put syntactic hole.

mkOp :: NUnaryOp -> NExpr -> NExpr Source #

Put an unary operator. @since 0.15.0

mkNot :: NExpr -> NExpr Source #

Logical negation: not.

mkNeg :: NExpr -> NExpr Source #

Number negation: -.

Negation in the language works with integers and floating point. @since 0.15.0

mkOp2 :: NBinaryOp -> NExpr -> NExpr -> NExpr Source #

Put a binary operator. @since 0.15.0

mkParamSet :: [(Text, Maybe NExpr)] -> Params NExpr Source #

{ x }

Since: 0.15.0

mkVariadicParamSet :: [(Text, Maybe NExpr)] -> Params NExpr Source #

{ x, ... }

Since: 0.15.0

mkNamedParamSet :: Text -> [(Text, Maybe NExpr)] -> Params NExpr Source #

s@{ x }

Since: 0.15.0

mkNamedVariadicParamSet :: Text -> [(Text, Maybe NExpr)] -> Params NExpr Source #

s@{ x, ... }

Since: 0.15.0

mkGeneralParamSet :: Maybe Text -> [(Text, Maybe NExpr)] -> Bool -> Params NExpr Source #

Args:

  1. Maybe name:
Nothing  ->   {}
Just "s" -> s@{}
  1. key:expr pairs
  2. Is variadic or not:
True  -> {...}
False -> {}

Since: 0.15.0

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

rec { .. }

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

Put a non-recursive set.

{ .. }

mkSet :: Recursivity -> [Binding NExpr] -> NExpr Source #

General set builder function.

emptySet :: NExpr Source #

Empty set.

Monoid. Use // operation (shorthand $//) to extend the set. @since 0.15.0

mkList :: [NExpr] -> NExpr Source #

Put a list.

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

Wrap in a let.

(Evaluate the second argument after introducing the bindings.)

HaskellNix
mkLets bindings expr let bindings; in expr

mkWith :: NExpr -> NExpr -> NExpr Source #

Create a whith: 1st expr - what to bring into the scope. 2nd - expression that recieves the scope extention.

HaskellNix
mkWith body mainwith body; expr

mkAssert :: NExpr -> NExpr -> NExpr Source #

Create an assert: 1st expr - asserting itself, must return true. 2nd - main expression to evaluated after assertion.

HaskellNix
mkAssert check evalassert check; eval

mkIf :: NExpr -> NExpr -> NExpr -> NExpr Source #

Put:

if expr1
  then expr2
  else expr3

mkFunction :: Params NExpr -> NExpr -> NExpr Source #

Lambda function, analog of Haskell's \ x -> x:

HaskellNix
mkFunction x expr x: expr

getRefOrDefault :: Maybe NExpr -> NExpr -> Text -> NExpr Source #

General dot-reference with optional alternative if the jey does not exist. @since 0.15.0

Base functor builders for basic expressions builders *sic

mkNullF :: NExprF a Source #

Unfixed mkNull.

mkBoolF :: Bool -> NExprF a Source #

Unfixed mkBool.

mkIntF :: Integer -> NExprF a Source #

Unfixed mkInt.

mkFloatF :: Float -> NExprF a Source #

Unfixed mkFloat.

mkPathF :: Bool -> FilePath -> NExprF a Source #

Unfixed mkPath.

mkEnvPathF :: FilePath -> NExprF a Source #

Unfixed mkEnvPath.

mkRelPathF :: FilePath -> NExprF a Source #

Unfixed mkRelPath.

mkSymF :: Text -> NExprF a Source #

Unfixed mkSym.

mkSynHoleF :: Text -> NExprF a Source #

Unfixed mkSynHole.

Other

inheritFrom :: e -> [VarName] -> Binding e Source #

An inherit clause with an expression to pull from.

HaskNixpseudocode
inheritFrom x [a, b] inherit (x) a b; a = x.a; b = x.b;

inherit :: [VarName] -> Binding e Source #

An inherit clause without an expression to pull from.

HaskNixpseudocode
inheritFrom [a, b] inherit a b; a = outside.a; b = outside.b;

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

Nix = (bind operator).

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

Shorthand for producing a binding of a name to an expression: Nix's =.

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 a non-recursive attribute set.

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

Make a recursive attribute set.

Nix binary operators

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

Function application (' ' in f x)

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

Equality: ==

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

Inequality: !=

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

Less than: <

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

Less than OR equal: <=

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

Greater than: >

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

Greater than OR equal: >=

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

AND: &&

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

OR: ||

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

Logical implication: ->

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

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

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

Addition: +

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

Subtraction: -

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

Multiplication: *

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

Division: /

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

List concatenation: ++

(@.) :: NExpr -> Text -> NExpr infix 9 Source #

Dot-reference into an attribute set: attrSet.k

(@.<|>) :: NExpr -> Text -> NExpr -> NExpr infix 9 Source #

Dot-reference into an attribute set with alternative if the key does not exist.

s.x or y

Since: 0.15.0

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

Lambda function, analog of Haskell's \ x -> x:

HaskellNix
x ==> expr x: expr

Under deprecation

mkOper :: NUnaryOp -> NExpr -> NExpr Source #

Deprecated: Please, use mkOp Put an unary operator.

mkOper2 :: NBinaryOp -> NExpr -> NExpr -> NExpr Source #

Deprecated: Please, use mkOp2 | Put a binary operator.

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

Deprecated: Please, use mkOp2 | Nix binary operator builder.

mkParamset :: [(Text, Maybe NExpr)] -> Bool -> Params NExpr Source #

Deprecated: Please, use: * mkParamSet is for closed sets; * mkVariadicSet is for variadic; * mkGeneralParamSet a general constructor.