boring-0.1: Boring and Absurd types

Safe HaskellNone
LanguageHaskell2010

Data.Boring

Contents

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

boring

Methods

boring :: a Source #

Instances

Boring () Source # 

Methods

boring :: () Source #

Absurd a => Boring [a] Source #

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

Methods

boring :: [a] Source #

Absurd a => Boring (Maybe a) Source #

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

Methods

boring :: Maybe a Source #

Boring a => Boring (Identity a) Source # 

Methods

boring :: Identity a Source #

c => Boring (Dict c) Source # 

Methods

boring :: Dict c Source #

(~) Nat n (S Z) => Boring (Fin n) Source # 

Methods

boring :: Fin n Source #

Boring a => Boring (I a) Source # 

Methods

boring :: I a Source #

Boring a => Boring (Stream a) Source # 

Methods

boring :: Stream a Source #

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

Methods

boring :: a -> b Source #

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

Methods

boring :: (a, b) Source #

Boring (Proxy * a) Source # 

Methods

boring :: Proxy * a Source #

(~) Nat n Z => Boring (Vec n a) Source # 

Methods

boring :: Vec n a Source #

(~) Nat n Z => Boring (Vec n a) Source # 

Methods

boring :: Vec n a Source #

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

Methods

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

Boring a => Boring (Const * a b) Source # 

Methods

boring :: Const * a b Source #

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

Type equality is Boring too.

Methods

boring :: (* :~: a) b Source #

Boring b => Boring (K * b a) Source # 

Methods

boring :: K * b a Source #

Boring b => Boring (Tagged * a b) Source # 

Methods

boring :: Tagged * a b Source #

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

Methods

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

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

Methods

boring :: Product * f g a Source #

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

Methods

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

Boring (f (g a)) => Boring (Compose * * f g a) Source # 

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

absurd

Methods

absurd :: a -> b Source #

Instances

Absurd Void Source # 

Methods

absurd :: Void -> b Source #

Absurd a => Absurd (NonEmpty a) Source # 

Methods

absurd :: NonEmpty a -> b Source #

Absurd a => Absurd (Identity a) Source # 

Methods

absurd :: Identity a -> b Source #

(~) Nat n Z => Absurd (Fin n) Source # 

Methods

absurd :: Fin n -> b Source #

Absurd a => Absurd (I a) Source # 

Methods

absurd :: I a -> b Source #

Absurd a => Absurd (Stream a) Source # 

Methods

absurd :: Stream a -> b Source #

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

Methods

absurd :: Either a b -> b Source #

Absurd b => Absurd (Const * b a) Source # 

Methods

absurd :: Const * b a -> b Source #

Absurd b => Absurd (K * b a) Source # 

Methods

absurd :: K * b a -> b Source #

Absurd a => Absurd (Tagged * b a) Source # 

Methods

absurd :: Tagged * b a -> b Source #

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

Methods

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

Absurd (f (g a)) => Absurd (Compose * * f g a) Source # 

Methods

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

More integeresting 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.

boringRep :: (Representable f, Absurd (Rep f)) => f a Source #

If an index of Representable f is Absurd, f a is Boring.

untainted :: (Representable f, Boring (Rep f)) => f a -> a Source #

If an index of Representable f is Boring, f is isomorphic to Identity.

See also Settable class in lens.

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