runtime-instances-1.0: Look up class instances at runtime.
CopyrightRichard Eisenberg
LicenseMIT
Maintainerrae@richarde.dev
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageGHC2021

Instance.Runtime

Description

The key innovation in this library is the Instances type, which is a database of instances that can be queried at runtime. More specifically, an Instances tt c is a mapping from elements of type tt to instances of class c.

It is expected that tt be an instance of the TypeText class, which controls how types are rendered into text. A good initial choice for tt is Unqualified, which will render all types as unqualified names. This is simple, but potentially ambiguous, if you have multiple types with the same name (declared in different modules). See Type.Reflection.Name for other alternatives.

An important restriction is that Instances can hold only ground instances: instances with no type variables or type families. Maybe we can accommodate non-ground instances in the future, but not today. (There seems to be no fundamental reason we cannot support non-ground instances, but doing so would be a good deal harder than ground instances.) The instance declarations may have variables, even though the Instances database will hold those instances' instantiations. For example, while we have instance Eq a => Eq (Maybe a), that polymorphic instance cannot be stored in Instances. Instead, you can build an Instances Unqualified Eq with, say, Eq (Maybe Int), Eq (Maybe Bool), and Eq (Maybe Double). Looking up Maybe Int, Maybe Bool, and Maybe Double will all succeed, but looking up Maybe Char would fail.

To create an Instances, use the instancesFor... functions. The Invisible variants accept a type argument specifying the (ground) types which should be used to populate the Instances database. The TypeRep variant expects a TypeRep. In the future, we expect to offer a instancesFor function which will use visible dependent quantification to accept the list of types. Note that Instances is a Monoid, so you can combine the results of several calls.

In order to build an Instances containing all instances in scope, see Instance.Runtime.TH.

To use an Instances, use the withInstanceProxy function. This function looks up an instance in the database and, if successful, passes that instance to a callback function. In the future, once we have the ability to bind type variables in a lambda, we expect withInstance to be a better interface.

Synopsis

Documentation

data Instances type_namer c Source #

A database of instances available for runtime queries. An Instances tn c contains instances of the class c, indexed by type names rendered according to the rules for tn.

Instances

Instances details
Ord type_namer => Monoid (Instances type_namer c) Source # 
Instance details

Defined in Instance.Runtime

Methods

mempty :: Instances type_namer c #

mappend :: Instances type_namer c -> Instances type_namer c -> Instances type_namer c #

mconcat :: [Instances type_namer c] -> Instances type_namer c #

Ord type_namer => Semigroup (Instances type_namer c) Source # 
Instance details

Defined in Instance.Runtime

Methods

(<>) :: Instances type_namer c -> Instances type_namer c -> Instances type_namer c #

sconcat :: NonEmpty (Instances type_namer c) -> Instances type_namer c #

stimes :: Integral b => b -> Instances type_namer c -> Instances type_namer c #

(Show type_namer, Typeable c) => Show (Instances type_namer c) Source #

for debugging only

Instance details

Defined in Instance.Runtime

Methods

showsPrec :: Int -> Instances type_namer c -> ShowS #

show :: Instances type_namer c -> String #

showList :: [Instances type_namer c] -> ShowS #

Creation

instanceForTypeRep :: forall {k} (x :: k) (c :: k -> Constraint) tn. c x => TypeText tn => TypeRep x -> Instances tn c Source #

Create an Instances for a type denoted by the given TypeRep.

instanceForInvisible :: forall {k} (x :: k) (c :: k -> Constraint) tn. Typeable x => c x => TypeText tn => Instances tn c Source #

Create an Instances for a type passed invisibly. Example: instanceForInvisible Int@.

instancesForInvisible :: forall {k} (xs :: [k]) (c :: k -> Constraint) tn. Typeable xs => All c xs => TypeText tn => Instances tn c Source #

Create an Instances for a list of types passed invisibly. Example: instancesForInvisible [Int, Bool, Double]@.

Usage

withInstance :: Ord tn => Instances tn c -> tn -> (forall x. c x => r) -> Maybe r Source #

Look up an instance in Instances, making the instance available for use in the continuation function. If the lookup fails, this returns Nothing. Until https://github.com/ghc-proposals/ghc-proposals/pull/448 is implemented, there is no way to bind a type variable to the found type, so this function is likely impossible to use well. For now, see withInstanceProxy instead.

withInstanceProxy :: Ord tn => Instances tn c -> tn -> (forall x. c x => Proxy x -> r) -> Maybe r Source #

Look up an instance in Instances, making the instance available for use in the continuation function. If the lookup fails, this returns Nothing. If https://github.com/ghc-proposals/ghc-proposals/pull/448 has been implemented in your GHC, you may prefer withInstance.

withInstanceTypeRep :: forall t c tn r. TypeText tn => Instances tn c -> TypeRep t -> (c t => r) -> Maybe r Source #

Look up an instance in Instances, when you already have a TypeRep for the type to look up. To use this function, the class c used in your Instances must imply Typeable; the Typeable instance is used to check that the retrieved type is actually the one you want. If it's not, this function throws an exception (this really shouldn't happen). (In GHCs before 9.4, this check is skipped, because of a bug around Typeable and quantified constraints.) If the lookup fails, this returns Nothing.

Folding

foldInstances :: Monoid m => Instances tn c -> (forall x. c x => Proxy x -> m) -> m Source #

Perform a computation for each instance in the database, accumulating results in a monoid. Your monoid should be commutative, because there is no predictable order of instances in the Instances.