Safe Haskell | None |
---|---|
Language | Haskell2010 |
Wraps the expression submodules.
- data NExprF r
- = NConstant !NAtom
- | NStr !(NString r)
- | NSym !Text
- | NList ![r]
- | NSet ![Binding r]
- | NRecSet ![Binding r]
- | NLiteralPath !FilePath
- | NEnvPath !FilePath
- | NUnary !NUnaryOp !r
- | NBinary !NBinaryOp !r !r
- | NSelect !r !(NAttrPath r) !(Maybe r)
- | NHasAttr !r !(NAttrPath r)
- | NAbs !(Params r) !r
- | NApp !r !r
- | NLet ![Binding r] !r
- | NIf !r !r !r
- | NWith !r !r
- | NAssert !r !r
- type NExpr = Fix NExprF
- data Binding r
- data Params r
- data ParamSet r
- = FixedParamSet !(Map Text (Maybe r))
- | VariadicParamSet !(Map Text (Maybe r))
- data Antiquoted v r
- = Plain !v
- | Antiquoted !r
- data NString r
- = DoubleQuoted ![Antiquoted Text r]
- | Indented ![Antiquoted Text r]
- data NKeyName r
- = DynamicKey !(Antiquoted (NString r) r)
- | StaticKey !Text
- type NAttrPath r = [NKeyName r]
- data NUnaryOp
- data NBinaryOp
- paramName :: Params r -> Maybe Text
- data SrcSpan = SrcSpan {}
- data Ann ann a = Ann {
- annotation :: ann
- annotated :: a
- type AnnF ann f = Compose (Ann ann) f
- annToAnnF :: Ann ann (f (Fix (AnnF ann f))) -> Fix (AnnF ann f)
- type NExprLocF = AnnF SrcSpan NExprF
- type NExprLoc = Fix NExprLocF
- pattern AnnE :: forall t t1. t1 -> t (Fix (Compose * * (Ann t1) t)) -> Fix (Compose * * (Ann t1) t)
- stripAnnotation :: Functor f => Fix (AnnF ann f) -> Fix f
- nApp :: NExprLoc -> NExprLoc -> NExprLoc
- nUnary :: Ann SrcSpan NUnaryOp -> NExprLoc -> NExprLoc
- nBinary :: Ann SrcSpan NBinaryOp -> NExprLoc -> NExprLoc -> NExprLoc
- nSelectLoc :: NExprLoc -> Ann SrcSpan (NAttrPath NExprLoc) -> Maybe NExprLoc -> NExprLoc
- nHasAttr :: NExprLoc -> Ann SrcSpan (NAttrPath NExprLoc) -> NExprLoc
- nAbs :: Ann SrcSpan (Params NExprLoc) -> NExprLoc -> NExprLoc
- nStr :: Ann SrcSpan (NString NExprLoc) -> NExprLoc
- data Delta :: *
- mkInt :: Integer -> NExpr
- mkIntF :: Integer -> NExprF a
- mkStr :: Text -> NExpr
- mkIndentedStr :: Text -> NExpr
- mkUri :: Text -> NExpr
- mkUriF :: Text -> NExprF a
- mkPath :: Bool -> FilePath -> NExpr
- mkPathF :: Bool -> FilePath -> NExprF a
- mkEnvPath :: FilePath -> NExpr
- mkEnvPathF :: FilePath -> NExprF a
- mkRelPath :: FilePath -> NExpr
- mkRelPathF :: FilePath -> NExprF a
- mkSym :: Text -> NExpr
- mkSymF :: Text -> NExprF a
- mkSelector :: Text -> NAttrPath NExpr
- mkBool :: Bool -> NExpr
- mkBoolF :: Bool -> NExprF a
- mkNull :: NExpr
- mkNullF :: NExprF a
- mkOper :: NUnaryOp -> NExpr -> NExpr
- mkOper2 :: NBinaryOp -> NExpr -> NExpr -> NExpr
- mkParamset :: [(Text, Maybe NExpr)] -> Params NExpr
- mkFixedParamSet :: [(Text, Maybe NExpr)] -> ParamSet NExpr
- mkVariadicParamSet :: [(Text, Maybe NExpr)] -> ParamSet NExpr
- mkApp :: NExpr -> NExpr -> NExpr
- mkRecSet :: [Binding NExpr] -> NExpr
- mkNonRecSet :: [Binding NExpr] -> NExpr
- mkLets :: [Binding NExpr] -> NExpr -> NExpr
- mkList :: [NExpr] -> NExpr
- mkWith :: NExpr -> NExpr -> NExpr
- mkAssert :: NExpr -> NExpr -> NExpr
- mkIf :: NExpr -> NExpr -> NExpr -> NExpr
- mkFunction :: Params NExpr -> NExpr -> NExpr
- mkDot :: NExpr -> Text -> NExpr
- mkDots :: NExpr -> [Text] -> NExpr
- inherit :: [NKeyName e] -> Binding e
- inheritFrom :: e -> [NKeyName e] -> Binding e
- bindTo :: Text -> NExpr -> Binding NExpr
- ($=) :: Text -> NExpr -> Binding NExpr
- appendBindings :: [Binding NExpr] -> NExpr -> NExpr
- modifyFunctionBody :: (NExpr -> NExpr) -> NExpr -> NExpr
- letsE :: [(Text, NExpr)] -> NExpr -> NExpr
- letE :: Text -> NExpr -> NExpr -> NExpr
- attrsE :: [(Text, NExpr)] -> NExpr
- recAttrsE :: [(Text, NExpr)] -> NExpr
- mkNot :: NExpr -> NExpr
- (!.) :: NExpr -> Text -> NExpr
- mkBinop :: NBinaryOp -> NExpr -> NExpr -> NExpr
- ($==) :: NExpr -> NExpr -> NExpr
- ($!=) :: NExpr -> NExpr -> NExpr
- ($<) :: NExpr -> NExpr -> NExpr
- ($<=) :: NExpr -> NExpr -> NExpr
- ($>) :: NExpr -> NExpr -> NExpr
- ($>=) :: NExpr -> NExpr -> NExpr
- ($&&) :: NExpr -> NExpr -> NExpr
- ($||) :: NExpr -> NExpr -> NExpr
- ($->) :: NExpr -> NExpr -> NExpr
- ($//) :: NExpr -> NExpr -> NExpr
- ($+) :: NExpr -> NExpr -> NExpr
- ($-) :: NExpr -> NExpr -> NExpr
- ($*) :: NExpr -> NExpr -> NExpr
- ($/) :: NExpr -> NExpr -> NExpr
- ($++) :: NExpr -> NExpr -> NExpr
- (@@) :: NExpr -> NExpr -> NExpr
- (==>) :: Params NExpr -> NExpr -> NExpr
Documentation
The main nix expression type. This is polymorphic so that it can be made
a functor, which allows us to traverse expressions and map functions over
them. The actual NExpr
type is a fixed point of this functor, defined
below.
NConstant !NAtom | Constants: ints, bools, URIs, and null. |
NStr !(NString r) | A string, with interpolated expressions. |
NSym !Text | A variable. For example, in the expression |
NList ![r] | A list literal. |
NSet ![Binding r] | An attribute set literal, not recursive. |
NRecSet ![Binding r] | An attribute set literal, recursive. |
NLiteralPath !FilePath | A path expression, which is evaluated to a store path. The path here can be relative, in which case it's evaluated relative to the file in which it appears. |
NEnvPath !FilePath | A path which refers to something in the Nix search path (the NIX_PATH
environment variable. For example, |
NUnary !NUnaryOp !r | Application of a unary operator to an expression. |
NBinary !NBinaryOp !r !r | Application of a binary operator to two expressions. |
NSelect !r !(NAttrPath r) !(Maybe r) | Dot-reference into an attribute set, optionally providing an alternative if the key doesn't exist. |
NHasAttr !r !(NAttrPath r) | Ask if a set contains a given attribute path. |
NAbs !(Params r) !r | A function literal (lambda abstraction). |
NApp !r !r | Apply a function to an argument. |
NLet ![Binding r] !r | Evaluate the second argument after introducing the bindings. |
NIf !r !r !r | If-then-else statement. |
NWith !r !r | Evaluate an attribute set, bring its bindings into scope, and evaluate the second argument. |
NAssert !r !r | Assert that the first returns true before evaluating the second. |
Functor NExprF Source # | |
IsString NExpr Source # | We make an |
Foldable NExprF Source # | |
Traversable NExprF Source # | |
Show1 NExprF Source # | |
Eq r => Eq (NExprF r) Source # | |
Data r => Data (NExprF r) Source # | |
Ord r => Ord (NExprF r) Source # | |
Show r => Show (NExprF r) Source # | |
Generic (NExprF r) Source # | |
type Rep (NExprF r) Source # | |
type NExpr = Fix NExprF Source #
The monomorphic expression type is a fixed point of the polymorphic one.
A single line of the bindings section of a let expression or of a set.
Params
represents all the ways the formal parameters to a
function can be represented.
Param !Text | For functions with a single named argument, such as |
ParamSet !(ParamSet r) !(Maybe Text) | Explicit parameters (argument must be a set). Might specify a name to bind to the set in the function body. |
Functor Params Source # | |
Foldable Params Source # | |
Traversable Params Source # | |
Show1 Params Source # | |
Eq r => Eq (Params r) Source # | |
Data r => Data (Params r) Source # | |
Ord r => Ord (Params r) Source # | |
Show r => Show (Params r) Source # | |
IsString (Params r) Source # | |
Generic (Params r) Source # | |
type Rep (Params r) Source # | |
An explicit parameter set; provides a shorthand for unpacking arguments.
FixedParamSet !(Map Text (Maybe r)) | A fixed set, where no arguments beyond what is specified in the map may be given. The map might contain defaults for arguments not passed. |
VariadicParamSet !(Map Text (Maybe r)) | Same as the |
Functor ParamSet Source # | |
Foldable ParamSet Source # | |
Traversable ParamSet Source # | |
Show1 ParamSet Source # | |
Eq r => Eq (ParamSet r) Source # | |
Data r => Data (ParamSet r) Source # | |
Ord r => Ord (ParamSet r) Source # | |
Show r => Show (ParamSet r) Source # | |
Generic (ParamSet r) Source # | |
type Rep (ParamSet r) Source # | |
data Antiquoted v r Source #
Antiquoted
represents an expression that is either
antiquoted (surrounded by ${...}) or plain (not antiquoted).
Plain !v | |
Antiquoted !r |
Show2 Antiquoted Source # | |
Functor (Antiquoted v) Source # | |
Foldable (Antiquoted v) Source # | |
Traversable (Antiquoted v) Source # | |
Show v0 => Show1 (Antiquoted v0) Source # | |
(Eq v, Eq r) => Eq (Antiquoted v r) Source # | |
(Data v, Data r) => Data (Antiquoted v r) Source # | |
(Ord v, Ord r) => Ord (Antiquoted v r) Source # | |
(Show v, Show r) => Show (Antiquoted v r) Source # | |
Generic (Antiquoted v r) Source # | |
type Rep (Antiquoted v r) Source # | |
An NString
is a list of things that are either a plain string
or an antiquoted expression. After the antiquotes have been evaluated,
the final string is constructed by concating all the parts.
DoubleQuoted ![Antiquoted Text r] | Strings wrapped with double-quotes (") are not allowed to contain literal newline characters. |
Indented ![Antiquoted Text r] | Strings wrapped with two single quotes ('') can contain newlines, and their indentation will be stripped. |
Functor NString Source # | |
Foldable NString Source # | |
Traversable NString Source # | |
Show1 NString Source # | |
Eq r => Eq (NString r) Source # | |
Data r => Data (NString r) Source # | |
Ord r => Ord (NString r) Source # | |
Show r => Show (NString r) Source # | |
IsString (NString r) Source # | For the the |
Generic (NString r) Source # | |
type Rep (NString r) Source # | |
A KeyName
is something that can appear at the right side of an
equals sign. For example, a
is a KeyName
in { a = 3; }
, let a = 3;
in ...
, {}.a
or {} ? a
.
Nix supports both static keynames (just an identifier) and dynamic
identifiers. Dynamic identifiers can be either a string (e.g.:
{ "a" = 3; }
) or an antiquotation (e.g.: let a = "example";
in { ${a} = 3; }.example
).
Note: There are some places where a dynamic keyname is not allowed. In particular, those include:
- The RHS of a
binding
insidelet
:let ${"a"} = 3; in ...
produces a syntax error. - The attribute names of an
inherit
:inherit ${"a"};
is forbidden.
Note: In Nix, a simple string without antiquotes such as "foo"
is
allowed even if the context requires a static keyname, but the
parser still considers it a DynamicKey
for simplicity.
DynamicKey !(Antiquoted (NString r) r) | |
StaticKey !Text |
Functor NKeyName Source # | |
Foldable NKeyName Source # | |
Traversable NKeyName Source # | |
Show1 NKeyName Source # | |
Eq r => Eq (NKeyName r) Source # | |
Data r => Data (NKeyName r) Source # | |
Ord r => Ord (NKeyName r) Source # | |
Show r => Show (NKeyName r) Source # | |
IsString (NKeyName r) Source # | Most key names are just static text, so this instance is convenient. |
Generic (NKeyName r) Source # | |
type Rep (NKeyName r) Source # | |
type NAttrPath r = [NKeyName r] Source #
A selector (for example in a let
or an attribute set) is made up
of strung-together key names.
There are two unary operations: logical not and integer negation.
Binary operators expressible in the nix language.
NEq | Equality (==) |
NNEq | Inequality (!=) |
NLt | Less than (<) |
NLte | Less than or equal (<=) |
NGt | Greater than (>) |
NGte | Greater than or equal (>=) |
NAnd | Logical and (&&) |
NOr | Logical or (||) |
NImpl | Logical implication (->) |
NUpdate | Joining two attribut sets (//) |
NPlus | Addition (+) |
NMinus | Subtraction (-) |
NMult | Multiplication (*) |
NDiv | Division (/) |
NConcat | List concatenation (++) |
paramName :: Params r -> Maybe Text Source #
Get the name out of the parameter (there might be none).
A location in a source file
A type constructor applied to a type along with an annotation
Intended to be used with Fix
:
type MyType = Fix (Compose (Ann Annotation) F)
Ann | |
|
Functor (Ann ann) Source # | |
Foldable (Ann ann) Source # | |
Traversable (Ann ann) Source # | |
Show ann0 => Show1 (Ann ann0) Source # | |
(Eq ann, Eq a) => Eq (Ann ann a) Source # | |
(Data ann, Data a) => Data (Ann ann a) Source # | |
(Ord ann, Ord a) => Ord (Ann ann a) Source # | |
(Read ann, Read a) => Read (Ann ann a) Source # | |
(Show ann, Show a) => Show (Ann ann a) Source # | |
Generic (Ann ann a) Source # | |
type Rep (Ann ann a) Source # | |
pattern AnnE :: forall t t1. t1 -> t (Fix (Compose * * (Ann t1) t)) -> Fix (Compose * * (Ann t1) t) Source #
mkIndentedStr :: Text -> NExpr Source #
Make an indented string.
mkEnvPath :: FilePath -> NExpr Source #
Make a path expression which pulls from the NIX_PATH env variable.
mkEnvPathF :: FilePath -> NExprF a Source #
mkRelPathF :: FilePath -> NExprF a Source #
inheritFrom :: e -> [NKeyName e] -> 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.
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`.