| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Nix.Value
Description
The core of the type system, Nix language values
Synopsis
- data NValueF p m r- = NVConstantF NAtom
- | NVStrF NixString
- | NVPathF FilePath
- | NVListF [r]
- | NVSetF (AttrSet r) (AttrSet SourcePos)
- | NVClosureF (Params ()) (p -> m r)
- | NVBuiltinF Text (p -> m r)
 
- sequenceNValueF :: (Functor n, Monad m, Applicative n) => (forall x. n x -> m x) -> NValueF p m (n a) -> n (NValueF p m a)
- bindNValueF :: (Monad m, Monad n) => (forall x. n x -> m x) -> (a -> n b) -> NValueF p m a -> n (NValueF p m b)
- liftNValueF :: (MonadTrans u, Monad m) => NValueF p m a -> NValueF p (u m) a
- unliftNValueF :: (MonadTrans u, Monad m) => (forall x. u m x -> m x) -> NValueF p (u m) a -> NValueF p m a
- hoistNValueF :: (forall x. m x -> n x) -> NValueF p m a -> NValueF p n a
- newtype NValue' t f m a = NValue' {}
- sequenceNValue' :: (Functor n, Traversable f, Monad m, Applicative n) => (forall x. n x -> m x) -> NValue' t f m (n a) -> n (NValue' t f m a)
- lmapNValueF :: Functor m => (b -> a) -> NValueF a m r -> NValueF b m r
- iterNValue' :: forall t f m a r. MonadDataContext f m => (a -> (NValue' t f m a -> r) -> r) -> (NValue' t f m r -> r) -> NValue' t f m a -> r
- hoistNValue' :: (Functor m, Functor n, Functor f) => (forall x. n x -> m x) -> (forall x. m x -> n x) -> NValue' t f m a -> NValue' t f n a
- bindNValue' :: (Traversable f, Monad m, Monad n) => (forall x. n x -> m x) -> (a -> n b) -> NValue' t f m a -> n (NValue' t f m b)
- liftNValue' :: (MonadTrans u, Monad m, Functor (u m), Functor f) => (forall x. u m x -> m x) -> NValue' t f m a -> NValue' t f (u m) a
- unliftNValue' :: (MonadTrans u, Monad m, Functor (u m), Functor f) => (forall x. u m x -> m x) -> NValue' t f (u m) a -> NValue' t f m a
- nvConstant' :: Applicative f => NAtom -> NValue' t f m r
- nvStr' :: Applicative f => NixString -> NValue' t f m r
- nvPath' :: Applicative f => FilePath -> NValue' t f m r
- nvList' :: Applicative f => [r] -> NValue' t f m r
- nvSet' :: Applicative f => AttrSet SourcePos -> AttrSet r -> NValue' t f m r
- nvClosure' :: (Applicative f, Functor m) => Params () -> (NValue t f m -> m r) -> NValue' t f m r
- nvBuiltin' :: (Applicative f, Functor m) => Text -> (NValue t f m -> m r) -> NValue' t f m r
- pattern NVConstant' :: Comonad w => NAtom -> NValue' t w m a
- pattern NVStr' :: Comonad w => NixString -> NValue' t w m a
- pattern NVPath' :: Comonad w => FilePath -> NValue' t w m a
- pattern NVList' :: forall w t m a. Comonad w => [a] -> NValue' t w m a
- pattern NVSet' :: forall w t m a. Comonad w => AttrSet a -> AttrSet SourcePos -> NValue' t w m a
- pattern NVClosure' :: Comonad w => Params () -> (NValue t w m -> m a) -> NValue' t w m a
- pattern NVBuiltin' :: Comonad w => Text -> (NValue t w m -> m a) -> NValue' t w m a
- type NValue t f m = Free (NValue' t f m) t
- iterNValue :: forall t f m r. MonadDataContext f m => ((Free (NValue' t f m) t -> r) -> t -> r) -> (NValue' t f m r -> r) -> Free (NValue' t f m) t -> r
- iterNValueByDiscardWith :: MonadDataContext f m => r -> (NValue' t f m r -> r) -> Free (NValue' t f m) t -> r
- iterNValueM :: (MonadDataContext f m, Monad n) => (forall x. n x -> m x) -> ((NValue t f m -> n r) -> t -> n r) -> (NValue' t f m (n r) -> n r) -> NValue t f m -> n r
- hoistNValue :: (Functor m, Functor n, Functor f) => (forall x. n x -> m x) -> (forall x. m x -> n x) -> NValue t f m -> NValue t f n
- liftNValue :: (MonadTrans u, Monad m, Functor (u m), Functor f) => (forall x. u m x -> m x) -> NValue t f m -> NValue t f (u m)
- unliftNValue :: (MonadTrans u, Monad m, Functor (u m), Functor f) => (forall x. u m x -> m x) -> NValue t f (u m) -> NValue t f m
- nvThunk :: Applicative f => t -> NValue t f m
- nvConstant :: Applicative f => NAtom -> NValue t f m
- nvStr :: Applicative f => NixString -> NValue t f m
- nvStrWithoutContext :: Applicative f => Text -> NValue t f m
- nvPath :: Applicative f => FilePath -> NValue t f m
- nvList :: Applicative f => [NValue t f m] -> NValue t f m
- nvSet :: Applicative f => AttrSet SourcePos -> AttrSet (NValue t f m) -> NValue t f m
- nvClosure :: (Applicative f, Functor m) => Params () -> (NValue t f m -> m (NValue t f m)) -> NValue t f m
- nvBuiltin :: (Applicative f, Functor m) => Text -> (NValue t f m -> m (NValue t f m)) -> NValue t f m
- builtin :: forall m f t. (MonadThunk t m (NValue t f m), MonadDataContext f m) => Text -> (NValue t f m -> m (NValue t f m)) -> m (NValue t f m)
- builtin2 :: (MonadThunk t m (NValue t f m), MonadDataContext f m) => Text -> (NValue t f m -> NValue t f m -> m (NValue t f m)) -> m (NValue t f m)
- builtin3 :: (MonadThunk t m (NValue t f m), MonadDataContext f m) => Text -> (NValue t f m -> NValue t f m -> NValue t f m -> m (NValue t f m)) -> m (NValue t f m)
- pattern NVThunk :: forall f a. a -> Free f a
- pattern NVValue :: f (Free f a) -> Free f a
- pattern NVConstant :: forall (w :: Type -> Type) t (m :: Type -> Type) a. Comonad w => NAtom -> Free (NValue' t w m) a
- pattern NVStr :: forall (w :: Type -> Type) t (m :: Type -> Type) a. Comonad w => NixString -> Free (NValue' t w m) a
- pattern NVPath :: forall (w :: Type -> Type) t (m :: Type -> Type) a. Comonad w => FilePath -> Free (NValue' t w m) a
- pattern NVList :: forall (w :: Type -> Type) t (m :: Type -> Type) a. Comonad w => [Free (NValue' t w m) a] -> Free (NValue' t w m) a
- pattern NVSet :: forall (w :: Type -> Type) t (m :: Type -> Type) a. Comonad w => AttrSet (Free (NValue' t w m) a) -> AttrSet SourcePos -> Free (NValue' t w m) a
- pattern NVClosure :: forall (w :: Type -> Type) t m a. Comonad w => Params () -> (NValue t w m -> m (Free (NValue' t w m) a)) -> Free (NValue' t w m) a
- pattern NVBuiltin :: forall (w :: Type -> Type) t m a. Comonad w => Text -> (NValue t w m -> m (Free (NValue' t w m) a)) -> Free (NValue' t w m) a
- data TStringContext
- data ValueType
- valueType :: NValueF a m r -> ValueType
- describeValue :: ValueType -> Text
- showValueType :: (MonadThunk t m (NValue t f m), Comonad f) => NValue t f m -> m Text
- data ValueFrame t f m- = ForcingThunk t
- | ConcerningValue (NValue t f m)
- | Comparison (NValue t f m) (NValue t f m)
- | Addition (NValue t f m) (NValue t f m)
- | Multiplication (NValue t f m) (NValue t f m)
- | Division (NValue t f m) (NValue t f m)
- | Coercion ValueType ValueType
- | CoercionToJson (NValue t f m)
- | CoercionFromJson Value
- | Expectation ValueType (NValue t f m)
 
- type MonadDataContext f (m :: Type -> Type) = (Comonad f, Applicative f, Traversable f, Monad m)
- type MonadDataErrorContext t f m = (Show t, Typeable t, Typeable m, Typeable f, MonadDataContext f m, MonadFail m)
- _NVBuiltinF :: Applicative f => ((Text, p -> m r) -> f (Text, p -> m r)) -> NValueF p m r -> f (NValueF p m r)
- _NVClosureF :: Applicative f => ((Params (), p -> m r) -> f (Params (), p -> m r)) -> NValueF p m r -> f (NValueF p m r)
- _NVSetF :: forall f r p (m :: Type -> Type). Applicative f => ((AttrSet r, AttrSet SourcePos) -> f (AttrSet r, AttrSet SourcePos)) -> NValueF p m r -> f (NValueF p m r)
- _NVListF :: forall f r p (m :: Type -> Type). Applicative f => ([r] -> f [r]) -> NValueF p m r -> f (NValueF p m r)
- _NVPathF :: forall f p (m :: Type -> Type) r. Applicative f => (FilePath -> f FilePath) -> NValueF p m r -> f (NValueF p m r)
- _NVStrF :: forall f p (m :: Type -> Type) r. Applicative f => (NixString -> f NixString) -> NValueF p m r -> f (NValueF p m r)
- _NVConstantF :: forall f p (m :: Type -> Type) r. Applicative f => (NAtom -> f NAtom) -> NValueF p m r -> f (NValueF p m r)
- nValue :: forall f1 f2 t1 (m1 :: Type -> Type) a1 f3 t2 (m2 :: Type -> Type) a2. Functor f1 => (f2 (NValueF (NValue t1 f2 m1) m1 a1) -> f1 (f3 (NValueF (NValue t2 f3 m2) m2 a2))) -> NValue' t1 f2 m1 a1 -> f1 (NValue' t2 f3 m2 a2)
- key :: (Traversable f, Applicative g) => VarName -> LensLike' g (NValue' t f m a) (Maybe a)
NValueF: Base functor (F)
An NValueF p m r represents all the possible types of Nix values.
Is is the base functor to form the Free monad of nix expressions.
   The parameter r represents Nix values in their final form (NValue).
   The parameter p represents exactly the same type, but is kept separate
   or it would prevent NValueF from being a proper functor.
   It is intended to be hard-coded to the same final type as r.
   m is the monad in which evaluations will run.
An NValue' t f m a is a magic layer between NValueF and the Free monad construction.
It fixes the p parameter of NValueF to the final NValue type, making the
   definition of NValue' and NValue depend on each other in a recursive
   fashion.
It also introduces a f parameter for a custom functor that can be used
   to wrap each intermediate value in the reduced expression tree.
   This is where expression evaluations can store annotations and other
   useful information.
t is not really used here, but is needed to type the (NValue t f m)
   used to tie the knot of the p parameter in the inner NValueF.
a is will be an `NValue t f m` when NValue' functor is turned into a
   Free monad.
'NValue t f m' is the most reduced form of a NExpr after evaluation is
   completed. It is a layer cake of NValueF base values, wrapped in the f
   functor and into the Free recursive construction.
Concretely, an NValue t f m can either be a thunk, representing a value
   yet to be evaluated (Pure t), or a know value in WHNF
   (Free (NValue' t f m (NValue t f m))) = (Free (f (NValueF NValue m NValue))
   That is, a base value type, wrapped into the generic f
   functor, and based on other NValue's, which can in turn be either thunks,
   or more already WHNF evaluated values.
As an example, the value `[1]` will be represented as
Free (f (NVListF [ (Free (f (NVConstantF (NInt 1)))) ]))
Should this 1 be a laziy and yet unevaluated value, it would be represented as
Free (f (NVListF [ (Pure t) ]))
Where the t is evaluator dependant, and should contain anough information
   to be evaluated to an NValue when needed. demand of force are used to
   turn a potential thunk into a `m (NValue t f m)`.
Of course, trees can be much bigger.
The number of layers and type aliases for similar things is huge, so this module provides ViewPatterns for each NValueF constructor.
For example, the pattern NVStr' ns matches a NValue' containing an NVStrF, and bind that NVStrF to ns, ignoring the f functor inside. Similarly, the pattern NVStr ns (without prime mark) will match the inner NVstrF value inside an NValue. Of course, the patterns are declined for all the NValueF constructors. The non primed version also has an NVThunk t pattern to account for the possibility of an NValue to no be fully evaluated yet, as opposed to an NValue'.
Constructors
| NVConstantF NAtom | |
| NVStrF NixString | A string has a value and a context, which can be used to record what a string has been build from | 
| NVPathF FilePath | |
| NVListF [r] | |
| NVSetF (AttrSet r) (AttrSet SourcePos) | |
| NVClosureF (Params ()) (p -> m r) | A function is a closed set of parameters representing the "call signature", used at application time to check the type of arguments passed to the function. Since it supports default values which may depend on other values within the final argument set, this dependency is represented as a set of pending evaluations. The arguments are finally normalized into a set which is passed to the function. Note that 'm r' is being used here because effectively a function and its set of default arguments is "never fully evaluated". This enforces in the type that it must be re-evaluated for each call. | 
| NVBuiltinF Text (p -> m r) | A builtin function is itself already in normal form. Also, it may or may not choose to evaluate its argument in the production of a result. | 
Instances
Eq1
Show
Foldable
Traversable
sequenceNValueF :: (Functor n, Monad m, Applicative n) => (forall x. n x -> m x) -> NValueF p m (n a) -> n (NValueF p m a) Source #
sequence
Monad
bindNValueF :: (Monad m, Monad n) => (forall x. n x -> m x) -> (a -> n b) -> NValueF p m a -> n (NValueF p m b) Source #
bind
MonadTrans
liftNValueF :: (MonadTrans u, Monad m) => NValueF p m a -> NValueF p (u m) a Source #
lift
MonadTransUnlift
unliftNValueF :: (MonadTrans u, Monad m) => (forall x. u m x -> m x) -> NValueF p (u m) a -> NValueF p m a Source #
unlift
Utils
hoistNValueF :: (forall x. m x -> n x) -> NValueF p m a -> NValueF p n a Source #
Back & forth hoisting in the monad stack
NValue': forming the (F(A))
newtype NValue' t f m a Source #
At the time of constructor, the expected arguments to closures are values that may contain thunks. The type of such thunks are fixed at that time.
Constructors
| NValue' | |
Instances
Show1
Traversable
sequenceNValue' :: (Functor n, Traversable f, Monad m, Applicative n) => (forall x. n x -> m x) -> NValue' t f m (n a) -> n (NValue' t f m a) Source #
sequence
Profunctor
Free
iterNValue' :: forall t f m a r. MonadDataContext f m => (a -> (NValue' t f m a -> r) -> r) -> (NValue' t f m r -> r) -> NValue' t f m a -> r Source #
iter
Utils
hoistNValue' :: (Functor m, Functor n, Functor f) => (forall x. n x -> m x) -> (forall x. m x -> n x) -> NValue' t f m a -> NValue' t f n a Source #
hoistFree: Back & forth hoisting in the monad stack
Monad
bindNValue' :: (Traversable f, Monad m, Monad n) => (forall x. n x -> m x) -> (a -> n b) -> NValue' t f m a -> n (NValue' t f m b) Source #
bind
MonadTrans
liftNValue' :: (MonadTrans u, Monad m, Functor (u m), Functor f) => (forall x. u m x -> m x) -> NValue' t f m a -> NValue' t f (u m) a Source #
lift
MonadTransUnlift
unliftNValue' :: (MonadTrans u, Monad m, Functor (u m), Functor f) => (forall x. u m x -> m x) -> NValue' t f (u m) a -> NValue' t f m a Source #
unlift
Bijective Hask subcategory - NValue'
F: Hask subcategory → NValue'
F: Hask → NValue'
Since Haskell and Nix are both recursive purely functional lazy languages. And since recursion-schemes. It is possible to create a direct functor between the Hask and Nix categories. Or make Nix a DLS language of Haskell, embed it into a Hask, if you would like. Of course, we mean: pick Hask subcategory and form Nix Category from it. Take subcategory of Hask, and by applying functor to it - have a Nix Category. Wouldn't it be cool and fast?
In fact - it is what we do here.
Since it is a proper way of scientific implementation, we would eventually form a lawful functor.
Facts of which are seen below:
nvConstant' :: Applicative f => NAtom -> NValue' t f m r Source #
Haskell constant to the Nix constant,
nvStr' :: Applicative f => NixString -> NValue' t f m r Source #
Haskell text & context to the Nix text & context,
nvList' :: Applicative f => [r] -> NValue' t f m r Source #
Haskell [] to the Nix [],
nvSet' :: Applicative f => AttrSet SourcePos -> AttrSet r -> NValue' t f m r Source #
Haskell key-value to the Nix key-value,
nvClosure' :: (Applicative f, Functor m) => Params () -> (NValue t f m -> m r) -> NValue' t f m r Source #
Haskell closure to the Nix closure,
nvBuiltin' :: (Applicative f, Functor m) => Text -> (NValue t f m -> m r) -> NValue' t f m r Source #
Haskell functions to the Nix functions!
F: NValue -> NValue'
pattern NVConstant' :: Comonad w => NAtom -> NValue' t w m a Source #
Module pattens use language PatternSynonyms: unidirectional synonyms (<-),
 and ViewPatterns: (->) at the same time.
 ViewPatterns Control.Comonad.extract extracts
 from the NValue (Free (NValueF a))
 the NValueF a. Which is NValueF p m r. Since it extracted from the
 NValue, which is formed by \( (F a -> a) F a \) in the first place.
 So NValueF p m r which is extracted here, internally holds the next NValue.
pattern NVSet' :: forall w t m a. Comonad w => AttrSet a -> AttrSet SourcePos -> NValue' t w m a Source #
NValue: Nix language values
type NValue t f m = Free (NValue' t f m) t Source #
'NValue t f m' is a value in head normal form (it means only the tip of it has been evaluated to the normal form, while the rest of it is in lazy not evaluated form (thunk), this known as WHNF).
An action 'm (NValue t f m)' is a pending evaluation that has yet to be performed.
An t is either:
     * a pending evaluation.
     * a value in head normal form.
The Free structure is used here to represent the possibility that
   Nix language allows cycles that may appear during normalization.
Free
iterNValue :: forall t f m r. MonadDataContext f m => ((Free (NValue' t f m) t -> r) -> t -> r) -> (NValue' t f m r -> r) -> Free (NValue' t f m) t -> r Source #
HOF of iter from Free
iterNValueByDiscardWith :: MonadDataContext f m => r -> (NValue' t f m r -> r) -> Free (NValue' t f m) t -> r Source #
iterNValueM :: (MonadDataContext f m, Monad n) => (forall x. n x -> m x) -> ((NValue t f m -> n r) -> t -> n r) -> (NValue' t f m (n r) -> n r) -> NValue t f m -> n r Source #
HOF of iterM from Free
Utils
hoistNValue :: (Functor m, Functor n, Functor f) => (forall x. n x -> m x) -> (forall x. m x -> n x) -> NValue t f m -> NValue t f n Source #
hoistFree, Back & forth hoisting in the monad stack
MonadTrans
liftNValue :: (MonadTrans u, Monad m, Functor (u m), Functor f) => (forall x. u m x -> m x) -> NValue t f m -> NValue t f (u m) Source #
lift
MonadTransUnlift
unliftNValue :: (MonadTrans u, Monad m, Functor (u m), Functor f) => (forall x. u m x -> m x) -> NValue t f (u m) -> NValue t f m Source #
unlift
Methods F: Hask → NValue
F: Hask → NValue
The morphisms of the functor Hask → NValue.
 Continuation of the mantra: Nix.Value
nvThunk :: Applicative f => t -> NValue t f m Source #
Life of a Haskell thunk to the life of a Nix thunk,
nvConstant :: Applicative f => NAtom -> NValue t f m Source #
Life of a Haskell constant to the life of a Nix constant,
nvStr :: Applicative f => NixString -> NValue t f m Source #
Life of a Haskell sting & context to the life of a Nix string & context,
nvStrWithoutContext :: Applicative f => Text -> NValue t f m Source #
nvPath :: Applicative f => FilePath -> NValue t f m Source #
Life of a Haskell FilePath to the life of a Nix path
nvClosure :: (Applicative f, Functor m) => Params () -> (NValue t f m -> m (NValue t f m)) -> NValue t f m Source #
nvBuiltin :: (Applicative f, Functor m) => Text -> (NValue t f m -> m (NValue t f m)) -> NValue t f m Source #
builtin :: forall m f t. (MonadThunk t m (NValue t f m), MonadDataContext f m) => Text -> (NValue t f m -> m (NValue t f m)) -> m (NValue t f m) Source #
builtin2 :: (MonadThunk t m (NValue t f m), MonadDataContext f m) => Text -> (NValue t f m -> NValue t f m -> m (NValue t f m)) -> m (NValue t f m) Source #
builtin3 :: (MonadThunk t m (NValue t f m), MonadDataContext f m) => Text -> (NValue t f m -> NValue t f m -> NValue t f m -> m (NValue t f m)) -> m (NValue t f m) Source #
F: Evaluation -> NValue
pattern NVConstant :: forall (w :: Type -> Type) t (m :: Type -> Type) a. Comonad w => NAtom -> Free (NValue' t w m) a Source #
pattern NVStr :: forall (w :: Type -> Type) t (m :: Type -> Type) a. Comonad w => NixString -> Free (NValue' t w m) a Source #
pattern NVPath :: forall (w :: Type -> Type) t (m :: Type -> Type) a. Comonad w => FilePath -> Free (NValue' t w m) a Source #
pattern NVList :: forall (w :: Type -> Type) t (m :: Type -> Type) a. Comonad w => [Free (NValue' t w m) a] -> Free (NValue' t w m) a Source #
pattern NVSet :: forall (w :: Type -> Type) t (m :: Type -> Type) a. Comonad w => AttrSet (Free (NValue' t w m) a) -> AttrSet SourcePos -> Free (NValue' t w m) a Source #
pattern NVClosure :: forall (w :: Type -> Type) t m a. Comonad w => Params () -> (NValue t w m -> m (Free (NValue' t w m) a)) -> Free (NValue' t w m) a Source #
pattern NVBuiltin :: forall (w :: Type -> Type) t m a. Comonad w => Text -> (NValue t w m -> m (Free (NValue' t w m) a)) -> Free (NValue' t w m) a Source #
TStringContext
data TStringContext Source #
Constructors
| NoContext | |
| HasContext | 
Instances
| Show TStringContext Source # | |
| Defined in Nix.Value Methods showsPrec :: Int -> TStringContext -> ShowS # show :: TStringContext -> String # showList :: [TStringContext] -> ShowS # | |
ValueType
describeValue :: ValueType -> Text Source #
Describe type value
showValueType :: (MonadThunk t m (NValue t f m), Comonad f) => NValue t f m -> m Text Source #
ValueFrame
data ValueFrame t f m Source #
Constructors
| ForcingThunk t | |
| ConcerningValue (NValue t f m) | |
| Comparison (NValue t f m) (NValue t f m) | |
| Addition (NValue t f m) (NValue t f m) | |
| Multiplication (NValue t f m) (NValue t f m) | |
| Division (NValue t f m) (NValue t f m) | |
| Coercion ValueType ValueType | |
| CoercionToJson (NValue t f m) | |
| CoercionFromJson Value | |
| Expectation ValueType (NValue t f m) | 
Instances
| (Comonad f, Show t) => Show (ValueFrame t f m) Source # | |
| Defined in Nix.Value Methods showsPrec :: Int -> ValueFrame t f m -> ShowS # show :: ValueFrame t f m -> String # showList :: [ValueFrame t f m] -> ShowS # | |
| MonadDataErrorContext t f m => Exception (ValueFrame t f m) Source # | |
| Defined in Nix.Value Methods toException :: ValueFrame t f m -> SomeException # fromException :: SomeException -> Maybe (ValueFrame t f m) # displayException :: ValueFrame t f m -> String # | |
MonadDataContext
type MonadDataContext f (m :: Type -> Type) = (Comonad f, Applicative f, Traversable f, Monad m) Source #
MonadDataErrorContext
type MonadDataErrorContext t f m = (Show t, Typeable t, Typeable m, Typeable f, MonadDataContext f m, MonadFail m) Source #
instance Eq1 NValue'
NValue' traversals, getter & setters
_NVBuiltinF :: Applicative f => ((Text, p -> m r) -> f (Text, p -> m r)) -> NValueF p m r -> f (NValueF p m r) Source #
Make traversals for Nix traversable structures.
_NVClosureF :: Applicative f => ((Params (), p -> m r) -> f (Params (), p -> m r)) -> NValueF p m r -> f (NValueF p m r) Source #
_NVSetF :: forall f r p (m :: Type -> Type). Applicative f => ((AttrSet r, AttrSet SourcePos) -> f (AttrSet r, AttrSet SourcePos)) -> NValueF p m r -> f (NValueF p m r) Source #
_NVListF :: forall f r p (m :: Type -> Type). Applicative f => ([r] -> f [r]) -> NValueF p m r -> f (NValueF p m r) Source #
_NVPathF :: forall f p (m :: Type -> Type) r. Applicative f => (FilePath -> f FilePath) -> NValueF p m r -> f (NValueF p m r) Source #
_NVStrF :: forall f p (m :: Type -> Type) r. Applicative f => (NixString -> f NixString) -> NValueF p m r -> f (NValueF p m r) Source #
_NVConstantF :: forall f p (m :: Type -> Type) r. Applicative f => (NAtom -> f NAtom) -> NValueF p m r -> f (NValueF p m r) Source #
nValue :: forall f1 f2 t1 (m1 :: Type -> Type) a1 f3 t2 (m2 :: Type -> Type) a2. Functor f1 => (f2 (NValueF (NValue t1 f2 m1) m1 a1) -> f1 (f3 (NValueF (NValue t2 f3 m2) m2 a2))) -> NValue' t1 f2 m1 a1 -> f1 (NValue' t2 f3 m2 a2) Source #
Make lenses for the Nix values
key :: (Traversable f, Applicative g) => VarName -> LensLike' g (NValue' t f m a) (Maybe a) Source #
Lens-generated getter-setter function for a traversable NValue' key-val structures.
   Nix value analogue of the Data-Aeson-Lens:key :: AsValue t => Text -> Traversal' t Value.