Safe Haskell | None |
---|---|
Language | Haskell2010 |
Nix.Types
- data NAtom
- atomText :: NAtom -> Text
- data Antiquoted v r
- = Plain v
- | Antiquoted r
- mergePlain :: Monoid v => [Antiquoted v r] -> [Antiquoted v r]
- removePlainEmpty :: (Eq v, Monoid v) => [Antiquoted v r] -> [Antiquoted v r]
- runAntiquoted :: (v -> a) -> (r -> a) -> Antiquoted v r -> a
- data StringKind
- data NString r
- = NString StringKind [Antiquoted Text r]
- | NUri Text
- splitLines :: [Antiquoted Text r] -> [[Antiquoted Text r]]
- unsplitLines :: [[Antiquoted Text r]] -> [Antiquoted Text r]
- stripIndent :: [Antiquoted Text r] -> NString r
- escapeCodes :: [(Char, Char)]
- fromEscapeCode :: Char -> Maybe Char
- toEscapeCode :: Char -> Maybe Char
- data NKeyName r
- = DynamicKey (Antiquoted (NString r) r)
- | StaticKey Text
- type NSelector r = [NKeyName r]
- data NOperF r
- data NUnaryOp
- data NSpecialOp
- data NBinaryOp
- data NAssoc
- data NOperatorDef
- nixOperators :: [Either NSpecialOp NOperatorDef]
- data OperatorInfo = OperatorInfo {}
- getUnaryOperator :: NUnaryOp -> OperatorInfo
- getBinaryOperator :: NBinaryOp -> OperatorInfo
- getSpecialOperatorPrec :: NSpecialOp -> Int
- selectOp :: OperatorInfo
- hasAttrOp :: OperatorInfo
- appOp :: OperatorInfo
- data NSetBind
- data Binding r
- data FormalParamSet r = FormalParamSet (Map Text (Maybe r))
- data Formals r
- = FormalName Text
- | FormalSet (FormalParamSet r)
- | FormalLeftAt Text (FormalParamSet r)
- | FormalRightAt (FormalParamSet r) Text
- data NExprF r
- type NExpr = Fix NExprF
- mkInt :: Integer -> NExpr
- mkStr :: StringKind -> Text -> NExpr
- mkUri :: Text -> NExpr
- mkPath :: Bool -> FilePath -> NExpr
- mkSym :: Text -> NExpr
- mkSelector :: Text -> NSelector NExpr
- mkBool :: Bool -> NExpr
- mkNull :: NExpr
- mkOper :: NUnaryOp -> NExpr -> NExpr
- mkOper2 :: NBinaryOp -> NExpr -> NExpr -> NExpr
- mkFormalSet :: [(Text, Maybe NExpr)] -> Formals NExpr
- mkApp :: NExpr -> NExpr -> NExpr
- mkRecSet :: [Binding NExpr] -> NExpr
- mkNonRecSet :: [Binding NExpr] -> NExpr
- mkLet :: [Binding NExpr] -> NExpr -> NExpr
- mkList :: [NExpr] -> NExpr
- mkWith :: NExpr -> NExpr -> NExpr
- mkAssert :: NExpr -> NExpr -> NExpr
- mkIf :: NExpr -> NExpr -> NExpr -> NExpr
- mkFunction :: Formals NExpr -> NExpr -> NExpr
- bindTo :: Text -> NExpr -> Binding NExpr
- appendBindings :: [Binding NExpr] -> NExpr -> NExpr
- modifyFunctionBody :: (NExpr -> NExpr) -> NExpr -> NExpr
- data NValueF r
- type NValue = Fix NValueF
- valueText :: NValue -> Text
Documentation
Atoms are values that evaluate to themselves. This means that they appear in both the parsed AST (in the form of literals) and the evaluated form.
Constructors
NInt Integer | An integer. The c nix implementation currently only supports integers that
fit in the range of |
NPath Bool FilePath | The first argument of |
NBool Bool | |
NNull |
data Antiquoted v r Source
Antiquoted
represents an expression that is either
antiquoted (surrounded by ${...}) or plain (not antiquoted).
Constructors
Plain v | |
Antiquoted r |
Instances
Functor (Antiquoted v) | |
(Eq v, Eq r) => Eq (Antiquoted v r) | |
(Data v, Data r) => Data (Antiquoted v r) | |
(Ord v, Ord r) => Ord (Antiquoted v r) | |
(Show v, Show r) => Show (Antiquoted v r) | |
Generic (Antiquoted v r) | |
Typeable (* -> * -> *) Antiquoted | |
type Rep (Antiquoted v r) |
mergePlain :: Monoid v => [Antiquoted v r] -> [Antiquoted v r] Source
removePlainEmpty :: (Eq v, Monoid v) => [Antiquoted v r] -> [Antiquoted v r] Source
runAntiquoted :: (v -> a) -> (r -> a) -> Antiquoted v r -> a Source
A NixString
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.
Constructors
NString StringKind [Antiquoted Text r] | |
NUri Text |
splitLines :: [Antiquoted Text r] -> [[Antiquoted Text r]] Source
Split a stream representing a string with antiquotes on line breaks.
unsplitLines :: [[Antiquoted Text r]] -> [Antiquoted Text r] Source
Join a stream of strings containing antiquotes again. This is the inverse
of splitLines
.
stripIndent :: [Antiquoted Text r] -> NString r Source
Form an indented string by stripping spaces equal to the minimal indent.
escapeCodes :: [(Char, Char)] Source
fromEscapeCode :: Char -> Maybe Char Source
toEscapeCode :: Char -> Maybe Char 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.
Constructors
DynamicKey (Antiquoted (NString r) r) | |
StaticKey Text |
Constructors
NAssocNone | |
NAssocLeft | |
NAssocRight |
data NOperatorDef Source
Instances
data OperatorInfo Source
Constructors
OperatorInfo | |
Fields
|
Instances
A single line of the bindings section of a let expression or of a set.
data FormalParamSet r Source
Constructors
FormalParamSet (Map Text (Maybe r)) |
Instances
Functor FormalParamSet | |
Foldable FormalParamSet | |
Traversable FormalParamSet | |
Eq r => Eq (FormalParamSet r) | |
Data r => Data (FormalParamSet r) | |
Ord r => Ord (FormalParamSet r) | |
Show r => Show (FormalParamSet r) | |
Generic (FormalParamSet r) | |
Typeable (* -> *) FormalParamSet | |
type Rep (FormalParamSet r) |
Formals
represents all the ways the formal parameters to a
function can be represented.
Constructors
FormalName Text | |
FormalSet (FormalParamSet r) | |
FormalLeftAt Text (FormalParamSet r) | |
FormalRightAt (FormalParamSet r) Text |
Constructors
NConstant NAtom | |
NStr (NString r) | |
NList [r] | |
NSet NSetBind [Binding r] | |
NAbs (Formals r) r | |
NOper (NOperF r) | |
NSelect r (NSelector r) (Maybe r) | |
NHasAttr r (NSelector r) | |
NApp r r | |
NSym Text | A |
NLet [Binding r] r | |
NIf r r r | |
NWith r r | |
NAssert r r |
mkStr :: StringKind -> Text -> NExpr Source
mkSelector :: Text -> NSelector NExpr Source
mkNonRecSet :: [Binding NExpr] -> NExpr Source
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`.
modifyFunctionBody :: (NExpr -> NExpr) -> NExpr -> NExpr Source
Applies a transformation to the body of a nix function.