Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- checkComparable :: (Framed e m, MonadDataErrorContext t f m) => NValue t f m -> NValue t f m -> m ()
- alignEqM :: (Align f, Traversable f, Monad m) => (a -> b -> m Bool) -> f a -> f b -> m Bool
- alignEq :: (Align f, Traversable f) => (a -> b -> Bool) -> f a -> f b -> Bool
- isDerivationM :: Monad m => (t -> m (Maybe NixString)) -> AttrSet t -> m Bool
- isDerivation :: Monad m => (t -> Maybe NixString) -> AttrSet t -> Bool
- valueFEqM :: Monad n => (AttrSet a -> AttrSet a -> n Bool) -> (a -> a -> n Bool) -> NValueF p m a -> NValueF p m a -> n Bool
- valueFEq :: (AttrSet a -> AttrSet a -> Bool) -> (a -> a -> Bool) -> NValueF p m a -> NValueF p m a -> Bool
- compareAttrSetsM :: Monad m => (t -> m (Maybe NixString)) -> (t -> t -> m Bool) -> AttrSet t -> AttrSet t -> m Bool
- compareAttrSets :: (t -> Maybe NixString) -> (t -> t -> Bool) -> AttrSet t -> AttrSet t -> Bool
- valueEqM :: forall t f m. (MonadThunk t m (NValue t f m), Comonad f) => NValue t f m -> NValue t f m -> m Bool
- thunkEqM :: (MonadThunk t m (NValue t f m), Comonad f) => t -> t -> m Bool
Documentation
checkComparable :: (Framed e m, MonadDataErrorContext t f m) => NValue t f m -> NValue t f m -> m () Source #
alignEqM :: (Align f, Traversable f, Monad m) => (a -> b -> m Bool) -> f a -> f b -> m Bool Source #
Checks whether two containers are equal, using the given item equality predicate. If there are any item slots that don't match between the two containers, the result will be False.
valueFEqM :: Monad n => (AttrSet a -> AttrSet a -> n Bool) -> (a -> a -> n Bool) -> NValueF p m a -> NValueF p m a -> n Bool Source #
valueFEq :: (AttrSet a -> AttrSet a -> Bool) -> (a -> a -> Bool) -> NValueF p m a -> NValueF p m a -> Bool Source #
compareAttrSetsM :: Monad m => (t -> m (Maybe NixString)) -> (t -> t -> m Bool) -> AttrSet t -> AttrSet t -> m Bool Source #
compareAttrSets :: (t -> Maybe NixString) -> (t -> t -> Bool) -> AttrSet t -> AttrSet t -> Bool Source #
valueEqM :: forall t f m. (MonadThunk t m (NValue t f m), Comonad f) => NValue t f m -> NValue t f m -> m Bool Source #