patch-0.0.8.2: Data structures for describing changes to other data structures.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Monoid.DecidablyEmpty

Description

 
Synopsis

Documentation

class Monoid a => DecidablyEmpty a where Source #

A DecidablyEmpty is one where it can be computed whether or not an arbitrary value is mempty.

By using this class rather than Eq, we avoid unnecessary constraining the contents of Functors. This makes it possible to efficiently combine and/or nest patch maps with Eq-lacking values (e.g. functions) at the leaves.

Minimal complete definition

Nothing

Methods

isEmpty :: a -> Bool Source #

default isEmpty :: Eq a => a -> Bool Source #

Instances

Instances details
DecidablyEmpty All Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: All -> Bool Source #

DecidablyEmpty Any Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Any -> Bool Source #

DecidablyEmpty IntSet Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: IntSet -> Bool Source #

DecidablyEmpty Ordering Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

DecidablyEmpty () Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: () -> Bool Source #

DecidablyEmpty a => DecidablyEmpty (Identity a) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Identity a -> Bool Source #

DecidablyEmpty (First a) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: First a -> Bool Source #

DecidablyEmpty (Last a) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Last a -> Bool Source #

DecidablyEmpty a => DecidablyEmpty (Down a) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Down a -> Bool Source #

(Ord a, Bounded a) => DecidablyEmpty (Max a) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Max a -> Bool Source #

(Ord a, Bounded a) => DecidablyEmpty (Min a) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Min a -> Bool Source #

DecidablyEmpty m => DecidablyEmpty (WrappedMonoid m) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

DecidablyEmpty a => DecidablyEmpty (Dual a) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Dual a -> Bool Source #

(Num a, Eq a) => DecidablyEmpty (Product a) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Product a -> Bool Source #

(Num a, Eq a) => DecidablyEmpty (Sum a) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Sum a -> Bool Source #

DecidablyEmpty p => DecidablyEmpty (Par1 p) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Par1 p -> Bool Source #

DecidablyEmpty (IntMap v) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: IntMap v -> Bool Source #

DecidablyEmpty (Seq v) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Seq v -> Bool Source #

Ord k => DecidablyEmpty (Set k) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Set k -> Bool Source #

DecidablyEmpty (PatchIntMap a) Source # 
Instance details

Defined in Data.Patch.IntMap

Semigroup a => DecidablyEmpty (Maybe a) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Maybe a -> Bool Source #

DecidablyEmpty [a] Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: [a] -> Bool Source #

DecidablyEmpty (Proxy s) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Proxy s -> Bool Source #

DecidablyEmpty (U1 p) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: U1 p -> Bool Source #

Ord k => DecidablyEmpty (Map k v) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Map k v -> Bool Source #

Ord k => DecidablyEmpty (PatchMap k v) Source # 
Instance details

Defined in Data.Patch.Map

Methods

isEmpty :: PatchMap k v -> Bool Source #

(Ord k, DecidablyEmpty p, Patch p) => DecidablyEmpty (PatchMapWithPatchingMove k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

(DecidablyEmpty a, DecidablyEmpty b) => DecidablyEmpty (a, b) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: (a, b) -> Bool Source #

DecidablyEmpty a => DecidablyEmpty (Const a b) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Const a b -> Bool Source #

DecidablyEmpty (f p) => DecidablyEmpty (Rec1 f p) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: Rec1 f p -> Bool Source #

GCompare k2 => DecidablyEmpty (DMap k2 v) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: DMap k2 v -> Bool Source #

GCompare k2 => DecidablyEmpty (PatchDMap k2 v) Source # 
Instance details

Defined in Data.Patch.DMap

Methods

isEmpty :: PatchDMap k2 v -> Bool Source #

GCompare k2 => DecidablyEmpty (PatchDMapWithMove k2 v) Source # 
Instance details

Defined in Data.Patch.DMapWithMove

(DecidablyEmpty a, DecidablyEmpty b, DecidablyEmpty c) => DecidablyEmpty (a, b, c) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: (a, b, c) -> Bool Source #

(DecidablyEmpty (f p), DecidablyEmpty (g p)) => DecidablyEmpty ((f :*: g) p) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: (f :*: g) p -> Bool Source #

DecidablyEmpty c => DecidablyEmpty (K1 i c p) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: K1 i c p -> Bool Source #

(DecidablyEmpty a, DecidablyEmpty b, DecidablyEmpty c, DecidablyEmpty d) => DecidablyEmpty (a, b, c, d) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: (a, b, c, d) -> Bool Source #

DecidablyEmpty (f (g p)) => DecidablyEmpty ((f :.: g) p) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: (f :.: g) p -> Bool Source #

DecidablyEmpty (f p) => DecidablyEmpty (M1 i c f p) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: M1 i c f p -> Bool Source #

(DecidablyEmpty a, DecidablyEmpty b, DecidablyEmpty c, DecidablyEmpty d, DecidablyEmpty e) => DecidablyEmpty (a, b, c, d, e) Source # 
Instance details

Defined in Data.Monoid.DecidablyEmpty

Methods

isEmpty :: (a, b, c, d, e) -> Bool Source #