| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Nix.Convert
Description
Although there are a lot of instances in this file, really it's just a combinatorial explosion of the following combinations:
- Several Haskell types being converted to/from Nix wrappers
- Several types of Nix wrappers
- Whether to be shallow or deep while unwrapping
Synopsis
- newtype Deeper a = Deeper a
- type CoerceDeeperToNValue t f m = Deeper (NValue t f m) -> NValue t f m
- type CoerceDeeperToNValue' t f m = Deeper (NValue' t f m (NValue t f m)) -> NValue' t f m (NValue t f m)
- class FromValue a m v where- fromValue :: v -> m a
- fromValueMay :: v -> m (Maybe a)
 
- fromMayToValue :: forall t f m a e. (Convertible e t f m, FromValue a m (NValue' t f m (NValue t f m))) => ValueType -> NValue' t f m (NValue t f m) -> m a
- fromMayToDeeperValue :: forall t f m a e m1. (Convertible e t f m, FromValue (m1 a) m (Deeper (NValue' t f m (NValue t f m)))) => ValueType -> Deeper (NValue' t f m (NValue t f m)) -> m (m1 a)
- type Convertible e t f m = (Framed e m, MonadDataErrorContext t f m, MonadThunk t m (NValue t f m))
- newtype Path = Path {}
- class ToValue a m v where- toValue :: a -> m v
 
Documentation
Constructors
| Deeper a | 
Instances
| Functor Deeper Source # | |
| Foldable Deeper Source # | |
| Defined in Nix.Convert Methods fold :: Monoid m => Deeper m -> m # foldMap :: Monoid m => (a -> m) -> Deeper a -> m # foldMap' :: Monoid m => (a -> m) -> Deeper a -> m # foldr :: (a -> b -> b) -> b -> Deeper a -> b # foldr' :: (a -> b -> b) -> b -> Deeper a -> b # foldl :: (b -> a -> b) -> b -> Deeper a -> b # foldl' :: (b -> a -> b) -> b -> Deeper a -> b # foldr1 :: (a -> a -> a) -> Deeper a -> a # foldl1 :: (a -> a -> a) -> Deeper a -> a # elem :: Eq a => a -> Deeper a -> Bool # maximum :: Ord a => Deeper a -> a # minimum :: Ord a => Deeper a -> a # | |
| Traversable Deeper Source # | |
| (Convertible e t f m, ToValue a m (Deeper (NValue' t f m (NValue t f m)))) => ToValue a m (Deeper (NValue t f m)) Source # | |
| (Convertible e t f m, FromValue a m (NValue' t f m (NValue t f m))) => FromValue a m (Deeper (NValue' t f m (NValue t f m))) Source # | |
| (Convertible e t f m, MonadValue (NValue t f m) m, FromValue a m (Deeper (NValue' t f m (NValue t f m)))) => FromValue a m (Deeper (NValue t f m)) Source # | |
| (Convertible e t f m, ToValue a m (NValue t f m)) => ToValue [a] m (Deeper (NValue' t f m (NValue t f m))) 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 # | |
| (Convertible e t f m, FromValue a m (NValue t f m)) => FromValue [a] m (Deeper (NValue' t f m (NValue t f m))) Source # | |
| (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 # | |
| (Convertible e t f m, ToValue a m (NValue t f m)) => ToValue (AttrSet a, AttrSet SourcePos) m (Deeper (NValue' t f m (NValue t f m))) Source # | |
| (Convertible e t f m, FromValue a m (NValue t f m)) => FromValue (AttrSet a, AttrSet SourcePos) m (Deeper (NValue' t f m (NValue t f m))) Source # | |
type CoerceDeeperToNValue' t f m = Deeper (NValue' t f m (NValue t f m)) -> NValue' t f m (NValue t f m) Source #
FromValue
class FromValue a m v where Source #
Instances
fromMayToValue :: forall t f m a e. (Convertible e t f m, FromValue a m (NValue' t f m (NValue t f m))) => ValueType -> NValue' t f m (NValue t f m) -> m a Source #
fromMayToDeeperValue :: forall t f m a e m1. (Convertible e t f m, FromValue (m1 a) m (Deeper (NValue' t f m (NValue t f m)))) => ValueType -> Deeper (NValue' t f m (NValue t f m)) -> m (m1 a) Source #
type Convertible e t f m = (Framed e m, MonadDataErrorContext t f m, MonadThunk t m (NValue t f m)) Source #
ToValue
class ToValue a m v where Source #