prim-uniq-0.2: Opaque unique identifiers in primitive state monads

Safe HaskellNone
LanguageHaskell98

Unsafe.Unique.Tag

Synopsis

Documentation

data Tag s a Source #

The Tag type is like an ad-hoc GADT allowing runtime creation of new constructors. Specifically, it is like a GADT "enumeration" with one phantom type.

A Tag constructor can be generated in any primitive monad (but only tags from the same one can be compared). Every tag is equal to itself and to no other. The GOrdering class allows rediscovery of a tag's phantom type, so that Tags and values of type DSum (Tag s) can be tested for equality even when their types are not known to be equal.

Tag uses a Uniq as a witness of type equality, which is sound as long as the Uniq is truly unique and only one Tag is ever constructed from any given Uniq. The type of newTag enforces these conditions. veryUnsafeMkTag provides a way for adventurous (or malicious!) users to assert that they know better than the type system.

Instances
GShow (Tag RealWorld) Source # 
Instance details

Defined in Unsafe.Unique.Tag

Methods

gshowsPrec :: Int -> Tag RealWorld a -> ShowS #

GEq (Tag s :: Type -> Type) Source # 
Instance details

Defined in Unsafe.Unique.Tag

Methods

geq :: Tag s a -> Tag s b -> Maybe (a :~: b) #

GCompare (Tag s :: Type -> Type) Source # 
Instance details

Defined in Unsafe.Unique.Tag

Methods

gcompare :: Tag s a -> Tag s b -> GOrdering a b #

Eq (Tag s a) Source # 
Instance details

Defined in Unsafe.Unique.Tag

Methods

(==) :: Tag s a -> Tag s a -> Bool #

(/=) :: Tag s a -> Tag s a -> Bool #

Ord (Tag s a) Source # 
Instance details

Defined in Unsafe.Unique.Tag

Methods

compare :: Tag s a -> Tag s a -> Ordering #

(<) :: Tag s a -> Tag s a -> Bool #

(<=) :: Tag s a -> Tag s a -> Bool #

(>) :: Tag s a -> Tag s a -> Bool #

(>=) :: Tag s a -> Tag s a -> Bool #

max :: Tag s a -> Tag s a -> Tag s a #

min :: Tag s a -> Tag s a -> Tag s a #

Show (Tag RealWorld a) Source # 
Instance details

Defined in Unsafe.Unique.Tag

newTag :: PrimMonad m => m (Tag (PrimState m) a) Source #

Create a new tag witnessing a type a. The GEq or GOrdering instance can be used to discover type equality of two occurrences of the same tag.

(I'm not sure whether the recovery is sound if a is instantiated as a polymorphic type, so I'd advise caution if you intend to try it. I suspect it is, but I have not thought through it very deeply and certainly have not proved it.)

veryUnsafeMkTag :: Integer -> Tag s a Source #

Very dangerous! This is essentially a deferred unsafeCoerce: by creating a tag with this function, the user accepts responsibility for ensuring uniqueness of the Integer across the lifetime of the Tag (including properly controlling the lifetime of the Tag if necessary by universal quantification when discharging the s phantom type)