Safe Haskell | None |
---|---|
Language | Haskell2010 |
The nix expression type and supporting types.
Synopsis
- type VarName = Text
- hashAt :: VarName -> Lens' (AttrSet v) (Maybe v)
- data NExprF r
- = NConstant !NAtom
- | NStr !(NString r)
- | NSym !VarName
- | NList ![r]
- | NSet !NRecordType ![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
- | NLet ![Binding r] !r
- | NIf !r !r !r
- | NWith !r !r
- | NAssert !r !r
- | NSynHole !VarName
- type NExpr = Fix NExprF
- data Binding r
- data Params r
- type ParamSet r = [(VarName, Maybe r)]
- data Antiquoted (v :: *) (r :: *)
- = Plain !v
- | EscapedNewline
- | Antiquoted !r
- data NString r
- = DoubleQuoted ![Antiquoted Text r]
- | Indented !Int ![Antiquoted Text r]
- data NKeyName r
- = DynamicKey !(Antiquoted (NString r) r)
- | StaticKey !VarName
- type NAttrPath r = NonEmpty (NKeyName r)
- data NUnaryOp
- data NBinaryOp
- data NRecordType
- paramName :: Params r -> Maybe VarName
- _NSynHole :: Applicative f => (VarName -> f VarName) -> NExprF r -> f (NExprF r)
- _NAssert :: Applicative f => ((r, r) -> f (r, r)) -> NExprF r -> f (NExprF r)
- _NWith :: Applicative f => ((r, r) -> f (r, r)) -> NExprF r -> f (NExprF r)
- _NIf :: Applicative f => ((r, r, r) -> f (r, r, r)) -> NExprF r -> f (NExprF r)
- _NLet :: Applicative f => (([Binding r], r) -> f ([Binding r], r)) -> NExprF r -> f (NExprF r)
- _NAbs :: Applicative f => ((Params r, r) -> f (Params r, r)) -> NExprF r -> f (NExprF r)
- _NHasAttr :: Applicative f => ((r, NAttrPath r) -> f (r, NAttrPath r)) -> NExprF r -> f (NExprF r)
- _NSelect :: Applicative f => ((r, NAttrPath r, Maybe r) -> f (r, NAttrPath r, Maybe r)) -> NExprF r -> f (NExprF r)
- _NBinary :: Applicative f => ((NBinaryOp, r, r) -> f (NBinaryOp, r, r)) -> NExprF r -> f (NExprF r)
- _NUnary :: Applicative f => ((NUnaryOp, r) -> f (NUnaryOp, r)) -> NExprF r -> f (NExprF r)
- _NEnvPath :: Applicative f => (FilePath -> f FilePath) -> NExprF r -> f (NExprF r)
- _NLiteralPath :: Applicative f => (FilePath -> f FilePath) -> NExprF r -> f (NExprF r)
- _NSet :: Applicative f => ((NRecordType, [Binding r]) -> f (NRecordType, [Binding r])) -> NExprF r -> f (NExprF r)
- _NList :: Applicative f => ([r] -> f [r]) -> NExprF r -> f (NExprF r)
- _NSym :: Applicative f => (VarName -> f VarName) -> NExprF r -> f (NExprF r)
- _NStr :: Applicative f => (NString r -> f (NString r)) -> NExprF r -> f (NExprF r)
- _NConstant :: Applicative f => (NAtom -> f NAtom) -> NExprF r -> f (NExprF r)
- _Inherit :: Applicative f => ((Maybe r, [NKeyName r], SourcePos) -> f (Maybe r, [NKeyName r], SourcePos)) -> Binding r -> f (Binding r)
- _NamedVar :: Applicative f => ((NAttrPath r, r, SourcePos) -> f (NAttrPath r, r, SourcePos)) -> Binding r -> f (Binding r)
- _ParamSet :: Applicative f => ((ParamSet r1, Bool, Maybe VarName) -> f (ParamSet r2, Bool, Maybe VarName)) -> Params r1 -> f (Params r2)
- _Param :: Applicative f => (VarName -> f VarName) -> Params r -> f (Params r)
- _Antiquoted :: Applicative f => (t -> f r) -> Antiquoted v t -> f (Antiquoted v r)
- _EscapedNewline :: Applicative f => (() -> f ()) -> Antiquoted v r -> f (Antiquoted v r)
- _Plain :: Applicative f => (t -> f v) -> Antiquoted t r -> f (Antiquoted v r)
- _Indented :: Applicative f => ((Int, [Antiquoted Text r]) -> f (Int, [Antiquoted Text r])) -> NString r -> f (NString r)
- _DoubleQuoted :: Applicative f => ([Antiquoted Text r] -> f [Antiquoted Text r]) -> NString r -> f (NString r)
- _StaticKey :: Applicative f => (VarName -> f VarName) -> NKeyName r -> f (NKeyName r)
- _DynamicKey :: Applicative f => (Antiquoted (NString r1) r1 -> f (Antiquoted (NString r2) r2)) -> NKeyName r1 -> f (NKeyName r2)
- _NNot :: Applicative f => (() -> f ()) -> NUnaryOp -> f NUnaryOp
- _NNeg :: Applicative f => (() -> f ()) -> NUnaryOp -> f NUnaryOp
- _NApp :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- _NConcat :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- _NDiv :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- _NMult :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- _NMinus :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- _NPlus :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- _NUpdate :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- _NImpl :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- _NOr :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- _NAnd :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- _NGte :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- _NGt :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- _NLte :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- _NLt :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- _NNEq :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- _NEq :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp
- class NExprAnn ann g | g -> ann where
- ekey :: NExprAnn ann g => NonEmpty Text -> SourcePos -> Lens' (Fix g) (Maybe (Fix g))
- stripPositionInfo :: NExpr -> NExpr
- nullPos :: SourcePos
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 !VarName | A variable. For example, in the expression |
NList ![r] | A list literal. |
NSet !NRecordType ![Binding r] | An attribute set literal |
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). |
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. |
NSynHole !VarName | Syntactic hole, e.g. |
Instances
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.
NamedVar !(NAttrPath r) !r !SourcePos | An explicit naming, such as |
Inherit !(Maybe r) ![NKeyName r] !SourcePos | Using a name already in scope, such as |
Instances
Params
represents all the ways the formal parameters to a
function can be represented.
Param !VarName | For functions with a single named argument, such as |
ParamSet !(ParamSet r) !Bool !(Maybe VarName) | Explicit parameters (argument must be a set). Might specify a name to bind to the set in the function body. The bool indicates whether it is variadic or not. |
Instances
data Antiquoted (v :: *) (r :: *) Source #
Antiquoted
represents an expression that is either
antiquoted (surrounded by ${...}) or plain (not antiquoted).
Plain !v | |
EscapedNewline | |
Antiquoted !r |
Instances
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 concatenating all the parts.
DoubleQuoted ![Antiquoted Text r] | Strings wrapped with double-quotes (") can contain literal newline characters, but the newlines are preserved and no indentation is stripped. |
Indented !Int ![Antiquoted Text r] | Strings wrapped with two single quotes ('') can contain newlines, and their indentation will be stripped, but the amount stripped is remembered. |
Instances
A KeyName
is something that can appear on the left 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 !VarName |
Instances
Functor NKeyName Source # | |
Foldable NKeyName Source # | |
Defined in Nix.Expr.Types fold :: Monoid m => NKeyName m -> m # foldMap :: Monoid m => (a -> m) -> NKeyName a -> m # foldMap' :: Monoid m => (a -> m) -> NKeyName a -> m # foldr :: (a -> b -> b) -> b -> NKeyName a -> b # foldr' :: (a -> b -> b) -> b -> NKeyName a -> b # foldl :: (b -> a -> b) -> b -> NKeyName a -> b # foldl' :: (b -> a -> b) -> b -> NKeyName a -> b # foldr1 :: (a -> a -> a) -> NKeyName a -> a # foldl1 :: (a -> a -> a) -> NKeyName a -> a # elem :: Eq a => a -> NKeyName a -> Bool # maximum :: Ord a => NKeyName a -> a # minimum :: Ord a => NKeyName a -> a # | |
Traversable NKeyName Source # | |
Eq1 NKeyName Source # | |
Show1 NKeyName Source # | |
NFData1 NKeyName Source # | |
Defined in Nix.Expr.Types | |
Hashable1 NKeyName Source # | |
Defined in Nix.Expr.Types | |
Eq r => Eq (NKeyName r) Source # | |
Data r => Data (NKeyName r) Source # | |
Defined in Nix.Expr.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NKeyName r -> c (NKeyName r) # gunfold :: (forall b r0. Data b => c (b -> r0) -> c r0) -> (forall r1. r1 -> c r1) -> Constr -> c (NKeyName r) # toConstr :: NKeyName r -> Constr # dataTypeOf :: NKeyName r -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NKeyName r)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NKeyName r)) # gmapT :: (forall b. Data b => b -> b) -> NKeyName r -> NKeyName r # gmapQl :: (r0 -> r' -> r0) -> r0 -> (forall d. Data d => d -> r') -> NKeyName r -> r0 # gmapQr :: forall r0 r'. (r' -> r0 -> r0) -> r0 -> (forall d. Data d => d -> r') -> NKeyName r -> r0 # gmapQ :: (forall d. Data d => d -> u) -> NKeyName r -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NKeyName r -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NKeyName r -> m (NKeyName r) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NKeyName r -> m (NKeyName r) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NKeyName r -> m (NKeyName r) # | |
Ord r => Ord (NKeyName r) Source # | |
Read r => Read (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. |
Defined in Nix.Expr.Types fromString :: String -> NKeyName r # | |
Generic (NKeyName r) Source # | |
Hashable r => Hashable (NKeyName r) Source # | |
Defined in Nix.Expr.Types | |
ToJSON a => ToJSON (NKeyName a) Source # | |
Defined in Nix.Expr.Types | |
FromJSON a => FromJSON (NKeyName a) Source # | |
Binary a => Binary (NKeyName a) Source # | |
NFData r => NFData (NKeyName r) Source # | |
Defined in Nix.Expr.Types | |
Serialise r => Serialise (NKeyName r) Source # | |
Generic1 NKeyName Source # | |
type Rep (NKeyName r) Source # | |
Defined in Nix.Expr.Types type Rep (NKeyName r) = D1 ('MetaData "NKeyName" "Nix.Expr.Types" "hnix-0.9.0-inplace" 'False) (C1 ('MetaCons "DynamicKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Antiquoted (NString r) r))) :+: C1 ('MetaCons "StaticKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarName))) | |
type Rep1 NKeyName Source # | |
Defined in Nix.Expr.Types |
type NAttrPath r = NonEmpty (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.
Instances
Bounded NUnaryOp Source # | |
Enum NUnaryOp Source # | |
Eq NUnaryOp Source # | |
Data NUnaryOp Source # | |
Defined in Nix.Expr.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NUnaryOp -> c NUnaryOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NUnaryOp # toConstr :: NUnaryOp -> Constr # dataTypeOf :: NUnaryOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NUnaryOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NUnaryOp) # gmapT :: (forall b. Data b => b -> b) -> NUnaryOp -> NUnaryOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NUnaryOp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NUnaryOp -> r # gmapQ :: (forall d. Data d => d -> u) -> NUnaryOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NUnaryOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NUnaryOp -> m NUnaryOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NUnaryOp -> m NUnaryOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NUnaryOp -> m NUnaryOp # | |
Ord NUnaryOp Source # | |
Defined in Nix.Expr.Types | |
Read NUnaryOp Source # | |
Show NUnaryOp Source # | |
Generic NUnaryOp Source # | |
Hashable NUnaryOp Source # | |
Defined in Nix.Expr.Types | |
ToJSON NUnaryOp Source # | |
Defined in Nix.Expr.Types | |
FromJSON NUnaryOp Source # | |
Binary NUnaryOp Source # | |
NFData NUnaryOp Source # | |
Defined in Nix.Expr.Types | |
Serialise NUnaryOp Source # | |
type Rep NUnaryOp Source # | |
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 attribute sets (//) |
NPlus | Addition (+) |
NMinus | Subtraction (-) |
NMult | Multiplication (*) |
NDiv | Division (/) |
NConcat | List concatenation (++) |
NApp | Apply a function to an argument. |
Instances
data NRecordType Source #
Instances
paramName :: Params r -> Maybe VarName Source #
Get the name out of the parameter (there might be none).
defaultOptions ''NExprF)
defaultOptions ''Binding)
_NLet :: Applicative f => (([Binding r], r) -> f ([Binding r], r)) -> NExprF r -> f (NExprF r) Source #
_NHasAttr :: Applicative f => ((r, NAttrPath r) -> f (r, NAttrPath r)) -> NExprF r -> f (NExprF r) Source #
_NSelect :: Applicative f => ((r, NAttrPath r, Maybe r) -> f (r, NAttrPath r, Maybe r)) -> NExprF r -> f (NExprF r) Source #
_NBinary :: Applicative f => ((NBinaryOp, r, r) -> f (NBinaryOp, r, r)) -> NExprF r -> f (NExprF r) Source #
_NLiteralPath :: Applicative f => (FilePath -> f FilePath) -> NExprF r -> f (NExprF r) Source #
_NSet :: Applicative f => ((NRecordType, [Binding r]) -> f (NRecordType, [Binding r])) -> NExprF r -> f (NExprF r) Source #
_NConstant :: Applicative f => (NAtom -> f NAtom) -> NExprF r -> f (NExprF r) Source #
_Inherit :: Applicative f => ((Maybe r, [NKeyName r], SourcePos) -> f (Maybe r, [NKeyName r], SourcePos)) -> Binding r -> f (Binding r) Source #
_NamedVar :: Applicative f => ((NAttrPath r, r, SourcePos) -> f (NAttrPath r, r, SourcePos)) -> Binding r -> f (Binding r) Source #
_ParamSet :: Applicative f => ((ParamSet r1, Bool, Maybe VarName) -> f (ParamSet r2, Bool, Maybe VarName)) -> Params r1 -> f (Params r2) Source #
_Antiquoted :: Applicative f => (t -> f r) -> Antiquoted v t -> f (Antiquoted v r) Source #
_EscapedNewline :: Applicative f => (() -> f ()) -> Antiquoted v r -> f (Antiquoted v r) Source #
_Plain :: Applicative f => (t -> f v) -> Antiquoted t r -> f (Antiquoted v r) Source #
_Indented :: Applicative f => ((Int, [Antiquoted Text r]) -> f (Int, [Antiquoted Text r])) -> NString r -> f (NString r) Source #
_DoubleQuoted :: Applicative f => ([Antiquoted Text r] -> f [Antiquoted Text r]) -> NString r -> f (NString r) Source #
_StaticKey :: Applicative f => (VarName -> f VarName) -> NKeyName r -> f (NKeyName r) Source #
_DynamicKey :: Applicative f => (Antiquoted (NString r1) r1 -> f (Antiquoted (NString r2) r2)) -> NKeyName r1 -> f (NKeyName r2) Source #
''Fix)
stripPositionInfo :: NExpr -> NExpr Source #