boring-0.2: Boring and Absurd types
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Boring

Description

Boring and Absurd classes. One approach.

Different approach would be to have

-- none-one-tons semiring
data NOT = None | One | Tons

type family Cardinality (a :: *) :: NOT

class Cardinality a ~ None => Absurd a where ...
class Cardinality a ~ One  => Boring a where ...

This would make possible to define more instances, e.g.

instance (Mult (Cardinality a) (Cardinality b) ~ None) => Absurd (a, b) where ...

Functions

Function is an exponential:

Cardinality (a -> b) ~ Exponent (Cardinality b) (Cardinality a)

or shortly |a -> b| = |b| ^ |a|. This gives us possible instances:

  • |a| = 0 => |a -> b| = m ^ 0 = 1, i.e. Absurd a => Boring (a -> b), or
  • |b| = 1 => |a -> b| = 1 ^ n = 1, i.e. Boring b => Boring (a -> b).

Both instances are Boring, but we chose to define the latter.

Note about adding instances

At this moment this module misses a lot of instances, please make a patch to add more. Especially, if the package is already in the transitive dependency closure.

E.g. any possibly empty container f has Absurd a => Boring (f a)

Synopsis

Classes

class Boring a where Source #

Boring types which contains one thing, also boring. There is nothing interesting to be gained by comparing one element of the boring type with another, because there is nothing to learn about an element of the boring type by giving it any of your attention.

Boring Law:

boring == x

Note: This is different class from Default. Default gives you some value, Boring gives you an unique value.

Also note, that we cannot have instances for e.g. Either, as both (Boring a, Absurd b) => Either a b and (Absurd a, Boring b) => Either a b would be valid instances.

Another useful trick, is that you can rewrite computations with Boring results, for example foo :: Int -> (), if you are sure that foo is total.

{-# RULES "less expensive" foo = boring #-}

That's particularly useful with equality :~: proofs.

Minimal complete definition

Nothing

Methods

boring :: a Source #

default boring :: (Generic a, GBoring (Rep a)) => a Source #

Instances

Instances details
Boring () Source # 
Instance details

Defined in Data.Boring

Methods

boring :: () Source #

Absurd a => Boring [a] Source #

Recall regular expressions, kleene star of empty regexp is epsilon!

Instance details

Defined in Data.Boring

Methods

boring :: [a] Source #

Absurd a => Boring (Maybe a) Source #

Maybe a = a + 1, 0 + 1 = 1.

Instance details

Defined in Data.Boring

Methods

boring :: Maybe a Source #

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

Defined in Data.Boring

Methods

boring :: Par1 p Source #

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

Defined in Data.Boring

Methods

boring :: Identity a Source #

Boring b => Boring (a -> b) Source # 
Instance details

Defined in Data.Boring

Methods

boring :: a -> b Source #

Boring (U1 p) Source # 
Instance details

Defined in Data.Boring

Methods

boring :: U1 p Source #

Typeable a => Boring (TypeRep a) Source # 
Instance details

Defined in Data.Boring

Methods

boring :: TypeRep a Source #

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

Defined in Data.Boring

Methods

boring :: (a, b) Source #

Boring (Proxy a) Source # 
Instance details

Defined in Data.Boring

Methods

boring :: Proxy a Source #

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

Defined in Data.Boring

Methods

boring :: Rec1 f p Source #

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

Defined in Data.Boring

Methods

boring :: (a, b, c) Source #

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

Defined in Data.Boring

Methods

boring :: Const a b Source #

a ~ b => Boring (a :~: b) Source #

Homogeneous type equality is Boring too.

Instance details

Defined in Data.Boring

Methods

boring :: a :~: b Source #

Boring b => Boring (Tagged a b) Source # 
Instance details

Defined in Data.Boring

Methods

boring :: Tagged a b Source #

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

Defined in Data.Boring

Methods

boring :: K1 i c p Source #

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

Defined in Data.Boring

Methods

boring :: (f :*: g) p Source #

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

Defined in Data.Boring

Methods

boring :: (a, b, c, d) Source #

(Boring (f a), Boring (g a)) => Boring (Product f g a) Source # 
Instance details

Defined in Data.Boring

Methods

boring :: Product f g a Source #

a ~~ b => Boring (a :~~: b) Source #

Heterogeneous type equality is Boring too.

Instance details

Defined in Data.Boring

Methods

boring :: a :~~: b Source #

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

Defined in Data.Boring

Methods

boring :: M1 i c f p Source #

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

Defined in Data.Boring

Methods

boring :: (f :.: g) p Source #

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

Defined in Data.Boring

Methods

boring :: (a, b, c, d, e) Source #

Boring (f (g a)) => Boring (Compose f g a) Source # 
Instance details

Defined in Data.Boring

Methods

boring :: Compose f g a Source #

class Absurd a where Source #

The Absurd type is very exciting, because if somebody ever gives you a value belonging to it, you know that you are already dead and in Heaven and that anything you want is yours.

Similarly as there are many Boring sums, there are many Absurd products, so we don't have Absurd instances for tuples.

Minimal complete definition

Nothing

Methods

absurd :: a -> b Source #

default absurd :: (Generic a, GAbsurd (Rep a)) => a -> b Source #

Instances

Instances details
Absurd Void Source # 
Instance details

Defined in Data.Boring

Methods

absurd :: Void -> b Source #

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

Defined in Data.Boring

Methods

absurd :: Par1 p -> b Source #

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

Defined in Data.Boring

Methods

absurd :: Identity a -> b Source #

Absurd a => Absurd (NonEmpty a) Source # 
Instance details

Defined in Data.Boring

Methods

absurd :: NonEmpty a -> b Source #

(Absurd a, Absurd b) => Absurd (Either a b) Source # 
Instance details

Defined in Data.Boring

Methods

absurd :: Either a b -> b0 Source #

Absurd (V1 p) Source # 
Instance details

Defined in Data.Boring

Methods

absurd :: V1 p -> b Source #

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

Defined in Data.Boring

Methods

absurd :: Rec1 f p -> b Source #

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

Defined in Data.Boring

Methods

absurd :: Const b a -> b0 Source #

Absurd a => Absurd (Tagged b a) Source # 
Instance details

Defined in Data.Boring

Methods

absurd :: Tagged b a -> b0 Source #

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

Defined in Data.Boring

Methods

absurd :: K1 i c p -> b Source #

(Absurd (f p), Absurd (g p)) => Absurd ((f :+: g) p) Source # 
Instance details

Defined in Data.Boring

Methods

absurd :: (f :+: g) p -> b Source #

(Absurd (f a), Absurd (g a)) => Absurd (Sum f g a) Source # 
Instance details

Defined in Data.Boring

Methods

absurd :: Sum f g a -> b Source #

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

Defined in Data.Boring

Methods

absurd :: M1 i c f p -> b Source #

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

Defined in Data.Boring

Methods

absurd :: (f :.: g) p -> b Source #

Absurd (f (g a)) => Absurd (Compose f g a) Source # 
Instance details

Defined in Data.Boring

Methods

absurd :: Compose f g a -> b Source #

Generic implementation

class GBoring f Source #

A helper class to implement Generic derivation of Boring.

Technically we could do (avoiding QuantifiedConstraints):

type GBoring f = (Boring (f V.Void), Functor f)

gboring :: forall f x. GBoring f => f x
gboring = vacuous (boring :: f V.Void)

but separate class is cleaner.

>>> data B2 = B2 () () deriving (Show, Generic)
>>> instance Boring B2
>>> boring :: B2
B2 () ()

Minimal complete definition

gboring

Instances

Instances details
GBoring (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Boring

Methods

gboring :: U1 a

Boring c => GBoring (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Data.Boring

Methods

gboring :: K1 i c a

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

Defined in Data.Boring

Methods

gboring :: (f :*: g) a

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

Defined in Data.Boring

Methods

gboring :: M1 i c f a

class GAbsurd f Source #

A helper class to implement of Generic derivation of Absurd.

type GAbsurd f = (Absurd (f ()), Functor f)

gabsurd :: forall f x y. GAbsurd f => f x -> y
gabsurd = absurd . void

Minimal complete definition

gabsurd

Instances

Instances details
GAbsurd (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.Boring

Methods

gabsurd :: V1 a -> b

Absurd c => GAbsurd (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Data.Boring

Methods

gabsurd :: K1 i c a -> b

(GAbsurd f, GAbsurd g) => GAbsurd (f :+: g) Source # 
Instance details

Defined in Data.Boring

Methods

gabsurd :: (f :+: g) a -> b

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

Defined in Data.Boring

Methods

gabsurd :: M1 i c f a -> b

More interesting stuff

vacuous :: (Functor f, Absurd a) => f a -> f b Source #

If Absurd is uninhabited then any Functor that holds only values of type Absurd is holding no values.

devoid :: Absurd s => p a (f b) -> s -> f s Source #

There is a field for every type in the Absurd. Very zen.

devoid :: Absurd s => Over p f s s a b

type Over p f s t a b = p a (f b) -> s -> f t

united :: (Boring a, Functor f) => (a -> f a) -> s -> f s Source #

We can always retrieve a Boring value from any type.

united :: Boring a => Lens' s a