hnix-0.5.2: Haskell implementation of the Nix language

Safe HaskellNone
LanguageHaskell2010

Nix.Expr.Types

Contents

Description

The nix expression type and supporting types.

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 !VarName

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

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 # 
Instance details

Defined in Nix.Expr.Types

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

Instance details

Defined in Nix.Expr.Types

Methods

fromString :: String -> NExpr #

Foldable NExprF Source # 
Instance details

Defined in Nix.Expr.Types

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 # 
Instance details

Defined in Nix.Expr.Types

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

Hashable NExprLoc # 
Instance details

Defined in Nix.Expr.Types.Annotated

Methods

hashWithSalt :: Int -> NExprLoc -> Int #

hash :: NExprLoc -> Int #

ToJSON NExpr Source # 
Instance details

Defined in Nix.Expr.Types

FromJSON NExpr Source # 
Instance details

Defined in Nix.Expr.Types

Eq1 NExprF Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

Show1 NExprF Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

Binary NExprLoc # 
Instance details

Defined in Nix.Expr.Types.Annotated

Methods

put :: NExprLoc -> Put #

get :: Get NExprLoc #

putList :: [NExprLoc] -> Put #

NFData NExprLoc # 
Instance details

Defined in Nix.Expr.Types.Annotated

Methods

rnf :: NExprLoc -> () #

NFData1 NExprF Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

Hashable1 NExprF Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> NExprF a -> Int #

Serialise NExpr Source # 
Instance details

Defined in Nix.Expr.Types

Serialise NExprLoc # 
Instance details

Defined in Nix.Expr.Types.Annotated

ToExpr NExprLoc Source # 
Instance details

Defined in Nix.TH

Applicative m => ToNix Bool m (NExprF r) Source # 
Instance details

Defined in Nix.Convert

Methods

toNix :: Bool -> m (NExprF r) Source #

Applicative m => ToNix () m (NExprF r) Source # 
Instance details

Defined in Nix.Convert

Methods

toNix :: () -> m (NExprF r) Source #

Applicative m => ToValue Bool m (NExprF r) Source # 
Instance details

Defined in Nix.Convert

Methods

toValue :: Bool -> m (NExprF r) Source #

Applicative m => ToValue () m (NExprF r) Source # 
Instance details

Defined in Nix.Convert

Methods

toValue :: () -> m (NExprF r) Source #

Eq r => Eq (NExprF r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

Data r => Data (NExprF r) Source # 
Instance details

Defined in Nix.Expr.Types

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

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

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 # 
Instance details

Defined in Nix.Expr.Types

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 # 
Instance details

Defined in Nix.Expr.Types

Methods

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

show :: NExprF r -> String #

showList :: [NExprF r] -> ShowS #

Generic (NExprF r) Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

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

Methods

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

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

Lift (Fix NExprF) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

lift :: Fix NExprF -> Q Exp #

Hashable r => Hashable (NExprF r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

hashWithSalt :: Int -> NExprF r -> Int #

hash :: NExprF r -> Int #

ToJSON a => ToJSON (NExprF a) Source # 
Instance details

Defined in Nix.Expr.Types

FromJSON a => FromJSON (NExprF a) Source # 
Instance details

Defined in Nix.Expr.Types

Binary a => Binary (NExprF a) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

put :: NExprF a -> Put #

get :: Get (NExprF a) #

putList :: [NExprF a] -> Put #

Binary r => Binary (NExprLocF r) # 
Instance details

Defined in Nix.Expr.Types.Annotated

Methods

put :: NExprLocF r -> Put #

get :: Get (NExprLocF r) #

putList :: [NExprLocF r] -> Put #

NFData r => NFData (NExprF r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

rnf :: NExprF r -> () #

Serialise r => Serialise (NExprF r) Source # 
Instance details

Defined in Nix.Expr.Types

Generic1 NExprF Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep1 NExprF :: k -> * #

Methods

from1 :: NExprF a -> Rep1 NExprF a #

to1 :: Rep1 NExprF a -> NExprF a #

Serialise r => Serialise (Compose (Ann SrcSpan) NExprF r) # 
Instance details

Defined in Nix.Expr.Types.Annotated

type Rep (NExprF r) Source # 
Instance details

Defined in Nix.Expr.Types

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

Defined in Nix.Expr.Types

type Rep1 NExprF = D1 (MetaData "NExprF" "Nix.Expr.Types" "hnix-0.5.2-ETCv3tuhAW86poVV9kTEZx" False) ((((C1 (MetaCons "NConstant" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 NAtom)) :+: C1 (MetaCons "NStr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec1 NString))) :+: (C1 (MetaCons "NSym" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 VarName)) :+: C1 (MetaCons "NList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec1 [])))) :+: ((C1 (MetaCons "NSet" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) ([] :.: Rec1 Binding)) :+: C1 (MetaCons "NRecSet" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) ([] :.: Rec1 Binding))) :+: (C1 (MetaCons "NLiteralPath" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilePath)) :+: C1 (MetaCons "NEnvPath" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilePath))))) :+: (((C1 (MetaCons "NUnary" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 NUnaryOp) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1) :+: C1 (MetaCons "NBinary" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 NBinaryOp) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1 :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1))) :+: (C1 (MetaCons "NSelect" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1 :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (NonEmpty :.: Rec1 NKeyName) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec1 Maybe))) :+: C1 (MetaCons "NHasAttr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1 :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (NonEmpty :.: Rec1 NKeyName)))) :+: ((C1 (MetaCons "NAbs" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec1 Params) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1) :+: C1 (MetaCons "NLet" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) ([] :.: Rec1 Binding) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1)) :+: (C1 (MetaCons "NIf" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1 :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1 :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1)) :+: (C1 (MetaCons "NWith" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1 :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1) :+: C1 (MetaCons "NAssert" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1 :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1))))))

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 !SourcePos

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

Inherit !(Maybe r) ![NKeyName r] !SourcePos

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;. The unsafeGetAttrPos for every name so inherited is the position of the first name, whether that be the first argument to this constructor, or the first member of the list in the second argument.

Instances
Functor Binding Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

Foldable Binding Source # 
Instance details

Defined in Nix.Expr.Types

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 # 
Instance details

Defined in Nix.Expr.Types

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 # 
Instance details

Defined in Nix.Expr.Types

Methods

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

Show1 Binding Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

NFData1 Binding Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

Hashable1 Binding Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Binding a -> Int #

Eq r => Eq (Binding r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

Data r => Data (Binding r) Source # 
Instance details

Defined in Nix.Expr.Types

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

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

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 # 
Instance details

Defined in Nix.Expr.Types

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 # 
Instance details

Defined in Nix.Expr.Types

Methods

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

show :: Binding r -> String #

showList :: [Binding r] -> ShowS #

Generic (Binding r) Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

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

Methods

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

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

Hashable r => Hashable (Binding r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

hashWithSalt :: Int -> Binding r -> Int #

hash :: Binding r -> Int #

ToJSON a => ToJSON (Binding a) Source # 
Instance details

Defined in Nix.Expr.Types

FromJSON a => FromJSON (Binding a) Source # 
Instance details

Defined in Nix.Expr.Types

Binary a => Binary (Binding a) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

put :: Binding a -> Put #

get :: Get (Binding a) #

putList :: [Binding a] -> Put #

NFData r => NFData (Binding r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

rnf :: Binding r -> () #

Serialise r => Serialise (Binding r) Source # 
Instance details

Defined in Nix.Expr.Types

Generic1 Binding Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep1 Binding :: k -> * #

Methods

from1 :: Binding a -> Rep1 Binding a #

to1 :: Rep1 Binding a -> Binding a #

type Rep (Binding r) Source # 
Instance details

Defined in Nix.Expr.Types

type Rep1 Binding Source # 
Instance details

Defined in Nix.Expr.Types

data Params r Source #

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

Constructors

Param !VarName

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

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
Functor Params Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

Foldable Params Source # 
Instance details

Defined in Nix.Expr.Types

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 # 
Instance details

Defined in Nix.Expr.Types

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

ToJSON1 Params Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Params a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Params a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Params a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Params a] -> Encoding #

FromJSON1 Params Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Params a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Params a] #

Eq1 Params Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

Ord1 Params Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftCompare :: (a -> b -> Ordering) -> Params a -> Params b -> Ordering #

Read1 Params Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Params a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Params a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Params a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Params a] #

Show1 Params Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

NFData1 Params Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

Hashable1 Params Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Params a -> Int #

Eq r => Eq (Params r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

Data r => Data (Params r) Source # 
Instance details

Defined in Nix.Expr.Types

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

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

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 # 
Instance details

Defined in Nix.Expr.Types

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 # 
Instance details

Defined in Nix.Expr.Types

Methods

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

show :: Params r -> String #

showList :: [Params r] -> ShowS #

IsString (Params r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

fromString :: String -> Params r #

Generic (Params r) Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

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

Methods

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

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

Hashable r => Hashable (Params r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

hashWithSalt :: Int -> Params r -> Int #

hash :: Params r -> Int #

ToJSON a => ToJSON (Params a) Source # 
Instance details

Defined in Nix.Expr.Types

FromJSON a => FromJSON (Params a) Source # 
Instance details

Defined in Nix.Expr.Types

Binary a => Binary (Params a) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

put :: Params a -> Put #

get :: Get (Params a) #

putList :: [Params a] -> Put #

NFData r => NFData (Params r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

rnf :: Params r -> () #

Serialise r => Serialise (Params r) Source # 
Instance details

Defined in Nix.Expr.Types

Generic1 Params Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep1 Params :: k -> * #

Methods

from1 :: Params a -> Rep1 Params a #

to1 :: Rep1 Params a -> Params a #

type Rep (Params r) Source # 
Instance details

Defined in Nix.Expr.Types

type Rep1 Params Source # 
Instance details

Defined in Nix.Expr.Types

type ParamSet r = [(VarName, Maybe r)] Source #

data Antiquoted (v :: *) (r :: *) Source #

Antiquoted represents an expression that is either antiquoted (surrounded by ${...}) or plain (not antiquoted).

Constructors

Plain !v 
EscapedNewline 
Antiquoted !r 
Instances
ToJSON2 Antiquoted Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> Antiquoted a b -> Value #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [Antiquoted a b] -> Value #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> Antiquoted a b -> Encoding #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [Antiquoted a b] -> Encoding #

FromJSON2 Antiquoted Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (Antiquoted a b) #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [Antiquoted a b] #

Eq2 Antiquoted Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

Ord2 Antiquoted Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Antiquoted a c -> Antiquoted b d -> Ordering #

Read2 Antiquoted Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Antiquoted a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Antiquoted a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Antiquoted a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Antiquoted a b] #

Show2 Antiquoted Source # 
Instance details

Defined in Nix.Expr.Types

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 #

Hashable2 Antiquoted Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftHashWithSalt2 :: (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> Antiquoted a b -> Int #

Functor (Antiquoted v) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

Foldable (Antiquoted v) Source # 
Instance details

Defined in Nix.Expr.Types

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 # 
Instance details

Defined in Nix.Expr.Types

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

ToJSON v => ToJSON1 (Antiquoted v) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Antiquoted v a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Antiquoted v a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Antiquoted v a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Antiquoted v a] -> Encoding #

FromJSON v => FromJSON1 (Antiquoted v) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Antiquoted v a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Antiquoted v a] #

Eq v => Eq1 (Antiquoted v) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

Ord v => Ord1 (Antiquoted v) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftCompare :: (a -> b -> Ordering) -> Antiquoted v a -> Antiquoted v b -> Ordering #

Read v => Read1 (Antiquoted v) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Antiquoted v a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Antiquoted v a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Antiquoted v a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Antiquoted v a] #

Show v => Show1 (Antiquoted v) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

NFData v => NFData1 (Antiquoted v) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

Hashable v => Hashable1 (Antiquoted v) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Antiquoted v a -> Int #

Generic1 (Antiquoted v :: * -> *) Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep1 (Antiquoted v) :: k -> * #

Methods

from1 :: Antiquoted v a -> Rep1 (Antiquoted v) a #

to1 :: Rep1 (Antiquoted v) a -> Antiquoted v a #

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

Defined in Nix.Expr.Types

Methods

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

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

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

Defined in Nix.Expr.Types

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 r0. Data b => c (b -> r0) -> c r0) -> (forall r1. r1 -> c r1) -> 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 :: (r0 -> r' -> r0) -> r0 -> (forall d. Data d => d -> r') -> Antiquoted v r -> r0 #

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

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 v, Ord r) => Ord (Antiquoted v r) Source # 
Instance details

Defined in Nix.Expr.Types

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 #

(Read v, Read r) => Read (Antiquoted v r) Source # 
Instance details

Defined in Nix.Expr.Types

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

Defined in Nix.Expr.Types

Methods

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

show :: Antiquoted v r -> String #

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

Generic (Antiquoted v r) Source # 
Instance details

Defined in Nix.Expr.Types

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 #

(Hashable v, Hashable r) => Hashable (Antiquoted v r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

hashWithSalt :: Int -> Antiquoted v r -> Int #

hash :: Antiquoted v r -> Int #

(ToJSON v, ToJSON a) => ToJSON (Antiquoted v a) Source # 
Instance details

Defined in Nix.Expr.Types

(FromJSON v, FromJSON a) => FromJSON (Antiquoted v a) Source # 
Instance details

Defined in Nix.Expr.Types

(Binary v, Binary a) => Binary (Antiquoted v a) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

put :: Antiquoted v a -> Put #

get :: Get (Antiquoted v a) #

putList :: [Antiquoted v a] -> Put #

(NFData v, NFData r) => NFData (Antiquoted v r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

rnf :: Antiquoted v r -> () #

(Serialise v, Serialise r) => Serialise (Antiquoted v r) Source # 
Instance details

Defined in Nix.Expr.Types

type Rep1 (Antiquoted v :: * -> *) Source # 
Instance details

Defined in Nix.Expr.Types

type Rep1 (Antiquoted v :: * -> *) = D1 (MetaData "Antiquoted" "Nix.Expr.Types" "hnix-0.5.2-ETCv3tuhAW86poVV9kTEZx" False) (C1 (MetaCons "Plain" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 v)) :+: (C1 (MetaCons "EscapedNewline" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Antiquoted" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1)))
type Rep (Antiquoted v r) Source # 
Instance details

Defined in Nix.Expr.Types

type Rep (Antiquoted v r) = D1 (MetaData "Antiquoted" "Nix.Expr.Types" "hnix-0.5.2-ETCv3tuhAW86poVV9kTEZx" False) (C1 (MetaCons "Plain" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 v)) :+: (C1 (MetaCons "EscapedNewline" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Antiquoted" PrefixI False) (S1 (MetaSel (Nothing :: Maybe 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 (") 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
Functor NString Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

Foldable NString Source # 
Instance details

Defined in Nix.Expr.Types

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 # 
Instance details

Defined in Nix.Expr.Types

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

ToJSON1 NString Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> NString a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [NString a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> NString a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [NString a] -> Encoding #

FromJSON1 NString Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (NString a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [NString a] #

Eq1 NString Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

Ord1 NString Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftCompare :: (a -> b -> Ordering) -> NString a -> NString b -> Ordering #

Read1 NString Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NString a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [NString a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (NString a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [NString a] #

Show1 NString Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

NFData1 NString Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

Hashable1 NString Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> NString a -> Int #

Eq r => Eq (NString r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

Data r => Data (NString r) Source # 
Instance details

Defined in Nix.Expr.Types

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

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

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 # 
Instance details

Defined in Nix.Expr.Types

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 #

Read r => Read (NString r) Source # 
Instance details

Defined in Nix.Expr.Types

Show r => Show (NString r) Source # 
Instance details

Defined in Nix.Expr.Types

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.

Instance details

Defined in Nix.Expr.Types

Methods

fromString :: String -> NString r #

Generic (NString r) Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

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

Methods

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

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

Hashable r => Hashable (NString r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

hashWithSalt :: Int -> NString r -> Int #

hash :: NString r -> Int #

ToJSON a => ToJSON (NString a) Source # 
Instance details

Defined in Nix.Expr.Types

FromJSON a => FromJSON (NString a) Source # 
Instance details

Defined in Nix.Expr.Types

Binary a => Binary (NString a) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

put :: NString a -> Put #

get :: Get (NString a) #

putList :: [NString a] -> Put #

NFData r => NFData (NString r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

rnf :: NString r -> () #

Serialise r => Serialise (NString r) Source # 
Instance details

Defined in Nix.Expr.Types

Generic1 NString Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep1 NString :: k -> * #

Methods

from1 :: NString a -> Rep1 NString a #

to1 :: Rep1 NString a -> NString a #

type Rep (NString r) Source # 
Instance details

Defined in Nix.Expr.Types

type Rep1 NString Source # 
Instance details

Defined in Nix.Expr.Types

data NKeyName r Source #

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 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 !VarName 
Instances
Functor NKeyName Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

Foldable NKeyName Source # 
Instance details

Defined in Nix.Expr.Types

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 # 
Instance details

Defined in Nix.Expr.Types

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 # 
Instance details

Defined in Nix.Expr.Types

Methods

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

Show1 NKeyName Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

NFData1 NKeyName Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftRnf :: (a -> ()) -> NKeyName a -> () #

Hashable1 NKeyName Source # 
Instance details

Defined in Nix.Expr.Types

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> NKeyName a -> Int #

Generic1 NKeyName Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep1 NKeyName :: k -> * #

Methods

from1 :: NKeyName a -> Rep1 NKeyName a #

to1 :: Rep1 NKeyName a -> NKeyName a #

Eq r => Eq (NKeyName r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

Data r => Data (NKeyName r) Source # 
Instance details

Defined in Nix.Expr.Types

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 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 :: (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 # 
Instance details

Defined in Nix.Expr.Types

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 #

Read r => Read (NKeyName r) Source # 
Instance details

Defined in Nix.Expr.Types

Show r => Show (NKeyName r) Source # 
Instance details

Defined in Nix.Expr.Types

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.

Instance details

Defined in Nix.Expr.Types

Methods

fromString :: String -> NKeyName r #

Generic (NKeyName r) Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

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

Methods

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

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

Hashable r => Hashable (NKeyName r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

hashWithSalt :: Int -> NKeyName r -> Int #

hash :: NKeyName r -> Int #

ToJSON a => ToJSON (NKeyName a) Source # 
Instance details

Defined in Nix.Expr.Types

FromJSON a => FromJSON (NKeyName a) Source # 
Instance details

Defined in Nix.Expr.Types

Binary a => Binary (NKeyName a) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

put :: NKeyName a -> Put #

get :: Get (NKeyName a) #

putList :: [NKeyName a] -> Put #

NFData r => NFData (NKeyName r) Source # 
Instance details

Defined in Nix.Expr.Types

Methods

rnf :: NKeyName r -> () #

Serialise r => Serialise (NKeyName r) Source # 
Instance details

Defined in Nix.Expr.Types

type Rep1 NKeyName Source # 
Instance details

Defined in Nix.Expr.Types

type Rep (NKeyName r) Source # 
Instance details

Defined in Nix.Expr.Types

type Rep (NKeyName r) = D1 (MetaData "NKeyName" "Nix.Expr.Types" "hnix-0.5.2-ETCv3tuhAW86poVV9kTEZx" 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 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.

data NUnaryOp Source #

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

Constructors

NNeg 
NNot 
Instances
Bounded NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Enum NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Eq NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Data NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

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 # 
Instance details

Defined in Nix.Expr.Types

Read NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Show NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Generic NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep NUnaryOp :: * -> * #

Methods

from :: NUnaryOp -> Rep NUnaryOp x #

to :: Rep NUnaryOp x -> NUnaryOp #

Hashable NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Methods

hashWithSalt :: Int -> NUnaryOp -> Int #

hash :: NUnaryOp -> Int #

ToJSON NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

FromJSON NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Binary NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Methods

put :: NUnaryOp -> Put #

get :: Get NUnaryOp #

putList :: [NUnaryOp] -> Put #

NFData NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Methods

rnf :: NUnaryOp -> () #

Serialise NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

type Rep NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

type Rep NUnaryOp = D1 (MetaData "NUnaryOp" "Nix.Expr.Types" "hnix-0.5.2-ETCv3tuhAW86poVV9kTEZx" 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 (++)

NApp

Apply a function to an argument.

Instances
Bounded NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Enum NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Eq NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Data NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

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 # 
Instance details

Defined in Nix.Expr.Types

Read NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Show NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Generic NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep NBinaryOp :: * -> * #

Hashable NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

ToJSON NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

FromJSON NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Binary NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

NFData NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Methods

rnf :: NBinaryOp -> () #

Serialise NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

type Rep NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

type Rep NBinaryOp = D1 (MetaData "NBinaryOp" "Nix.Expr.Types" "hnix-0.5.2-ETCv3tuhAW86poVV9kTEZx" 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 :: * -> *) :+: C1 (MetaCons "NApp" PrefixI False) (U1 :: * -> *)))))

paramName :: Params r -> Maybe VarName Source #

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

defaultOptions ''NExprF)

defaultOptions ''Binding)

_NAssert :: Applicative f => ((r, r) -> f (r, r)) -> NExprF r -> f (NExprF r) Source #

_NWith :: Applicative f => ((r, r) -> f (r, r)) -> NExprF r -> f (NExprF r) Source #

_NIf :: Applicative f => ((r, r, r) -> f (r, r, r)) -> NExprF r -> f (NExprF r) Source #

_NLet :: Applicative f => (([Binding r], r) -> f ([Binding r], r)) -> NExprF r -> f (NExprF r) Source #

_NAbs :: Applicative f => ((Params r, r) -> f (Params 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 #

_NUnary :: Applicative f => ((NUnaryOp, r) -> f (NUnaryOp, r)) -> NExprF r -> f (NExprF r) Source #

_NRecSet :: Applicative f => ([Binding r] -> f [Binding r]) -> NExprF r -> f (NExprF r) Source #

_NSet :: Applicative f => ([Binding r] -> f [Binding r]) -> NExprF r -> f (NExprF r) Source #

_NList :: Applicative f => ([r] -> f [r]) -> NExprF r -> f (NExprF r) Source #

_NSym :: Applicative f => (VarName -> f VarName) -> NExprF r -> f (NExprF r) Source #

_NStr :: Applicative f => (NString r -> f (NString 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 #

_Param :: Applicative f => (VarName -> f VarName) -> Params r -> f (Params r) 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 #

_DynamicKey :: Applicative f => (Antiquoted (NString r1) r1 -> f (Antiquoted (NString r2) r2)) -> NKeyName r1 -> f (NKeyName r2) Source #

_NNot :: Applicative f => (() -> f ()) -> NUnaryOp -> f NUnaryOp Source #

_NNeg :: Applicative f => (() -> f ()) -> NUnaryOp -> f NUnaryOp Source #

_NApp :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NConcat :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NDiv :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NMult :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NMinus :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NPlus :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NUpdate :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NImpl :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NOr :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NAnd :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NGte :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NGt :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NLte :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NLt :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NNEq :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NEq :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

''Fix)

class NExprAnn ann g | g -> ann where Source #

Minimal complete definition

fromNExpr, toNExpr

Methods

fromNExpr :: g r -> (NExprF r, ann) Source #

toNExpr :: (NExprF r, ann) -> g r Source #

ekey :: NExprAnn ann g => NonEmpty Text -> SourcePos -> Lens' (Fix g) (Maybe (Fix g)) Source #

Orphan instances

Hashable Pos Source # 
Instance details

Methods

hashWithSalt :: Int -> Pos -> Int #

hash :: Pos -> Int #

Hashable SourcePos Source # 
Instance details

ToJSON Pos Source # 
Instance details

ToJSON SourcePos Source # 
Instance details

ToJSON NAtom Source # 
Instance details

FromJSON Pos Source # 
Instance details

FromJSON SourcePos Source # 
Instance details

FromJSON NAtom Source # 
Instance details

Binary Pos Source # 
Instance details

Methods

put :: Pos -> Put #

get :: Get Pos #

putList :: [Pos] -> Put #

Binary SourcePos Source # 
Instance details

Binary NAtom Source # 
Instance details

Methods

put :: NAtom -> Put #

get :: Get NAtom #

putList :: [NAtom] -> Put #

Hashable1 NonEmpty Source # 
Instance details

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> NonEmpty a -> Int #

Serialise Pos Source # 
Instance details

Serialise SourcePos Source # 
Instance details