nullary-0.1.0.0: A package for working with nullary type classes.

Copyright2015 Derek Elkins
LicenseBSD2
MaintainerDerek Elkins <derek.a.elkins@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Type.Class.Nullary

Description

Provides a framework for defining and using nullary type classes without needing orphan instances. To do this requires some evil to locally generate a type class instances. This library encapsulates that evil and provides a mechanism for safely defining new nullary type classes.

To define a nullary type class, you use the following pattern:

-- The following four extensions are necessary.
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE UndecidableInstances #-}

-- Not exported unless you want to allow users to opt out of
-- the checking by making an instance for Tag PartialTag.
data PartialTag

-- The nullary type class. It can have members, but it's not
-- clear this accomplishes anything.
class Partial

-- Enable this library.  Instances like this unfortunately
-- require UndecidableInstances.
instance Tag PartialTag => Partial

-- Wrap unsafeTag for user convenience.
partial :: (Partial => a) -> a
partial = unsafeTag (Proxy :: Proxy PartialTag)
{-# INLINE partial #-}

-- Define your functions using the Partial class.
head :: Partial => [a] -> a
head (x:xs) = x

Synopsis

Documentation

class Tag t Source

Class for declaring tagged nullary instances. See module description.

unsafeTag :: forall r t. Proxy t -> (Tag t => r) -> r Source

Unsafely cast off the Tag constraint. This should only be used at the "top-level" of an application. In practice, specializations of this should be provided, e.g. unsafeUnsafe. This uses the same evil as Data.Reflect.

data Proxy t :: k -> *

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Monad (Proxy *) 
Functor (Proxy *) 
Applicative (Proxy *) 
Bounded (Proxy k s) 
Enum (Proxy k s) 
Eq (Proxy k s) 
Ord (Proxy k s) 
Read (Proxy k s) 
Show (Proxy k s) 
Ix (Proxy k s) 
Monoid (Proxy k s)