newtype-zoo-1.1.0.0: Newtype Wrapper Zoo

Safe HaskellNone
LanguageHaskell2010

NewtypeZoo.Inconsistent

Description

Indicate that something is Inconsistent.

Documentation

newtype Inconsistent a Source #

Constructors

Inconsistent a 
Instances
Monad Inconsistent Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Functor Inconsistent Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Methods

fmap :: (a -> b) -> Inconsistent a -> Inconsistent b #

(<$) :: a -> Inconsistent b -> Inconsistent a #

MonadFix Inconsistent Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Methods

mfix :: (a -> Inconsistent a) -> Inconsistent a #

Applicative Inconsistent Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Foldable Inconsistent Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Methods

fold :: Monoid m => Inconsistent m -> m #

foldMap :: Monoid m => (a -> m) -> Inconsistent a -> m #

foldr :: (a -> b -> b) -> b -> Inconsistent a -> b #

foldr' :: (a -> b -> b) -> b -> Inconsistent a -> b #

foldl :: (b -> a -> b) -> b -> Inconsistent a -> b #

foldl' :: (b -> a -> b) -> b -> Inconsistent a -> b #

foldr1 :: (a -> a -> a) -> Inconsistent a -> a #

foldl1 :: (a -> a -> a) -> Inconsistent a -> a #

toList :: Inconsistent a -> [a] #

null :: Inconsistent a -> Bool #

length :: Inconsistent a -> Int #

elem :: Eq a => a -> Inconsistent a -> Bool #

maximum :: Ord a => Inconsistent a -> a #

minimum :: Ord a => Inconsistent a -> a #

sum :: Num a => Inconsistent a -> a #

product :: Num a => Inconsistent a -> a #

Traversable Inconsistent Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Methods

traverse :: Applicative f => (a -> f b) -> Inconsistent a -> f (Inconsistent b) #

sequenceA :: Applicative f => Inconsistent (f a) -> f (Inconsistent a) #

mapM :: Monad m => (a -> m b) -> Inconsistent a -> m (Inconsistent b) #

sequence :: Monad m => Inconsistent (m a) -> m (Inconsistent a) #

Eq1 Inconsistent Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Methods

liftEq :: (a -> b -> Bool) -> Inconsistent a -> Inconsistent b -> Bool #

Ord1 Inconsistent Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Methods

liftCompare :: (a -> b -> Ordering) -> Inconsistent a -> Inconsistent b -> Ordering #

Read1 Inconsistent Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Show1 Inconsistent Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Inconsistent a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Inconsistent a] -> ShowS #

MonadZip Inconsistent Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Methods

mzip :: Inconsistent a -> Inconsistent b -> Inconsistent (a, b) #

mzipWith :: (a -> b -> c) -> Inconsistent a -> Inconsistent b -> Inconsistent c #

munzip :: Inconsistent (a, b) -> (Inconsistent a, Inconsistent b) #

Pointed Inconsistent Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Methods

point :: a -> Inconsistent a #

Copointed Inconsistent Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Methods

copoint :: Inconsistent a -> a #

Bounded a => Bounded (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Enum a => Enum (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Eq a => Eq (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Floating a => Floating (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Fractional a => Fractional (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Integral a => Integral (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Num a => Num (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Ord a => Ord (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Read a => Read (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Real a => Real (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

RealFloat a => RealFloat (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

RealFrac a => RealFrac (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Show a => Show (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Ix a => Ix (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

IsString a => IsString (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Generic (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Associated Types

type Rep (Inconsistent a) :: Type -> Type #

Methods

from :: Inconsistent a -> Rep (Inconsistent a) x #

to :: Rep (Inconsistent a) x -> Inconsistent a #

Semigroup a => Semigroup (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Monoid a => Monoid (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Arbitrary a => Arbitrary (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Bits a => Bits (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

FiniteBits a => FiniteBits (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Default a => Default (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Methods

def :: Inconsistent a #

NFData a => NFData (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Methods

rnf :: Inconsistent a -> () #

Random a => Random (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Generic1 Inconsistent Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

Associated Types

type Rep1 Inconsistent :: k -> Type #

type Rep (Inconsistent a) Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

type Rep (Inconsistent a) = D1 (MetaData "Inconsistent" "NewtypeZoo.Inconsistent" "newtype-zoo-1.1.0.0-Ax7CodmSe5a620hcbx2lu9" True) (C1 (MetaCons "Inconsistent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Inconsistent Source # 
Instance details

Defined in NewtypeZoo.Inconsistent

type Rep1 Inconsistent = D1 (MetaData "Inconsistent" "NewtypeZoo.Inconsistent" "newtype-zoo-1.1.0.0-Ax7CodmSe5a620hcbx2lu9" True) (C1 (MetaCons "Inconsistent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

theInconsistent :: forall a b p f. (Profunctor p, Functor f) => p a (f b) -> p (Inconsistent a) (f (Inconsistent b)) Source #