Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 String (p -> m r)
- lmapNValueF :: Functor m => (b -> a) -> NValueF a m r -> NValueF b m r
- hoistNValueF :: (forall x. m x -> n x) -> NValueF p m a -> NValueF p n a
- 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
- type MonadDataContext f (m :: * -> *) = (Comonad f, Applicative f, Traversable f, Monad m)
- 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)
- 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)
- 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
- 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
- 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
- type NValue t f m = Free (NValue' t f m) t
- 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
- iterNValue :: forall t f m r. MonadDataContext f m => (t -> (NValue t f m -> r) -> r) -> (NValue' t f m r -> r) -> NValue t f m -> r
- iterNValueM :: (MonadDataContext f m, Monad n) => (forall x. n x -> m x) -> (t -> (NValue t f m -> n r) -> n r) -> (NValue' t f m (n r) -> n r) -> NValue t f m -> n r
- pattern NVThunk :: forall f a. a -> Free f a
- nvThunk :: Applicative f => t -> NValue t f m
- pattern NVConstant' :: Comonad w => NAtom -> NValue' t w m a
- pattern NVConstant :: forall (w :: Type -> Type) t (m :: Type -> Type) a. Comonad w => NAtom -> Free (NValue' t w m) a
- nvConstant' :: Applicative f => NAtom -> NValue' t f m r
- nvConstant :: Applicative f => NAtom -> NValue t f m
- pattern NVStr' :: Comonad w => NixString -> 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
- nvStr' :: Applicative f => NixString -> NValue' t f m r
- nvStr :: Applicative f => NixString -> NValue t f m
- pattern NVPath' :: Comonad w => FilePath -> 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
- nvPath' :: Applicative f => FilePath -> NValue' t f m r
- nvPath :: Applicative f => FilePath -> NValue t f m
- pattern NVList' :: forall w t m a. Comonad w => [a] -> 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
- nvList' :: Applicative f => [r] -> NValue' t f m r
- nvList :: Applicative f => [NValue t f m] -> NValue t f m
- pattern NVSet' :: forall w t m a. Comonad w => AttrSet a -> AttrSet SourcePos -> 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
- nvSet' :: Applicative f => HashMap Text r -> HashMap Text SourcePos -> NValue' t f m r
- nvSet :: Applicative f => HashMap Text (NValue t f m) -> HashMap Text SourcePos -> NValue t f m
- pattern NVClosure' :: Comonad w => Params () -> (NValue t w m -> m a) -> 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
- nvClosure' :: (Applicative f, Functor m) => Params () -> (NValue t f m -> m r) -> NValue' t f m r
- nvClosure :: (Applicative f, Functor m) => Params () -> (NValue t f m -> m (NValue t f m)) -> NValue t f m
- pattern NVBuiltin' :: Comonad w => String -> (NValue t w m -> m a) -> NValue' t w m a
- pattern NVBuiltin :: forall (w :: Type -> Type) t m a. Comonad w => String -> (NValue t w m -> m (Free (NValue' t w m) a)) -> Free (NValue' t w m) a
- nvBuiltin' :: (Applicative f, Functor m) => String -> (NValue t f m -> m r) -> NValue' t f m r
- nvBuiltin :: (Applicative f, Functor m) => String -> (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) => String -> (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) => String -> (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) => String -> (NValue t f m -> NValue t f m -> NValue t f m -> m (NValue t f m)) -> m (NValue t f m)
- data TStringContext
- data ValueType
- valueType :: NValueF a m r -> ValueType
- describeValue :: ValueType -> String
- showValueType :: (MonadThunk t m (NValue t f m), Comonad f) => NValue t f m -> m String
- 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 MonadDataErrorContext t f m = (Show t, Typeable t, Typeable m, Typeable f, MonadDataContext f m)
- _NVBuiltinF :: Applicative f => ((String, p -> m r) -> f (String, 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)
Documentation
An NValue
is the most reduced form of an NExpr
after evaluation is
completed. s
is related to the type of errors that might occur during
construction or use of a value.
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 String (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
hoistNValueF :: (forall x. m x -> n x) -> NValueF p m a -> NValueF p n a Source #
sequenceNValueF :: (Functor n, Monad m, Applicative n) => (forall x. n x -> m x) -> NValueF p m (n a) -> n (NValueF p m a) Source #
bindNValueF :: (Monad m, Monad n) => (forall x. n x -> m x) -> (a -> n b) -> NValueF p m a -> n (NValueF p m b) Source #
liftNValueF :: (MonadTrans u, Monad m) => NValueF p m a -> NValueF p (u m) a Source #
unliftNValueF :: (MonadTrans u, Monad m) => (forall x. u m x -> m x) -> NValueF p (u m) a -> NValueF p m a Source #
type MonadDataContext f (m :: * -> *) = (Comonad f, Applicative f, Traversable f, Monad m) Source #
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.
Instances
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 #
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 #
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 #
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 #
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 #
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 #
type NValue t f m = Free (NValue' t f m) t Source #
An NValueNF
is a fully evaluated value in normal form. An 'NValue f t m' is
a value in head normal form, where only the "top layer" has been
evaluated. An action of type 'm (NValue f t m)' is a pending evaluation that
has yet to be performed. An t
is either a pending evaluation, or
a value in head normal form. A NThunkSet
is a set of mappings from keys
to thunks.
The Free
structure is used here to represent the possibility that
cycles may appear during normalization.
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 #
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 #
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 #
iterNValue :: forall t f m r. MonadDataContext f m => (t -> (NValue t f m -> r) -> r) -> (NValue' t f m r -> r) -> NValue t f m -> r Source #
iterNValueM :: (MonadDataContext f m, Monad n) => (forall x. n x -> m x) -> (t -> (NValue t f m -> n r) -> n r) -> (NValue' t f m (n r) -> n r) -> NValue t f m -> n r Source #
nvThunk :: Applicative f => t -> NValue t f m Source #
pattern NVConstant :: forall (w :: Type -> Type) t (m :: Type -> Type) a. Comonad w => NAtom -> Free (NValue' t w m) a Source #
nvConstant' :: Applicative f => NAtom -> NValue' t f m r Source #
nvConstant :: Applicative f => NAtom -> NValue t f m 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 #
nvList' :: Applicative f => [r] -> NValue' t f m r Source #
pattern NVSet' :: forall w t m a. Comonad w => AttrSet a -> AttrSet SourcePos -> 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 #
nvSet :: Applicative f => HashMap Text (NValue t f m) -> HashMap Text SourcePos -> NValue t f m 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 #
nvClosure' :: (Applicative f, Functor m) => Params () -> (NValue t f m -> m r) -> NValue' t f m r Source #
nvClosure :: (Applicative f, Functor m) => Params () -> (NValue t f m -> m (NValue t f m)) -> NValue t f m Source #
pattern NVBuiltin :: forall (w :: Type -> Type) t m a. Comonad w => String -> (NValue t w m -> m (Free (NValue' t w m) a)) -> Free (NValue' t w m) a Source #
nvBuiltin' :: (Applicative f, Functor m) => String -> (NValue t f m -> m r) -> NValue' t f m r Source #
nvBuiltin :: (Applicative f, Functor m) => String -> (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) => String -> (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) => String -> (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) => String -> (NValue t f m -> NValue t f m -> NValue t f m -> m (NValue t f m)) -> m (NValue t f m) Source #
data TStringContext Source #
Instances
Show TStringContext Source # | |
Defined in Nix.Value showsPrec :: Int -> TStringContext -> ShowS # show :: TStringContext -> String # showList :: [TStringContext] -> ShowS # |
describeValue :: ValueType -> String Source #
showValueType :: (MonadThunk t m (NValue t f m), Comonad f) => NValue t f m -> m String Source #
data ValueFrame t f m Source #
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 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 toException :: ValueFrame t f m -> SomeException # fromException :: SomeException -> Maybe (ValueFrame t f m) # displayException :: ValueFrame t f m -> String # |
type MonadDataErrorContext t f m = (Show t, Typeable t, Typeable m, Typeable f, MonadDataContext f m) Source #
_NVBuiltinF :: Applicative f => ((String, p -> m r) -> f (String, p -> m r)) -> NValueF p m r -> f (NValueF p m r) Source #
_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 #
key :: (Traversable f, Applicative g) => VarName -> LensLike' g (NValue' t f m a) (Maybe a) Source #