hnix-0.4.0: Haskell implementation of the Nix language

Safe HaskellNone
LanguageHaskell2010

Nix.Expr

Description

Wraps the expression submodules.

Synopsis

Documentation

data NExprF r Source #

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.

Constructors

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 f a, f is represented as NSym "f" and a as NSym "a".

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, nixpkgs/pkgs.

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.

Instances

Functor NExprF Source # 

Methods

fmap :: (a -> b) -> NExprF a -> NExprF b #

(<$) :: a -> NExprF b -> NExprF a #

IsString NExpr Source #

We make an IsString for expressions, where the string is interpreted as an identifier. This is the most common use-case...

Methods

fromString :: String -> NExpr #

Foldable NExprF Source # 

Methods

fold :: Monoid m => NExprF m -> m #

foldMap :: Monoid m => (a -> m) -> NExprF a -> m #

foldr :: (a -> b -> b) -> b -> NExprF a -> b #

foldr' :: (a -> b -> b) -> b -> NExprF a -> b #

foldl :: (b -> a -> b) -> b -> NExprF a -> b #

foldl' :: (b -> a -> b) -> b -> NExprF a -> b #

foldr1 :: (a -> a -> a) -> NExprF a -> a #

foldl1 :: (a -> a -> a) -> NExprF a -> a #

toList :: NExprF a -> [a] #

null :: NExprF a -> Bool #

length :: NExprF a -> Int #

elem :: Eq a => a -> NExprF a -> Bool #

maximum :: Ord a => NExprF a -> a #

minimum :: Ord a => NExprF a -> a #

sum :: Num a => NExprF a -> a #

product :: Num a => NExprF a -> a #

Traversable NExprF Source # 

Methods

traverse :: Applicative f => (a -> f b) -> NExprF a -> f (NExprF b) #

sequenceA :: Applicative f => NExprF (f a) -> f (NExprF a) #

mapM :: Monad m => (a -> m b) -> NExprF a -> m (NExprF b) #

sequence :: Monad m => NExprF (m a) -> m (NExprF a) #

Eq1 NExprF Source # 

Methods

liftEq :: (a -> b -> Bool) -> NExprF a -> NExprF b -> Bool #

Show1 NExprF Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NExprF a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NExprF a] -> ShowS #

Eq r => Eq (NExprF r) Source # 

Methods

(==) :: NExprF r -> NExprF r -> Bool #

(/=) :: NExprF r -> NExprF r -> Bool #

Data r => Data (NExprF r) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NExprF r -> c (NExprF r) #

gunfold :: (forall b a. Data b => c (b -> a) -> c a) -> (forall a. a -> c a) -> Constr -> c (NExprF r) #

toConstr :: NExprF r -> Constr #

dataTypeOf :: NExprF r -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (NExprF r)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NExprF r)) #

gmapT :: (forall b. Data b => b -> b) -> NExprF r -> NExprF r #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NExprF r -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NExprF r -> r #

gmapQ :: (forall d. Data d => d -> u) -> NExprF r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NExprF r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NExprF r -> m (NExprF r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NExprF r -> m (NExprF r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NExprF r -> m (NExprF r) #

Ord r => Ord (NExprF r) Source # 

Methods

compare :: NExprF r -> NExprF r -> Ordering #

(<) :: NExprF r -> NExprF r -> Bool #

(<=) :: NExprF r -> NExprF r -> Bool #

(>) :: NExprF r -> NExprF r -> Bool #

(>=) :: NExprF r -> NExprF r -> Bool #

max :: NExprF r -> NExprF r -> NExprF r #

min :: NExprF r -> NExprF r -> NExprF r #

Show r => Show (NExprF r) Source # 

Methods

showsPrec :: Int -> NExprF r -> ShowS #

show :: NExprF r -> String #

showList :: [NExprF r] -> ShowS #

Generic (NExprF r) Source # 

Associated Types

type Rep (NExprF r) :: * -> * #

Methods

from :: NExprF r -> Rep (NExprF r) x #

to :: Rep (NExprF r) x -> NExprF r #

type Rep (NExprF r) Source # 
type Rep (NExprF r) = D1 * (MetaData "NExprF" "Nix.Expr.Types" "hnix-0.4.0-Ceu7qnqs8HfFdzUe608zID" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NConstant" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * NAtom))) (C1 * (MetaCons "NStr" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (NString r))))) ((:+:) * (C1 * (MetaCons "NSym" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) (C1 * (MetaCons "NList" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [r]))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NSet" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Binding r]))) (C1 * (MetaCons "NRecSet" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Binding r])))) ((:+:) * (C1 * (MetaCons "NLiteralPath" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * FilePath))) ((:+:) * (C1 * (MetaCons "NEnvPath" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * FilePath))) (C1 * (MetaCons "NUnary" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * NUnaryOp)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NBinary" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * NBinaryOp)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r))))) (C1 * (MetaCons "NSelect" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (NAttrPath r))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe r))))))) ((:+:) * (C1 * (MetaCons "NHasAttr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (NAttrPath r))))) (C1 * (MetaCons "NAbs" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Params r))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NApp" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)))) (C1 * (MetaCons "NLet" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Binding r])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r))))) ((:+:) * (C1 * (MetaCons "NIf" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r))))) ((:+:) * (C1 * (MetaCons "NWith" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)))) (C1 * (MetaCons "NAssert" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)))))))))

type NExpr = Fix NExprF Source #

The monomorphic expression type is a fixed point of the polymorphic one.

data Binding r Source #

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

Constructors

NamedVar !(NAttrPath r) !r

An explicit naming, such as x = y or x.y = z.

Inherit !(Maybe r) ![NKeyName r]

Using a name already in scope, such as inherit x; which is shorthand for x = x; or inherit (x) y; which means y = x.y;.

Instances

Functor Binding Source # 

Methods

fmap :: (a -> b) -> Binding a -> Binding b #

(<$) :: a -> Binding b -> Binding a #

Foldable Binding Source # 

Methods

fold :: Monoid m => Binding m -> m #

foldMap :: Monoid m => (a -> m) -> Binding a -> m #

foldr :: (a -> b -> b) -> b -> Binding a -> b #

foldr' :: (a -> b -> b) -> b -> Binding a -> b #

foldl :: (b -> a -> b) -> b -> Binding a -> b #

foldl' :: (b -> a -> b) -> b -> Binding a -> b #

foldr1 :: (a -> a -> a) -> Binding a -> a #

foldl1 :: (a -> a -> a) -> Binding a -> a #

toList :: Binding a -> [a] #

null :: Binding a -> Bool #

length :: Binding a -> Int #

elem :: Eq a => a -> Binding a -> Bool #

maximum :: Ord a => Binding a -> a #

minimum :: Ord a => Binding a -> a #

sum :: Num a => Binding a -> a #

product :: Num a => Binding a -> a #

Traversable Binding Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Binding a -> f (Binding b) #

sequenceA :: Applicative f => Binding (f a) -> f (Binding a) #

mapM :: Monad m => (a -> m b) -> Binding a -> m (Binding b) #

sequence :: Monad m => Binding (m a) -> m (Binding a) #

Eq1 Binding Source # 

Methods

liftEq :: (a -> b -> Bool) -> Binding a -> Binding b -> Bool #

Show1 Binding Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Binding a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Binding a] -> ShowS #

Eq r => Eq (Binding r) Source # 

Methods

(==) :: Binding r -> Binding r -> Bool #

(/=) :: Binding r -> Binding r -> Bool #

Data r => Data (Binding r) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Binding r -> c (Binding r) #

gunfold :: (forall b a. Data b => c (b -> a) -> c a) -> (forall a. a -> c a) -> Constr -> c (Binding r) #

toConstr :: Binding r -> Constr #

dataTypeOf :: Binding r -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Binding r)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Binding r)) #

gmapT :: (forall b. Data b => b -> b) -> Binding r -> Binding r #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Binding r -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Binding r -> r #

gmapQ :: (forall d. Data d => d -> u) -> Binding r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Binding r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Binding r -> m (Binding r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Binding r -> m (Binding r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Binding r -> m (Binding r) #

Ord r => Ord (Binding r) Source # 

Methods

compare :: Binding r -> Binding r -> Ordering #

(<) :: Binding r -> Binding r -> Bool #

(<=) :: Binding r -> Binding r -> Bool #

(>) :: Binding r -> Binding r -> Bool #

(>=) :: Binding r -> Binding r -> Bool #

max :: Binding r -> Binding r -> Binding r #

min :: Binding r -> Binding r -> Binding r #

Show r => Show (Binding r) Source # 

Methods

showsPrec :: Int -> Binding r -> ShowS #

show :: Binding r -> String #

showList :: [Binding r] -> ShowS #

data Params r Source #

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

Constructors

Param !Text

For functions with a single named argument, such as x: x + 1.

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.

Instances

Functor Params Source # 

Methods

fmap :: (a -> b) -> Params a -> Params b #

(<$) :: a -> Params b -> Params a #

Foldable Params Source # 

Methods

fold :: Monoid m => Params m -> m #

foldMap :: Monoid m => (a -> m) -> Params a -> m #

foldr :: (a -> b -> b) -> b -> Params a -> b #

foldr' :: (a -> b -> b) -> b -> Params a -> b #

foldl :: (b -> a -> b) -> b -> Params a -> b #

foldl' :: (b -> a -> b) -> b -> Params a -> b #

foldr1 :: (a -> a -> a) -> Params a -> a #

foldl1 :: (a -> a -> a) -> Params a -> a #

toList :: Params a -> [a] #

null :: Params a -> Bool #

length :: Params a -> Int #

elem :: Eq a => a -> Params a -> Bool #

maximum :: Ord a => Params a -> a #

minimum :: Ord a => Params a -> a #

sum :: Num a => Params a -> a #

product :: Num a => Params a -> a #

Traversable Params Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Params a -> f (Params b) #

sequenceA :: Applicative f => Params (f a) -> f (Params a) #

mapM :: Monad m => (a -> m b) -> Params a -> m (Params b) #

sequence :: Monad m => Params (m a) -> m (Params a) #

Eq1 Params Source # 

Methods

liftEq :: (a -> b -> Bool) -> Params a -> Params b -> Bool #

Show1 Params Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Params a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Params a] -> ShowS #

Eq r => Eq (Params r) Source # 

Methods

(==) :: Params r -> Params r -> Bool #

(/=) :: Params r -> Params r -> Bool #

Data r => Data (Params r) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Params r -> c (Params r) #

gunfold :: (forall b a. Data b => c (b -> a) -> c a) -> (forall a. a -> c a) -> Constr -> c (Params r) #

toConstr :: Params r -> Constr #

dataTypeOf :: Params r -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Params r)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Params r)) #

gmapT :: (forall b. Data b => b -> b) -> Params r -> Params r #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Params r -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Params r -> r #

gmapQ :: (forall d. Data d => d -> u) -> Params r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Params r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Params r -> m (Params r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Params r -> m (Params r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Params r -> m (Params r) #

Ord r => Ord (Params r) Source # 

Methods

compare :: Params r -> Params r -> Ordering #

(<) :: Params r -> Params r -> Bool #

(<=) :: Params r -> Params r -> Bool #

(>) :: Params r -> Params r -> Bool #

(>=) :: Params r -> Params r -> Bool #

max :: Params r -> Params r -> Params r #

min :: Params r -> Params r -> Params r #

Show r => Show (Params r) Source # 

Methods

showsPrec :: Int -> Params r -> ShowS #

show :: Params r -> String #

showList :: [Params r] -> ShowS #

IsString (Params r) Source # 

Methods

fromString :: String -> Params r #

Generic (Params r) Source # 

Associated Types

type Rep (Params r) :: * -> * #

Methods

from :: Params r -> Rep (Params r) x #

to :: Rep (Params r) x -> Params r #

type Rep (Params r) Source # 

data ParamSet r Source #

An explicit parameter set; provides a shorthand for unpacking arguments.

Constructors

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 FixedParamSet, but extra arguments are allowed.

Instances

Functor ParamSet Source # 

Methods

fmap :: (a -> b) -> ParamSet a -> ParamSet b #

(<$) :: a -> ParamSet b -> ParamSet a #

Foldable ParamSet Source # 

Methods

fold :: Monoid m => ParamSet m -> m #

foldMap :: Monoid m => (a -> m) -> ParamSet a -> m #

foldr :: (a -> b -> b) -> b -> ParamSet a -> b #

foldr' :: (a -> b -> b) -> b -> ParamSet a -> b #

foldl :: (b -> a -> b) -> b -> ParamSet a -> b #

foldl' :: (b -> a -> b) -> b -> ParamSet a -> b #

foldr1 :: (a -> a -> a) -> ParamSet a -> a #

foldl1 :: (a -> a -> a) -> ParamSet a -> a #

toList :: ParamSet a -> [a] #

null :: ParamSet a -> Bool #

length :: ParamSet a -> Int #

elem :: Eq a => a -> ParamSet a -> Bool #

maximum :: Ord a => ParamSet a -> a #

minimum :: Ord a => ParamSet a -> a #

sum :: Num a => ParamSet a -> a #

product :: Num a => ParamSet a -> a #

Traversable ParamSet Source # 

Methods

traverse :: Applicative f => (a -> f b) -> ParamSet a -> f (ParamSet b) #

sequenceA :: Applicative f => ParamSet (f a) -> f (ParamSet a) #

mapM :: Monad m => (a -> m b) -> ParamSet a -> m (ParamSet b) #

sequence :: Monad m => ParamSet (m a) -> m (ParamSet a) #

Eq1 ParamSet Source # 

Methods

liftEq :: (a -> b -> Bool) -> ParamSet a -> ParamSet b -> Bool #

Show1 ParamSet Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ParamSet a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ParamSet a] -> ShowS #

Eq r => Eq (ParamSet r) Source # 

Methods

(==) :: ParamSet r -> ParamSet r -> Bool #

(/=) :: ParamSet r -> ParamSet r -> Bool #

Data r => Data (ParamSet r) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParamSet r -> c (ParamSet r) #

gunfold :: (forall b a. Data b => c (b -> a) -> c a) -> (forall a. a -> c a) -> Constr -> c (ParamSet r) #

toConstr :: ParamSet r -> Constr #

dataTypeOf :: ParamSet r -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ParamSet r)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParamSet r)) #

gmapT :: (forall b. Data b => b -> b) -> ParamSet r -> ParamSet r #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParamSet r -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParamSet r -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParamSet r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParamSet r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParamSet r -> m (ParamSet r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParamSet r -> m (ParamSet r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParamSet r -> m (ParamSet r) #

Ord r => Ord (ParamSet r) Source # 

Methods

compare :: ParamSet r -> ParamSet r -> Ordering #

(<) :: ParamSet r -> ParamSet r -> Bool #

(<=) :: ParamSet r -> ParamSet r -> Bool #

(>) :: ParamSet r -> ParamSet r -> Bool #

(>=) :: ParamSet r -> ParamSet r -> Bool #

max :: ParamSet r -> ParamSet r -> ParamSet r #

min :: ParamSet r -> ParamSet r -> ParamSet r #

Show r => Show (ParamSet r) Source # 

Methods

showsPrec :: Int -> ParamSet r -> ShowS #

show :: ParamSet r -> String #

showList :: [ParamSet r] -> ShowS #

Generic (ParamSet r) Source # 

Associated Types

type Rep (ParamSet r) :: * -> * #

Methods

from :: ParamSet r -> Rep (ParamSet r) x #

to :: Rep (ParamSet r) x -> ParamSet r #

type Rep (ParamSet r) Source # 
type Rep (ParamSet r) = D1 * (MetaData "ParamSet" "Nix.Expr.Types" "hnix-0.4.0-Ceu7qnqs8HfFdzUe608zID" False) ((:+:) * (C1 * (MetaCons "FixedParamSet" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Map Text (Maybe r))))) (C1 * (MetaCons "VariadicParamSet" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Map Text (Maybe r))))))

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

Eq2 Antiquoted Source # 

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Antiquoted a c -> Antiquoted b d -> Bool #

Show2 Antiquoted Source # 

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Antiquoted a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Antiquoted a b] -> ShowS #

Functor (Antiquoted v) Source # 

Methods

fmap :: (a -> b) -> Antiquoted v a -> Antiquoted v b #

(<$) :: a -> Antiquoted v b -> Antiquoted v a #

Foldable (Antiquoted v) Source # 

Methods

fold :: Monoid m => Antiquoted v m -> m #

foldMap :: Monoid m => (a -> m) -> Antiquoted v a -> m #

foldr :: (a -> b -> b) -> b -> Antiquoted v a -> b #

foldr' :: (a -> b -> b) -> b -> Antiquoted v a -> b #

foldl :: (b -> a -> b) -> b -> Antiquoted v a -> b #

foldl' :: (b -> a -> b) -> b -> Antiquoted v a -> b #

foldr1 :: (a -> a -> a) -> Antiquoted v a -> a #

foldl1 :: (a -> a -> a) -> Antiquoted v a -> a #

toList :: Antiquoted v a -> [a] #

null :: Antiquoted v a -> Bool #

length :: Antiquoted v a -> Int #

elem :: Eq a => a -> Antiquoted v a -> Bool #

maximum :: Ord a => Antiquoted v a -> a #

minimum :: Ord a => Antiquoted v a -> a #

sum :: Num a => Antiquoted v a -> a #

product :: Num a => Antiquoted v a -> a #

Traversable (Antiquoted v) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Antiquoted v a -> f (Antiquoted v b) #

sequenceA :: Applicative f => Antiquoted v (f a) -> f (Antiquoted v a) #

mapM :: Monad m => (a -> m b) -> Antiquoted v a -> m (Antiquoted v b) #

sequence :: Monad m => Antiquoted v (m a) -> m (Antiquoted v a) #

Eq v => Eq1 (Antiquoted v) Source # 

Methods

liftEq :: (a -> b -> Bool) -> Antiquoted v a -> Antiquoted v b -> Bool #

Show v => Show1 (Antiquoted v) Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Antiquoted v a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Antiquoted v a] -> ShowS #

(Eq r, Eq v) => Eq (Antiquoted v r) Source # 

Methods

(==) :: Antiquoted v r -> Antiquoted v r -> Bool #

(/=) :: Antiquoted v r -> Antiquoted v r -> Bool #

(Data r, Data v) => Data (Antiquoted v r) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Antiquoted v r -> c (Antiquoted v r) #

gunfold :: (forall b a. Data b => c (b -> a) -> c a) -> (forall a. a -> c a) -> Constr -> c (Antiquoted v r) #

toConstr :: Antiquoted v r -> Constr #

dataTypeOf :: Antiquoted v r -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Antiquoted v r)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Antiquoted v r)) #

gmapT :: (forall b. Data b => b -> b) -> Antiquoted v r -> Antiquoted v r #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Antiquoted v r -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Antiquoted v r -> r #

gmapQ :: (forall d. Data d => d -> u) -> Antiquoted v r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Antiquoted v r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Antiquoted v r -> m (Antiquoted v r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Antiquoted v r -> m (Antiquoted v r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Antiquoted v r -> m (Antiquoted v r) #

(Ord r, Ord v) => Ord (Antiquoted v r) Source # 

Methods

compare :: Antiquoted v r -> Antiquoted v r -> Ordering #

(<) :: Antiquoted v r -> Antiquoted v r -> Bool #

(<=) :: Antiquoted v r -> Antiquoted v r -> Bool #

(>) :: Antiquoted v r -> Antiquoted v r -> Bool #

(>=) :: Antiquoted v r -> Antiquoted v r -> Bool #

max :: Antiquoted v r -> Antiquoted v r -> Antiquoted v r #

min :: Antiquoted v r -> Antiquoted v r -> Antiquoted v r #

(Show r, Show v) => Show (Antiquoted v r) Source # 

Methods

showsPrec :: Int -> Antiquoted v r -> ShowS #

show :: Antiquoted v r -> String #

showList :: [Antiquoted v r] -> ShowS #

Generic (Antiquoted v r) Source # 

Associated Types

type Rep (Antiquoted v r) :: * -> * #

Methods

from :: Antiquoted v r -> Rep (Antiquoted v r) x #

to :: Rep (Antiquoted v r) x -> Antiquoted v r #

type Rep (Antiquoted v r) Source # 
type Rep (Antiquoted v r) = D1 * (MetaData "Antiquoted" "Nix.Expr.Types" "hnix-0.4.0-Ceu7qnqs8HfFdzUe608zID" False) ((:+:) * (C1 * (MetaCons "Plain" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * v))) (C1 * (MetaCons "Antiquoted" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r))))

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

Constructors

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.

Instances

Functor NString Source # 

Methods

fmap :: (a -> b) -> NString a -> NString b #

(<$) :: a -> NString b -> NString a #

Foldable NString Source # 

Methods

fold :: Monoid m => NString m -> m #

foldMap :: Monoid m => (a -> m) -> NString a -> m #

foldr :: (a -> b -> b) -> b -> NString a -> b #

foldr' :: (a -> b -> b) -> b -> NString a -> b #

foldl :: (b -> a -> b) -> b -> NString a -> b #

foldl' :: (b -> a -> b) -> b -> NString a -> b #

foldr1 :: (a -> a -> a) -> NString a -> a #

foldl1 :: (a -> a -> a) -> NString a -> a #

toList :: NString a -> [a] #

null :: NString a -> Bool #

length :: NString a -> Int #

elem :: Eq a => a -> NString a -> Bool #

maximum :: Ord a => NString a -> a #

minimum :: Ord a => NString a -> a #

sum :: Num a => NString a -> a #

product :: Num a => NString a -> a #

Traversable NString Source # 

Methods

traverse :: Applicative f => (a -> f b) -> NString a -> f (NString b) #

sequenceA :: Applicative f => NString (f a) -> f (NString a) #

mapM :: Monad m => (a -> m b) -> NString a -> m (NString b) #

sequence :: Monad m => NString (m a) -> m (NString a) #

Eq1 NString Source # 

Methods

liftEq :: (a -> b -> Bool) -> NString a -> NString b -> Bool #

Show1 NString Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NString a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NString a] -> ShowS #

Eq r => Eq (NString r) Source # 

Methods

(==) :: NString r -> NString r -> Bool #

(/=) :: NString r -> NString r -> Bool #

Data r => Data (NString r) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NString r -> c (NString r) #

gunfold :: (forall b a. Data b => c (b -> a) -> c a) -> (forall a. a -> c a) -> Constr -> c (NString r) #

toConstr :: NString r -> Constr #

dataTypeOf :: NString r -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (NString r)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NString r)) #

gmapT :: (forall b. Data b => b -> b) -> NString r -> NString r #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NString r -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NString r -> r #

gmapQ :: (forall d. Data d => d -> u) -> NString r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NString r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NString r -> m (NString r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NString r -> m (NString r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NString r -> m (NString r) #

Ord r => Ord (NString r) Source # 

Methods

compare :: NString r -> NString r -> Ordering #

(<) :: NString r -> NString r -> Bool #

(<=) :: NString r -> NString r -> Bool #

(>) :: NString r -> NString r -> Bool #

(>=) :: NString r -> NString r -> Bool #

max :: NString r -> NString r -> NString r #

min :: NString r -> NString r -> NString r #

Show r => Show (NString r) Source # 

Methods

showsPrec :: Int -> NString r -> ShowS #

show :: NString r -> String #

showList :: [NString r] -> ShowS #

IsString (NString r) Source #

For the the IsString instance, we use a plain doublequoted string.

Methods

fromString :: String -> NString r #

Generic (NString r) Source # 

Associated Types

type Rep (NString r) :: * -> * #

Methods

from :: NString r -> Rep (NString r) x #

to :: Rep (NString r) x -> NString r #

type Rep (NString r) Source # 
type Rep (NString r) = D1 * (MetaData "NString" "Nix.Expr.Types" "hnix-0.4.0-Ceu7qnqs8HfFdzUe608zID" False) ((:+:) * (C1 * (MetaCons "DoubleQuoted" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Antiquoted Text r]))) (C1 * (MetaCons "Indented" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Antiquoted Text r]))))

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 Source # 

Methods

fmap :: (a -> b) -> NKeyName a -> NKeyName b #

(<$) :: a -> NKeyName b -> NKeyName a #

Foldable NKeyName Source # 

Methods

fold :: Monoid m => NKeyName m -> 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 #

toList :: NKeyName a -> [a] #

null :: NKeyName a -> Bool #

length :: NKeyName a -> Int #

elem :: Eq a => a -> NKeyName a -> Bool #

maximum :: Ord a => NKeyName a -> a #

minimum :: Ord a => NKeyName a -> a #

sum :: Num a => NKeyName a -> a #

product :: Num a => NKeyName a -> a #

Traversable NKeyName Source # 

Methods

traverse :: Applicative f => (a -> f b) -> NKeyName a -> f (NKeyName b) #

sequenceA :: Applicative f => NKeyName (f a) -> f (NKeyName a) #

mapM :: Monad m => (a -> m b) -> NKeyName a -> m (NKeyName b) #

sequence :: Monad m => NKeyName (m a) -> m (NKeyName a) #

Eq1 NKeyName Source # 

Methods

liftEq :: (a -> b -> Bool) -> NKeyName a -> NKeyName b -> Bool #

Show1 NKeyName Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NKeyName a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NKeyName a] -> ShowS #

Eq r => Eq (NKeyName r) Source # 

Methods

(==) :: NKeyName r -> NKeyName r -> Bool #

(/=) :: NKeyName r -> NKeyName r -> Bool #

Data r => Data (NKeyName r) Source # 

Methods

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 a. Data b => c (b -> a) -> c a) -> (forall a. a -> c a) -> 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 :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NKeyName r -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NKeyName r -> r #

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 # 

Methods

compare :: NKeyName r -> NKeyName r -> Ordering #

(<) :: NKeyName r -> NKeyName r -> Bool #

(<=) :: NKeyName r -> NKeyName r -> Bool #

(>) :: NKeyName r -> NKeyName r -> Bool #

(>=) :: NKeyName r -> NKeyName r -> Bool #

max :: NKeyName r -> NKeyName r -> NKeyName r #

min :: NKeyName r -> NKeyName r -> NKeyName r #

Show r => Show (NKeyName r) Source # 

Methods

showsPrec :: Int -> NKeyName r -> ShowS #

show :: NKeyName r -> String #

showList :: [NKeyName r] -> ShowS #

IsString (NKeyName r) Source #

Most key names are just static text, so this instance is convenient.

Methods

fromString :: String -> NKeyName r #

Generic (NKeyName r) Source # 

Associated Types

type Rep (NKeyName r) :: * -> * #

Methods

from :: NKeyName r -> Rep (NKeyName r) x #

to :: Rep (NKeyName r) x -> NKeyName r #

type Rep (NKeyName r) Source # 
type Rep (NKeyName r) = D1 * (MetaData "NKeyName" "Nix.Expr.Types" "hnix-0.4.0-Ceu7qnqs8HfFdzUe608zID" False) ((:+:) * (C1 * (MetaCons "DynamicKey" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Antiquoted (NString r) r)))) (C1 * (MetaCons "StaticKey" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

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.

data NUnaryOp Source #

There are two unary operations: logical not and integer negation.

Constructors

NNeg 
NNot 

Instances

Eq NUnaryOp Source # 
Data NUnaryOp Source # 

Methods

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 :: (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 # 
Show NUnaryOp Source # 
Generic NUnaryOp Source # 

Associated Types

type Rep NUnaryOp :: * -> * #

Methods

from :: NUnaryOp -> Rep NUnaryOp x #

to :: Rep NUnaryOp x -> NUnaryOp #

type Rep NUnaryOp Source # 
type Rep NUnaryOp = D1 * (MetaData "NUnaryOp" "Nix.Expr.Types" "hnix-0.4.0-Ceu7qnqs8HfFdzUe608zID" False) ((:+:) * (C1 * (MetaCons "NNeg" PrefixI False) (U1 *)) (C1 * (MetaCons "NNot" PrefixI False) (U1 *)))

data NBinaryOp Source #

Binary operators expressible in the nix language.

Constructors

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 (++)

Instances

Eq NBinaryOp Source # 
Data NBinaryOp Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NBinaryOp -> c NBinaryOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NBinaryOp #

toConstr :: NBinaryOp -> Constr #

dataTypeOf :: NBinaryOp -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NBinaryOp) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NBinaryOp) #

gmapT :: (forall b. Data b => b -> b) -> NBinaryOp -> NBinaryOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NBinaryOp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NBinaryOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> NBinaryOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NBinaryOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NBinaryOp -> m NBinaryOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NBinaryOp -> m NBinaryOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NBinaryOp -> m NBinaryOp #

Ord NBinaryOp Source # 
Show NBinaryOp Source # 
Generic NBinaryOp Source # 

Associated Types

type Rep NBinaryOp :: * -> * #

type Rep NBinaryOp Source # 
type Rep NBinaryOp = D1 * (MetaData "NBinaryOp" "Nix.Expr.Types" "hnix-0.4.0-Ceu7qnqs8HfFdzUe608zID" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NEq" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NNEq" PrefixI False) (U1 *)) (C1 * (MetaCons "NLt" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "NLte" PrefixI False) (U1 *)) (C1 * (MetaCons "NGt" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NGte" PrefixI False) (U1 *)) (C1 * (MetaCons "NAnd" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NOr" PrefixI False) (U1 *)) (C1 * (MetaCons "NImpl" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NUpdate" PrefixI False) (U1 *)) (C1 * (MetaCons "NPlus" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "NMinus" PrefixI False) (U1 *)) (C1 * (MetaCons "NMult" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NDiv" PrefixI False) (U1 *)) (C1 * (MetaCons "NConcat" PrefixI False) (U1 *))))))

paramName :: Params r -> Maybe Text Source #

Get the name out of the parameter (there might be none).

data SrcSpan Source #

A location in a source file

Constructors

SrcSpan 

Fields

Instances

Eq SrcSpan Source # 

Methods

(==) :: SrcSpan -> SrcSpan -> Bool #

(/=) :: SrcSpan -> SrcSpan -> Bool #

Data SrcSpan Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcSpan -> c SrcSpan #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcSpan #

toConstr :: SrcSpan -> Constr #

dataTypeOf :: SrcSpan -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SrcSpan) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcSpan) #

gmapT :: (forall b. Data b => b -> b) -> SrcSpan -> SrcSpan #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r #

gmapQ :: (forall d. Data d => d -> u) -> SrcSpan -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcSpan -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan #

Ord SrcSpan Source # 
Show SrcSpan Source # 
Generic SrcSpan Source # 

Associated Types

type Rep SrcSpan :: * -> * #

Methods

from :: SrcSpan -> Rep SrcSpan x #

to :: Rep SrcSpan x -> SrcSpan #

Semigroup SrcSpan Source # 
type Rep SrcSpan Source # 
type Rep SrcSpan = D1 * (MetaData "SrcSpan" "Nix.Expr.Types.Annotated" "hnix-0.4.0-Ceu7qnqs8HfFdzUe608zID" False) (C1 * (MetaCons "SrcSpan" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "spanBegin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Delta)) (S1 * (MetaSel (Just Symbol "spanEnd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Delta))))

data Ann ann a Source #

A type constructor applied to a type along with an annotation

Intended to be used with Fix: type MyType = Fix (Compose (Ann Annotation) F)

Constructors

Ann 

Fields

Instances

Functor (Ann ann) Source # 

Methods

fmap :: (a -> b) -> Ann ann a -> Ann ann b #

(<$) :: a -> Ann ann b -> Ann ann a #

Foldable (Ann ann) Source # 

Methods

fold :: Monoid m => Ann ann m -> m #

foldMap :: Monoid m => (a -> m) -> Ann ann a -> m #

foldr :: (a -> b -> b) -> b -> Ann ann a -> b #

foldr' :: (a -> b -> b) -> b -> Ann ann a -> b #

foldl :: (b -> a -> b) -> b -> Ann ann a -> b #

foldl' :: (b -> a -> b) -> b -> Ann ann a -> b #

foldr1 :: (a -> a -> a) -> Ann ann a -> a #

foldl1 :: (a -> a -> a) -> Ann ann a -> a #

toList :: Ann ann a -> [a] #

null :: Ann ann a -> Bool #

length :: Ann ann a -> Int #

elem :: Eq a => a -> Ann ann a -> Bool #

maximum :: Ord a => Ann ann a -> a #

minimum :: Ord a => Ann ann a -> a #

sum :: Num a => Ann ann a -> a #

product :: Num a => Ann ann a -> a #

Traversable (Ann ann) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Ann ann a -> f (Ann ann b) #

sequenceA :: Applicative f => Ann ann (f a) -> f (Ann ann a) #

mapM :: Monad m => (a -> m b) -> Ann ann a -> m (Ann ann b) #

sequence :: Monad m => Ann ann (m a) -> m (Ann ann a) #

Show ann => Show1 (Ann ann) Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Ann ann a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Ann ann a] -> ShowS #

(Eq a, Eq ann) => Eq (Ann ann a) Source # 

Methods

(==) :: Ann ann a -> Ann ann a -> Bool #

(/=) :: Ann ann a -> Ann ann a -> Bool #

(Data a, Data ann) => Data (Ann ann a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ann ann a -> c (Ann ann a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ann ann a) #

toConstr :: Ann ann a -> Constr #

dataTypeOf :: Ann ann a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Ann ann a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ann ann a)) #

gmapT :: (forall b. Data b => b -> b) -> Ann ann a -> Ann ann a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ann ann a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ann ann a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ann ann a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ann ann a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ann ann a -> m (Ann ann a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ann ann a -> m (Ann ann a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ann ann a -> m (Ann ann a) #

(Ord a, Ord ann) => Ord (Ann ann a) Source # 

Methods

compare :: Ann ann a -> Ann ann a -> Ordering #

(<) :: Ann ann a -> Ann ann a -> Bool #

(<=) :: Ann ann a -> Ann ann a -> Bool #

(>) :: Ann ann a -> Ann ann a -> Bool #

(>=) :: Ann ann a -> Ann ann a -> Bool #

max :: Ann ann a -> Ann ann a -> Ann ann a #

min :: Ann ann a -> Ann ann a -> Ann ann a #

(Read a, Read ann) => Read (Ann ann a) Source # 

Methods

readsPrec :: Int -> ReadS (Ann ann a) #

readList :: ReadS [Ann ann a] #

readPrec :: ReadPrec (Ann ann a) #

readListPrec :: ReadPrec [Ann ann a] #

(Show a, Show ann) => Show (Ann ann a) Source # 

Methods

showsPrec :: Int -> Ann ann a -> ShowS #

show :: Ann ann a -> String #

showList :: [Ann ann a] -> ShowS #

Generic (Ann ann a) Source # 

Associated Types

type Rep (Ann ann a) :: * -> * #

Methods

from :: Ann ann a -> Rep (Ann ann a) x #

to :: Rep (Ann ann a) x -> Ann ann a #

type Rep (Ann ann a) Source # 
type Rep (Ann ann a) = D1 * (MetaData "Ann" "Nix.Expr.Types.Annotated" "hnix-0.4.0-Ceu7qnqs8HfFdzUe608zID" False) (C1 * (MetaCons "Ann" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "annotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ann)) (S1 * (MetaSel (Just Symbol "annotated") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))

type AnnF ann f = Compose (Ann ann) f Source #

annToAnnF :: Ann ann (f (Fix (AnnF ann f))) -> Fix (AnnF ann f) Source #

type NExprLoc = Fix NExprLocF Source #

A nix expression with source location at each subexpression.

pattern AnnE :: forall ann (g :: * -> *). ann -> g (Fix (Compose * * (Ann ann) g)) -> Fix (Compose * * (Ann ann) g) Source #

stripAnnotation :: Functor f => Fix (AnnF ann f) -> Fix f Source #

data Delta :: * #

Instances

Eq Delta 

Methods

(==) :: Delta -> Delta -> Bool #

(/=) :: Delta -> Delta -> Bool #

Data Delta 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Delta -> c Delta #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Delta #

toConstr :: Delta -> Constr #

dataTypeOf :: Delta -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Delta) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Delta) #

gmapT :: (forall b. Data b => b -> b) -> Delta -> Delta #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Delta -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Delta -> r #

gmapQ :: (forall d. Data d => d -> u) -> Delta -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Delta -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Delta -> m Delta #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Delta -> m Delta #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Delta -> m Delta #

Ord Delta 

Methods

compare :: Delta -> Delta -> Ordering #

(<) :: Delta -> Delta -> Bool #

(<=) :: Delta -> Delta -> Bool #

(>) :: Delta -> Delta -> Bool #

(>=) :: Delta -> Delta -> Bool #

max :: Delta -> Delta -> Delta #

min :: Delta -> Delta -> Delta #

Show Delta 

Methods

showsPrec :: Int -> Delta -> ShowS #

show :: Delta -> String #

showList :: [Delta] -> ShowS #

Generic Delta 

Associated Types

type Rep Delta :: * -> * #

Methods

from :: Delta -> Rep Delta x #

to :: Rep Delta x -> Delta #

Semigroup Delta 

Methods

(<>) :: Delta -> Delta -> Delta #

sconcat :: NonEmpty Delta -> Delta #

stimes :: Integral b => b -> Delta -> Delta #

Monoid Delta 

Methods

mempty :: Delta #

mappend :: Delta -> Delta -> Delta #

mconcat :: [Delta] -> Delta #

Pretty Delta 

Methods

pretty :: Delta -> Doc #

prettyList :: [Delta] -> Doc #

Hashable Delta 

Methods

hashWithSalt :: Int -> Delta -> Int #

hash :: Delta -> Int #

HasBytes Delta 

Methods

bytes :: Delta -> Int64 #

HasDelta Delta 

Methods

delta :: Delta -> Delta #

Measured Delta Strand 

Methods

measure :: Strand -> Delta #

Measured Delta Rope 

Methods

measure :: Rope -> Delta #

MarkParsing Delta Parser 

Methods

mark :: Parser Delta #

release :: Delta -> Parser () #

type Rep Delta 
type Rep Delta = D1 * (MetaData "Delta" "Text.Trifecta.Delta" "trifecta-1.7.1.1-JGhEWKqZl1pj4aEkudSHA" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Columns" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)))) (C1 * (MetaCons "Tab" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)))))) ((:+:) * (C1 * (MetaCons "Lines" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64))))) (C1 * (MetaCons "Directed" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ByteString)) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64)) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int64))))))))

mkInt :: Integer -> NExpr Source #

Make an integer literal expression.

mkStr :: Text -> NExpr Source #

Make a regular (double-quoted) string.

mkIndentedStr :: Text -> NExpr Source #

Make an indented string.

mkUri :: Text -> NExpr Source #

Make a literal URI expression.

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

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

mkEnvPath :: FilePath -> NExpr Source #

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

mkRelPath :: FilePath -> NExpr Source #

Make a path expression which references a relative path.

mkSym :: Text -> NExpr Source #

Make a variable (symbol)

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

An inherit clause without an expression to pull from.

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.

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

Infix version of bindTo.

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 an attribute set (non-recursive).

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

Make an attribute set (recursive).

mkNot :: NExpr -> NExpr Source #

Logical negation.

(!.) :: NExpr -> Text -> NExpr infixl 8 Source #

Dot-reference into an attribute set.

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

Various nix binary operators

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

Various nix binary operators

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

Various nix binary operators

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

Various nix binary operators

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

Various nix binary operators

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

Various nix binary operators

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

Various nix binary operators

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

Various nix binary operators

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

Various nix binary operators

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

Various nix binary operators

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

Various nix binary operators

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

Various nix binary operators

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

Various nix binary operators

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

Various nix binary operators

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

Various nix binary operators

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

Function application expression.

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

Lambda shorthand.