hnix-0.17.0: Haskell implementation of the Nix language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Nix.Expr.Types

Description

The Nix expression type and supporting types.

Brief introduction of the Nix expression language.

This module is a beginning of a deep embedding (term) of a Nix language into Haskell. Brief on shallow & deep embedding.

(additiona info for dev): Big use of TemplateHaskell in the module requires proper (top-down) organization of declarations.

Synopsis

Documentation

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.

Param "x"                                  ~  x
ParamSet !(Maybe VarName) !Variadic !(ParamSet r)

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.

ParamSet  Nothing   False [("x",Nothing)]  ~  { x }
ParamSet (pure "s") True  [("x", pure y)]  ~  s@{ x ? y, ... }

Instances

Instances details
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] #

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 #

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 #

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 #

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 #

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

Functor Params Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

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 #

Generic1 Params Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep1 Params :: k -> Type #

Methods

from1 :: forall (a :: k). Params a -> Rep1 Params a #

to1 :: forall (a :: k). Rep1 Params a -> Params a #

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

Defined in Nix.Expr.Types

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

Defined in Nix.Expr.Types

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 :: forall r0 r'. (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) #

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

Methods

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

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

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

Defined in Nix.Expr.Types

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 #

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

Defined in Nix.Expr.Types

Methods

put :: Params r -> Put #

get :: Get (Params r) #

putList :: [Params r] -> Put #

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

Defined in Nix.Expr.Types

Methods

rnf :: Params r -> () #

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

Defined in Nix.Expr.Types

Methods

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

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

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 #

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

Defined in Nix.Expr.Types

Methods

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

hash :: Params r -> Int #

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

Defined in Nix.Expr.Types

type Rep1 Params Source # 
Instance details

Defined in Nix.Expr.Types

type Rep (Params r) Source # 
Instance details

Defined in Nix.Expr.Types

data Variadic Source #

Constructors

Closed 
Variadic 

Instances

Instances details
FromJSON Variadic Source # 
Instance details

Defined in Nix.Expr.Types

ToJSON Variadic Source # 
Instance details

Defined in Nix.Expr.Types

Data Variadic 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) -> Variadic -> c Variadic #

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

toConstr :: Variadic -> Constr #

dataTypeOf :: Variadic -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid Variadic Source # 
Instance details

Defined in Nix.Expr.Types

Semigroup Variadic Source # 
Instance details

Defined in Nix.Expr.Types

Generic Variadic Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep Variadic :: Type -> Type #

Methods

from :: Variadic -> Rep Variadic x #

to :: Rep Variadic x -> Variadic #

Read Variadic Source # 
Instance details

Defined in Nix.Expr.Types

Show Variadic Source # 
Instance details

Defined in Nix.Expr.Types

Binary Variadic Source # 
Instance details

Defined in Nix.Expr.Types

Methods

put :: Variadic -> Put #

get :: Get Variadic #

putList :: [Variadic] -> Put #

NFData Variadic Source # 
Instance details

Defined in Nix.Expr.Types

Methods

rnf :: Variadic -> () #

Eq Variadic Source # 
Instance details

Defined in Nix.Expr.Types

Ord Variadic Source # 
Instance details

Defined in Nix.Expr.Types

Hashable Variadic Source # 
Instance details

Defined in Nix.Expr.Types

Methods

hashWithSalt :: Int -> Variadic -> Int #

hash :: Variadic -> Int #

Serialise Variadic Source # 
Instance details

Defined in Nix.Expr.Types

type Rep Variadic Source # 
Instance details

Defined in Nix.Expr.Types

type Rep Variadic = D1 ('MetaData "Variadic" "Nix.Expr.Types" "hnix-0.17.0-8saIMbclRB9HPH4JCEpCXn" 'False) (C1 ('MetaCons "Closed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Variadic" 'PrefixI 'False) (U1 :: Type -> Type))

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

newtype VarName Source #

Constructors

VarName Text 

Instances

Instances details
FromJSON VarName Source # 
Instance details

Defined in Nix.Expr.Types

ToJSON VarName Source # 
Instance details

Defined in Nix.Expr.Types

Data VarName 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) -> VarName -> c VarName #

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

toConstr :: VarName -> Constr #

dataTypeOf :: VarName -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString VarName Source # 
Instance details

Defined in Nix.Expr.Types

Methods

fromString :: String -> VarName #

Generic VarName Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep VarName :: Type -> Type #

Methods

from :: VarName -> Rep VarName x #

to :: Rep VarName x -> VarName #

Read VarName Source # 
Instance details

Defined in Nix.Expr.Types

Show VarName Source # 
Instance details

Defined in Nix.Expr.Types

Binary VarName Source # 
Instance details

Defined in Nix.Expr.Types

Methods

put :: VarName -> Put #

get :: Get VarName #

putList :: [VarName] -> Put #

NFData VarName Source # 
Instance details

Defined in Nix.Expr.Types

Methods

rnf :: VarName -> () #

Eq VarName Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

Ord VarName Source # 
Instance details

Defined in Nix.Expr.Types

Hashable VarName Source # 
Instance details

Defined in Nix.Expr.Types

Methods

hashWithSalt :: Int -> VarName -> Int #

hash :: VarName -> Int #

ToExpr VarName Source # 
Instance details

Defined in Nix.TH

Methods

toExpr :: VarName -> NExpr Source #

ToString VarName Source # 
Instance details

Defined in Nix.Expr.Types

Methods

toString :: VarName -> String #

Serialise VarName Source # 
Instance details

Defined in Nix.Expr.Types

(Convertible e t f m, FromValue a m (NValue t f m)) => FromValue (AttrSet a) m (Deeper (NValue' t f m (NValue t f m))) Source # 
Instance details

Defined in Nix.Convert

Methods

fromValue :: Deeper (NValue' t f m (NValue t f m)) -> m (AttrSet a) Source #

fromValueMay :: Deeper (NValue' t f m (NValue t f m)) -> m (Maybe (AttrSet a)) Source #

(Convertible e t f m, ToValue a m (NValue t f m)) => ToValue (AttrSet a) m (Deeper (NValue' t f m (NValue t f m))) Source # 
Instance details

Defined in Nix.Convert

Methods

toValue :: AttrSet a -> m (Deeper (NValue' t f m (NValue t f m))) Source #

Convertible e t f m => FromValue (AttrSet (NValue t f m)) m (NValue' t f m (NValue t f m)) Source # 
Instance details

Defined in Nix.Convert

Methods

fromValue :: NValue' t f m (NValue t f m) -> m (AttrSet (NValue t f m)) Source #

fromValueMay :: NValue' t f m (NValue t f m) -> m (Maybe (AttrSet (NValue t f m))) Source #

Convertible e t f m => ToValue (AttrSet (NValue t f m)) m (NValue' t f m (NValue t f m)) Source # 
Instance details

Defined in Nix.Convert

Methods

toValue :: AttrSet (NValue t f m) -> m (NValue' t f m (NValue t f m)) Source #

FromValue (AttrSet (Symbolic m), PositionSet) m (Symbolic m) Source # 
Instance details

Defined in Nix.Lint

(Convertible e t f m, FromValue a m (NValue t f m)) => FromValue (AttrSet a, PositionSet) m (Deeper (NValue' t f m (NValue t f m))) Source # 
Instance details

Defined in Nix.Convert

Methods

fromValue :: Deeper (NValue' t f m (NValue t f m)) -> m (AttrSet a, PositionSet) Source #

fromValueMay :: Deeper (NValue' t f m (NValue t f m)) -> m (Maybe (AttrSet a, PositionSet)) Source #

ToValue (AttrSet (Symbolic m), PositionSet) m (Symbolic m) Source # 
Instance details

Defined in Nix.Lint

Methods

toValue :: (AttrSet (Symbolic m), PositionSet) -> m (Symbolic m) Source #

(Convertible e t f m, ToValue a m (NValue t f m)) => ToValue (AttrSet a, PositionSet) m (Deeper (NValue' t f m (NValue t f m))) Source # 
Instance details

Defined in Nix.Convert

Methods

toValue :: (AttrSet a, PositionSet) -> m (Deeper (NValue' t f m (NValue t f m))) Source #

Convertible e t f m => FromValue (AttrSet (NValue t f m), PositionSet) m (NValue' t f m (NValue t f m)) Source # 
Instance details

Defined in Nix.Convert

Methods

fromValue :: NValue' t f m (NValue t f m) -> m (AttrSet (NValue t f m), PositionSet) Source #

fromValueMay :: NValue' t f m (NValue t f m) -> m (Maybe (AttrSet (NValue t f m), PositionSet)) Source #

Convertible e t f m => ToValue (AttrSet (NValue t f m), PositionSet) m (NValue' t f m (NValue t f m)) Source # 
Instance details

Defined in Nix.Convert

Methods

toValue :: (AttrSet (NValue t f m), PositionSet) -> m (NValue' t f m (NValue t f m)) Source #

type Rep VarName Source # 
Instance details

Defined in Nix.Expr.Types

type Rep VarName = D1 ('MetaData "VarName" "Nix.Expr.Types" "hnix-0.17.0-8saIMbclRB9HPH4JCEpCXn" 'True) (C1 ('MetaCons "VarName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

type PositionSet = AttrSet NSourcePos Source #

Holds file positionng information for abstrations. A type synonym for HashMap VarName NSourcePos.

type AttrSet = HashMap VarName Source #

Hashmap VarName -- type synonym

data NSourcePos Source #

Represents source positions. Source line & column positions change intensively during parsing, so they are declared strict to avoid memory leaks.

The data type is a reimplementation of Pos SourcePos.

Constructors

NSourcePos 

Fields

Instances

Instances details
FromJSON NSourcePos Source # 
Instance details

Defined in Nix.Expr.Types

ToJSON NSourcePos Source # 
Instance details

Defined in Nix.Expr.Types

Data NSourcePos 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) -> NSourcePos -> c NSourcePos #

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

toConstr :: NSourcePos -> Constr #

dataTypeOf :: NSourcePos -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic NSourcePos Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep NSourcePos :: Type -> Type #

Read NSourcePos Source # 
Instance details

Defined in Nix.Expr.Types

Show NSourcePos Source # 
Instance details

Defined in Nix.Expr.Types

Binary NSourcePos Source # 
Instance details

Defined in Nix.Expr.Types

NFData NSourcePos Source # 
Instance details

Defined in Nix.Expr.Types

Methods

rnf :: NSourcePos -> () #

Eq NSourcePos Source # 
Instance details

Defined in Nix.Expr.Types

Ord NSourcePos Source # 
Instance details

Defined in Nix.Expr.Types

Hashable NSourcePos Source # 
Instance details

Defined in Nix.Expr.Types

Serialise NSourcePos Source # 
Instance details

Defined in Nix.Expr.Types

Convertible e t f m => ToValue NSourcePos m (NValue' t f m (NValue t f m)) Source # 
Instance details

Defined in Nix.Convert

Methods

toValue :: NSourcePos -> m (NValue' t f m (NValue t f m)) Source #

FromValue (AttrSet (Symbolic m), PositionSet) m (Symbolic m) Source # 
Instance details

Defined in Nix.Lint

(Convertible e t f m, FromValue a m (NValue t f m)) => FromValue (AttrSet a, PositionSet) m (Deeper (NValue' t f m (NValue t f m))) Source # 
Instance details

Defined in Nix.Convert

Methods

fromValue :: Deeper (NValue' t f m (NValue t f m)) -> m (AttrSet a, PositionSet) Source #

fromValueMay :: Deeper (NValue' t f m (NValue t f m)) -> m (Maybe (AttrSet a, PositionSet)) Source #

ToValue (AttrSet (Symbolic m), PositionSet) m (Symbolic m) Source # 
Instance details

Defined in Nix.Lint

Methods

toValue :: (AttrSet (Symbolic m), PositionSet) -> m (Symbolic m) Source #

(Convertible e t f m, ToValue a m (NValue t f m)) => ToValue (AttrSet a, PositionSet) m (Deeper (NValue' t f m (NValue t f m))) Source # 
Instance details

Defined in Nix.Convert

Methods

toValue :: (AttrSet a, PositionSet) -> m (Deeper (NValue' t f m (NValue t f m))) Source #

Convertible e t f m => FromValue (AttrSet (NValue t f m), PositionSet) m (NValue' t f m (NValue t f m)) Source # 
Instance details

Defined in Nix.Convert

Methods

fromValue :: NValue' t f m (NValue t f m) -> m (AttrSet (NValue t f m), PositionSet) Source #

fromValueMay :: NValue' t f m (NValue t f m) -> m (Maybe (AttrSet (NValue t f m), PositionSet)) Source #

Convertible e t f m => ToValue (AttrSet (NValue t f m), PositionSet) m (NValue' t f m (NValue t f m)) Source # 
Instance details

Defined in Nix.Convert

Methods

toValue :: (AttrSet (NValue t f m), PositionSet) -> m (NValue' t f m (NValue t f m)) Source #

type Rep NSourcePos Source # 
Instance details

Defined in Nix.Expr.Types

type Rep NSourcePos = D1 ('MetaData "NSourcePos" "Nix.Expr.Types" "hnix-0.17.0-8saIMbclRB9HPH4JCEpCXn" 'False) (C1 ('MetaCons "NSourcePos" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSourceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Path) :*: (S1 ('MetaSel ('Just "getSourceLine") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NPos) :*: S1 ('MetaSel ('Just "getSourceColumn") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NPos))))

newtype NPos Source #

Constructors

NPos Pos 

Instances

Instances details
FromJSON NPos Source # 
Instance details

Defined in Nix.Expr.Types

ToJSON NPos Source # 
Instance details

Defined in Nix.Expr.Types

Data NPos 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) -> NPos -> c NPos #

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

toConstr :: NPos -> Constr #

dataTypeOf :: NPos -> DataType #

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

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

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

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

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

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

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

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

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

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

Semigroup NPos Source # 
Instance details

Defined in Nix.Expr.Types

Methods

(<>) :: NPos -> NPos -> NPos #

sconcat :: NonEmpty NPos -> NPos #

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

Generic NPos Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep NPos :: Type -> Type #

Methods

from :: NPos -> Rep NPos x #

to :: Rep NPos x -> NPos #

Read NPos Source # 
Instance details

Defined in Nix.Expr.Types

Show NPos Source # 
Instance details

Defined in Nix.Expr.Types

Methods

showsPrec :: Int -> NPos -> ShowS #

show :: NPos -> String #

showList :: [NPos] -> ShowS #

Binary NPos Source # 
Instance details

Defined in Nix.Expr.Types

Methods

put :: NPos -> Put #

get :: Get NPos #

putList :: [NPos] -> Put #

NFData NPos Source # 
Instance details

Defined in Nix.Expr.Types

Methods

rnf :: NPos -> () #

Eq NPos Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

Ord NPos Source # 
Instance details

Defined in Nix.Expr.Types

Methods

compare :: NPos -> NPos -> Ordering #

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

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

(>) :: NPos -> NPos -> Bool #

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

max :: NPos -> NPos -> NPos #

min :: NPos -> NPos -> NPos #

Hashable NPos Source # 
Instance details

Defined in Nix.Expr.Types

Methods

hashWithSalt :: Int -> NPos -> Int #

hash :: NPos -> Int #

Serialise NPos Source # 
Instance details

Defined in Nix.Expr.Types

type Rep NPos Source # 
Instance details

Defined in Nix.Expr.Types

type Rep NPos = D1 ('MetaData "NPos" "Nix.Expr.Types" "hnix-0.17.0-8saIMbclRB9HPH4JCEpCXn" 'True) (C1 ('MetaCons "NPos" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pos)))

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

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

Constructors

Plain !v 
EscapedNewline

EscapedNewline corresponds to the special newline form

''\n

in an indented string. It is equivalent to a single newline character:

''''\n''  ≡  "\n"
Antiquoted !r 

Instances

Instances details
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] #

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 #

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 #

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

Defined in Nix.Expr.Types

Associated Types

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

Methods

from1 :: forall (a :: k). Antiquoted v a -> Rep1 (Antiquoted v) a #

to1 :: forall (a :: k). Rep1 (Antiquoted v) a -> Antiquoted v a #

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

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 #

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 #

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 #

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 #

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

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 #

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 #

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

Defined in Nix.Expr.Types

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

Defined in Nix.Expr.Types

(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 :: forall r0 r'. (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) #

Generic (Antiquoted v r) Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

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

Methods

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

to :: Rep (Antiquoted v r) x -> 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 #

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

Defined in Nix.Expr.Types

Methods

put :: Antiquoted v r -> Put #

get :: Get (Antiquoted v r) #

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

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

Defined in Nix.Expr.Types

Methods

rnf :: Antiquoted v r -> () #

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

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

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

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

Defined in Nix.Expr.Types

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

Defined in Nix.Expr.Types

type Rep1 (Antiquoted v :: Type -> Type) = D1 ('MetaData "Antiquoted" "Nix.Expr.Types" "hnix-0.17.0-8saIMbclRB9HPH4JCEpCXn" 'False) (C1 ('MetaCons "Plain" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 v)) :+: (C1 ('MetaCons "EscapedNewline" 'PrefixI 'False) (U1 :: Type -> Type) :+: 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.17.0-8saIMbclRB9HPH4JCEpCXn" 'False) (C1 ('MetaCons "Plain" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 v)) :+: (C1 ('MetaCons "EscapedNewline" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Antiquoted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 r))))

_Param :: Applicative f => (VarName -> f VarName) -> Params r -> f (Params r) Source #

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

DoubleQuoted [Plain "x",Antiquoted y]   ~  "x${y}"
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.

Indented 1 [Plain "x"]                  ~  '' x''

Indented 0 [EscapedNewline]             ~  ''''\n''

Indented 0 [Plain "x\n ",Antiquoted y]  ~  ''
                                           x
                                            ${y}''

Instances

Instances details
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] #

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 #

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 #

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 #

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 #

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

Functor NString Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

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 #

Generic1 NString Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep1 NString :: k -> Type #

Methods

from1 :: forall (a :: k). NString a -> Rep1 NString a #

to1 :: forall (a :: k). Rep1 NString a -> NString a #

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

Defined in Nix.Expr.Types

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

Defined in Nix.Expr.Types

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 :: forall r0 r'. (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) #

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

Methods

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

to :: Rep (NString r) x -> 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 #

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

Defined in Nix.Expr.Types

Methods

put :: NString r -> Put #

get :: Get (NString r) #

putList :: [NString r] -> Put #

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

Defined in Nix.Expr.Types

Methods

rnf :: NString r -> () #

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

Defined in Nix.Expr.Types

Methods

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

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

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 #

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

Defined in Nix.Expr.Types

Methods

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

hash :: NString r -> Int #

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

Defined in Nix.Expr.Types

type Rep1 NString Source # 
Instance details

Defined in Nix.Expr.Types

type Rep (NString r) Source # 
Instance details

Defined in Nix.Expr.Types

_Plain :: Applicative f => (t -> f v) -> Antiquoted t r -> f (Antiquoted v r) Source #

_EscapedNewline :: Applicative f => (() -> f ()) -> Antiquoted v r -> f (Antiquoted v r) Source #

_Antiquoted :: Applicative f => (t -> f r) -> Antiquoted v t -> f (Antiquoted v r) Source #

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 fail.
  • 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)
DynamicKey (Plain (DoubleQuoted [Plain "x"]))     ~  "x"
DynamicKey (Antiquoted x)                         ~  ${x}
DynamicKey (Plain (DoubleQuoted [Antiquoted x]))  ~  "${x}"
StaticKey !VarName
StaticKey "x"                                     ~  x

Instances

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

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 #

Eq1 NKeyName Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

Ord1 NKeyName Source #

Since: 0.10.1

Instance details

Defined in Nix.Expr.Types

Methods

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

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 #

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

Functor NKeyName Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

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 #

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

Defined in Nix.Expr.Types

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

Defined in Nix.Expr.Types

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

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

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

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

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

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

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

Methods

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

to :: Rep (NKeyName r) x -> 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 #

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

Defined in Nix.Expr.Types

Methods

put :: NKeyName r -> Put #

get :: Get (NKeyName r) #

putList :: [NKeyName r] -> Put #

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

Defined in Nix.Expr.Types

Methods

rnf :: NKeyName r -> () #

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

Defined in Nix.Expr.Types

Methods

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

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

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 #

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

Defined in Nix.Expr.Types

Methods

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

hash :: NKeyName r -> Int #

Serialise r => Serialise (NKeyName r) 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.17.0-8saIMbclRB9HPH4JCEpCXn" '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)))

_Indented :: Applicative f => ((Int, [Antiquoted Text r]) -> f (Int, [Antiquoted Text r])) -> NString r -> f (NString r) Source #

data Binding r Source #

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

Constructors

NamedVar !(NAttrPath r) !r !NSourcePos

An explicit naming.

NamedVar (StaticKey "x" :| [StaticKey "y"]) z NSourcePos{}  ~  x.y = z;
Inherit !(Maybe r) ![VarName] !NSourcePos

Inheriting an attribute (binding) into the attribute set from the other scope (attribute set). No denoted scope means to inherit from the closest outside scope.

HaskNixpseudocode
Inherit Nothing [StaticKey "a"] NSourcePos{}inherit a;a = outside.a;
Inherit (pure x) [StaticKey "a"] NSourcePos{}inherit (x) a;a = x.a;
Inherit (pure x) [StaticKey "a", StaticKey "b"] NSourcePos{} inherit (x) a b; a = x.a; b = x.b;

(2021-07-07 use details): Inherits the position of the first name through unsafeGetAttrPos. The position of the scope inherited from else - the position of the first member of the binds list.

Instances

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

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 #

Eq1 Binding Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

Ord1 Binding Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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 #

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

Functor Binding Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

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 #

Generic1 Binding Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep1 Binding :: k -> Type #

Methods

from1 :: forall (a :: k). Binding a -> Rep1 Binding a #

to1 :: forall (a :: k). Rep1 Binding a -> Binding a #

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

Defined in Nix.Expr.Types

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

Defined in Nix.Expr.Types

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 :: forall r0 r'. (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) #

Generic (Binding r) Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

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

Methods

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

to :: Rep (Binding r) x -> 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 #

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

Defined in Nix.Expr.Types

Methods

put :: Binding r -> Put #

get :: Get (Binding r) #

putList :: [Binding r] -> Put #

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

Defined in Nix.Expr.Types

Methods

rnf :: Binding r -> () #

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

Defined in Nix.Expr.Types

Methods

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

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

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 #

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

Defined in Nix.Expr.Types

Methods

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

hash :: Binding r -> Int #

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

Defined in Nix.Expr.Types

type Rep1 Binding Source # 
Instance details

Defined in Nix.Expr.Types

type Rep (Binding r) Source # 
Instance details

Defined in Nix.Expr.Types

type NAttrPath r = NonEmpty (NKeyName r) Source #

A selector (for example in a let or an attribute set) is made up of strung-together key names.

StaticKey "x" :| [DynamicKey (Antiquoted y)]  ~  x.${y}

data NUnaryOp Source #

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

Constructors

NNeg
-
NNot
!

Instances

Instances details
FromJSON NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

ToJSON 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 :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NUnaryOp -> r #

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

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

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

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

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

Bounded NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Enum NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Generic NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep NUnaryOp :: Type -> Type #

Methods

from :: NUnaryOp -> Rep NUnaryOp x #

to :: Rep NUnaryOp x -> NUnaryOp #

Read NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

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

Eq NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Ord NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Hashable NUnaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Methods

hashWithSalt :: Int -> NUnaryOp -> Int #

hash :: NUnaryOp -> Int #

NOp NUnaryOp Source # 
Instance details

Defined in Nix.Parser

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.17.0-8saIMbclRB9HPH4JCEpCXn" 'False) (C1 ('MetaCons "NNeg" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NNot" 'PrefixI 'False) (U1 :: Type -> Type))

data Recursivity Source #

Distinguishes between recursive and non-recursive. Mainly for attribute sets.

Constructors

NonRecursive
    { ... }
Recursive
rec { ... }

Instances

Instances details
FromJSON Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

ToJSON Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

Data Recursivity 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) -> Recursivity -> c Recursivity #

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

toConstr :: Recursivity -> Constr #

dataTypeOf :: Recursivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

Semigroup Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

Bounded Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

Enum Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

Generic Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep Recursivity :: Type -> Type #

Read Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

Show Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

Binary Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

NFData Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

Methods

rnf :: Recursivity -> () #

Eq Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

Ord Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

Hashable Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

Serialise Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

type Rep Recursivity Source # 
Instance details

Defined in Nix.Expr.Types

type Rep Recursivity = D1 ('MetaData "Recursivity" "Nix.Expr.Types" "hnix-0.17.0-8saIMbclRB9HPH4JCEpCXn" 'False) (C1 ('MetaCons "NonRecursive" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Recursive" 'PrefixI 'False) (U1 :: Type -> Type))

_NamedVar :: Applicative f => ((NAttrPath r, r, NSourcePos) -> f (NAttrPath r, r, NSourcePos)) -> Binding r -> f (Binding r) Source #

_Inherit :: Applicative f => ((Maybe r, [VarName], NSourcePos) -> f (Maybe r, [VarName], NSourcePos)) -> Binding r -> f (Binding r) Source #

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

Get the left attr set, extend it with the right one & override equal keys (//)

NPlus

Addition (+)

NMinus

Subtraction (-)

NMult

Multiplication (*)

NDiv

Division (/)

NConcat

List concatenation (++)

Instances

Instances details
FromJSON NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

ToJSON 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 :: forall r r'. (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 #

Bounded NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Enum NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Generic NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep NBinaryOp :: Type -> Type #

Read NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

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

Eq NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Ord NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

Hashable NBinaryOp Source # 
Instance details

Defined in Nix.Expr.Types

NOp NBinaryOp Source # 
Instance details

Defined in Nix.Parser

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.17.0-8saIMbclRB9HPH4JCEpCXn" 'False) (((C1 ('MetaCons "NEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NNEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NLt" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NLte" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NGt" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NGte" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NAnd" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "NOr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NImpl" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NUpdate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NPlus" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NMinus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NMult" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NDiv" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NConcat" 'PrefixI 'False) (U1 :: Type -> Type)))))

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

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

data NExprF r Source #

The main Nix expression type. As it is polimorphic, has a functor, which allows 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, floats, 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".

NSym "x"                                    ~  x
NList ![r]

A list literal.

NList [x,y]                                 ~  [ x y ]
NSet !Recursivity ![Binding r]

An attribute set literal

NSet Recursive    [NamedVar x y _]         ~  rec { x = y; }
NSet NonRecursive [Inherit Nothing [x] _]  ~  { inherit x; }
NLiteralPath !Path

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.

NLiteralPath "/x"                           ~  /x
NLiteralPath "x/y"                          ~  x/y
NEnvPath !Path

A path which refers to something in the Nix search path (the NIX_PATH environment variable. For example, nixpkgs/pkgs.

NEnvPath "x"                                ~  <x>
NApp !r !r

Functional application (aka F.A., apply a function to an argument).

NApp f x  ~  f x
NUnary !NUnaryOp !r

Application of a unary operator to an expression.

NUnary NNeg x                               ~  - x
NUnary NNot x                               ~  ! x
NBinary !NBinaryOp !r !r

Application of a binary operator to two expressions.

NBinary NPlus x y                           ~  x + y
NBinary NApp  f x                           ~  f x
NSelect !(Maybe r) !r !(NAttrPath r)

Dot-reference into an attribute set, optionally providing an alternative if the key doesn't exist.

NSelect Nothing  s (x :| [])                ~  s.x
NSelect (pure y) s (x :| [])                ~  s.x or y
NHasAttr !r !(NAttrPath r)

Ask if a set contains a given attribute path.

NHasAttr s (x :| [])                        ~  s ? x
NAbs !(Params r) !r

A function literal (lambda abstraction).

NAbs (Param "x") y                          ~  x: y
NLet ![Binding r] !r

Evaluate the second argument after introducing the bindings.

NLet []                    x                ~  let in x
NLet [NamedVar x y _]      z                ~  let x = y; in z
NLet [Inherit Nothing x _] y                ~  let inherit x; in y
NIf !r !r !r

If-then-else statement.

NIf x y z                                   ~  if x then y else z
NWith !r !r

Evaluate an attribute set, bring its bindings into scope, and evaluate the second argument.

NWith x y                                   ~  with x; y
NAssert !r !r

Checks that the first argument is a predicate that is true before evaluating the second argument.

NAssert x y                                 ~  assert x; y
NSynHole !VarName

Syntactic hole.

See https://github.com/haskell-nix/hnix/issues/197 for context.

NSynHole "x"                                ~  ^x

Instances

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

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 #

Eq1 NExprF Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

Ord1 NExprF Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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 #

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 #

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

Functor NExprF Source # 
Instance details

Defined in Nix.Expr.Types

Methods

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

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

Binary NExprLoc Source # 
Instance details

Defined in Nix.Expr.Types.Annotated

Methods

put :: NExprLoc -> Put #

get :: Get NExprLoc #

putList :: [NExprLoc] -> Put #

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 #

ToExpr NExpr Source # 
Instance details

Defined in Nix.TH

Methods

toExpr :: NExpr -> NExpr Source #

Serialise NExpr Source # 
Instance details

Defined in Nix.Expr.Types

Serialise NExprLoc Source # 
Instance details

Defined in Nix.Expr.Types.Annotated

Generic1 NExprF Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

type Rep1 NExprF :: k -> Type #

Methods

from1 :: forall (a :: k). NExprF a -> Rep1 NExprF a #

to1 :: forall (a :: k). Rep1 NExprF a -> NExprF a #

Lift NExpr Source # 
Instance details

Defined in Nix.Expr.Types

Methods

lift :: Quote m => NExpr -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => NExpr -> Code m NExpr #

Convertible e t f m => ToValue () m (NExprF (NValue t f m)) Source # 
Instance details

Defined in Nix.Convert

Methods

toValue :: () -> m (NExprF (NValue t f m)) Source #

Convertible e t f m => ToValue Bool m (NExprF (NValue t f m)) Source # 
Instance details

Defined in Nix.Convert

Methods

toValue :: Bool -> m (NExprF (NValue t f m)) Source #

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

Defined in Nix.Expr.Types

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

Defined in Nix.Expr.Types

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 :: forall r0 r'. (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) #

Generic (NExprF r) Source # 
Instance details

Defined in Nix.Expr.Types

Associated Types

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

Methods

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

to :: Rep (NExprF r) x -> 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 #

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

Defined in Nix.Expr.Types

Methods

put :: NExprF r -> Put #

get :: Get (NExprF r) #

putList :: [NExprF r] -> Put #

Binary r => Binary (NExprLocF r) Source # 
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 -> () #

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

Defined in Nix.Expr.Types

Methods

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

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

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 #

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

Defined in Nix.Expr.Types

Methods

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

hash :: NExprF r -> Int #

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

Defined in Nix.Expr.Types

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

Defined in Nix.Expr.Types.Annotated

Monad m => MonadState (HashMap Path NExprLoc, HashMap Text Text) (StandardTF r m) Source # 
Instance details

Defined in Nix.Standard

type Rep1 NExprF Source # 
Instance details

Defined in Nix.Expr.Types

type Rep1 NExprF = D1 ('MetaData "NExprF" "Nix.Expr.Types" "hnix-0.17.0-8saIMbclRB9HPH4JCEpCXn" '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) (Rec0 Recursivity) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) ([] :.: Rec1 Binding)) :+: C1 ('MetaCons "NLiteralPath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Path))) :+: (C1 ('MetaCons "NEnvPath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Path)) :+: (C1 ('MetaCons "NApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1) :+: 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) (Rec1 Maybe) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (NonEmpty :.: Rec1 NKeyName)))) :+: (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) :+: C1 ('MetaCons "NSynHole" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarName)))))))
type Rep (NExprF r) Source # 
Instance details

Defined in Nix.Expr.Types

type Rep (NExprF r) = D1 ('MetaData "NExprF" "Nix.Expr.Types" "hnix-0.17.0-8saIMbclRB9HPH4JCEpCXn" '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 Recursivity) :*: 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 Path))) :+: (C1 ('MetaCons "NEnvPath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Path)) :+: (C1 ('MetaCons "NApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 r) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 r)) :+: 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 (Maybe r)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 r) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NAttrPath 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)) :+: C1 ('MetaCons "NSynHole" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarName)))))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

type NExpr = Fix NExprF Source #

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

_NConstant :: Applicative f => (NAtom -> f NAtom) -> NExprF r -> f (NExprF r) Source #

_NStr :: Applicative f => (NString r -> f (NString r)) -> NExprF r -> f (NExprF r) Source #

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

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

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

_NLiteralPath :: Applicative f => (Path -> f Path) -> NExprF r -> f (NExprF r) Source #

_NEnvPath :: Applicative f => (Path -> f Path) -> NExprF r -> f (NExprF r) Source #

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

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

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

_NSelect :: Applicative f => ((Maybe r, r, NAttrPath r) -> f (Maybe r, r, NAttrPath r)) -> NExprF r -> f (NExprF r) Source #

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

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

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

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

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

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

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

hashAt :: Functor f => VarName -> (Maybe v -> f (Maybe v)) -> AttrSet v -> f (AttrSet v) Source #

paramName :: Params r -> Maybe VarName Source #

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

ekey :: forall ann g. NExprAnn ann g => NonEmpty VarName -> NSourcePos -> Lens' (Fix g) (Maybe (Fix g)) Source #

data SourcePos #

The data type SourcePos represents source positions. It contains the name of the source file, a line number, and a column number. Source line and column positions change intensively during parsing, so we need to make them strict to avoid memory leaks.

Constructors

SourcePos FilePath !Pos !Pos 

Instances

Instances details
Data SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

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

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

toConstr :: SourcePos -> Constr #

dataTypeOf :: SourcePos -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep SourcePos :: Type -> Type #

Read SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Show SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

NFData SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

rnf :: SourcePos -> () #

Eq SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Ord SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

type Rep SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

type Rep SourcePos = D1 ('MetaData "SourcePos" "Text.Megaparsec.Pos" "megaparsec-9.5.0-nV6NFlDOdsDHucVPlnquI" 'False) (C1 ('MetaCons "SourcePos" 'PrefixI 'True) (S1 ('MetaSel ('Just "sourceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: (S1 ('MetaSel ('Just "sourceLine") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos) :*: S1 ('MetaSel ('Just "sourceColumn") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos))))

unPos :: Pos -> Int #

Extract Int from Pos.

Since: megaparsec-6.0.0

mkPos :: Int -> Pos #

Construction of Pos from Int. The function throws InvalidPosException when given a non-positive argument.

Since: megaparsec-6.0.0