hnix-0.2.0: Haskell implementation of the Nix language

Safe HaskellNone
LanguageHaskell2010

Nix.Types

Synopsis

Documentation

data NAtom Source

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 Int64.

NPath Bool FilePath

The first argument of NPath is True if the path must be looked up in the Nix search path. For example, nixpkgs/pkgs is represented by NPath True "nixpkgs/pkgs", while foo/bar is represented by NPath False "foo/bar.

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

Merge adjacent Plain values with mappend.

removePlainEmpty :: (Eq v, Monoid v) => [Antiquoted v r] -> [Antiquoted v r] Source

Remove Plain values equal to mempty.

runAntiquoted :: (v -> a) -> (r -> a) -> Antiquoted v r -> a Source

data NString r 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.

Instances

Functor NString 
Eq r => Eq (NString r) 
Data r => Data (NString r) 
Ord r => Ord (NString r) 
Show r => Show (NString r) 
IsString (NString r) 
Generic (NString r) 
Typeable (* -> *) NString 
type Rep (NString r) 

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.

data NKeyName 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 inside let: 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 

Instances

Functor NKeyName 
Eq r => Eq (NKeyName r) 
Data r => Data (NKeyName r) 
Ord r => Ord (NKeyName r) 
Show r => Show (NKeyName r) 
Generic (NKeyName r) 
Typeable (* -> *) NKeyName 
type Rep (NKeyName r) 

data NOperF r Source

Constructors

NUnary NUnaryOp r 
NBinary NBinaryOp r r 

Instances

Functor NOperF 
Eq r => Eq (NOperF r) 
Data r => Data (NOperF r) 
Ord r => Ord (NOperF r) 
Show r => Show (NOperF r) 
Generic (NOperF r) 
Typeable (* -> *) NOperF 
type Rep (NOperF r) 

data Binding r Source

A single line of the bindings section of a let expression or of a set.

Constructors

NamedVar (NSelector r) r 
Inherit (Maybe r) [NSelector r] 

Instances

Functor Binding 
Eq r => Eq (Binding r) 
Data r => Data (Binding r) 
Ord r => Ord (Binding r) 
Show r => Show (Binding r) 
Typeable (* -> *) Binding 

data Formals r Source

Formals represents all the ways the formal parameters to a function can be represented.

Instances

data NExprF r Source

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 NSym is a reference to a variable. For example, f is represented as NSym "f" and a as NSym "a" in f a@.

NLet [Binding r] r 
NIf r r r 
NWith r r 
NAssert r r 

Instances

Functor NExprF 
Eq r => Eq (NExprF r) 
Data r => Data (NExprF r) 
Ord r => Ord (NExprF r) 
Show r => Show (NExprF r) 
Generic (NExprF r) 
Typeable (* -> *) NExprF 
type Rep (NExprF r) 

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.

data NValueF r Source

An NValue is the most reduced form of an NExpr after evaluation is completed.

Constructors

NVConstant NAtom 
NVStr Text 
NVList [r] 
NVSet (Map Text r) 
NVFunction (Formals r) (NValue -> IO r) 

Instances

Functor NValueF 
Show f => Show (NValueF f) 
Generic (NValueF r) 
Typeable (* -> *) NValueF 
type Rep (NValueF r)