| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
DiscoverInstances
Description
Generally speaking, this module is only useful to discover instances of unary type classes where the instance is unconstrained.
That is to say - not all that useful in libraries.
However, this has ended up being super useful to me in a bunch of
application contexts. Consider persistent-discover, which grabs all
the PersistEntity instances in scope and makes the [EntityDef] for
them. Or consider a front-end types generating module, which needs to
import a ton of modules, and then call toSomeFrontEndClass :: SomeClass
a => Proxy a -> SomeThing on each thing.
This library can simplify that process.
Since: 0.1.0.0
Synopsis
- discoverInstances :: forall (c :: _ -> Constraint). Typeable c => SpliceQ [SomeDict c]
- withInstances :: Functor f => f (SomeDict c) -> (forall a. c a => Proxy a -> r) -> f r
- forInstances :: (Traversable t, Applicative f) => t (SomeDict c) -> (forall a. c a => Proxy a -> f r) -> f (t r)
- module SomeDictOf
- module Data.Proxy
The main interface
discoverInstances :: forall (c :: _ -> Constraint). Typeable c => SpliceQ [SomeDict c] Source #
This TemplateHaskell function accepts a type and splices in a list of
SomeDicts that provide evidence that the type is an instance of
the class that you asked for.
There are some limitations.
- The class can only accept a single parameter.
- The instances returned do not have a context.
Example Use:
eq :: [SomeDict Eq]
eq = $$(discoverInstances)
This function uses typed TemplateHaskell, which means you don't need to
provide a type annotation directly. However, you can pass a type directly.
ord :: [SomeDictOrd] ord = $$(discoverInstances @Ord)
GHC supports using the $$ syntax without parentheses if the expression is
a single term. So you can also write this:
functor :: [SomeDictFunctor] functor = $$discoverInstances
But you'll get an error if you type-apply like that.
Since: 0.1.0.0
Using the results of discoverInstances
Once you've acquired a for some type class SomeDict cc that you care
about, it's not entirely clear how you might use it.
The SomeDictOf module contains functions for working with these, but the simplest thing to do is probably pattern match on them directly. The use case that this library was designed to support is iterating over all the visible instances of a class and performing some operation on the class.
Consider the persistent database library. The PersistEntity type class
defines a method entityDef :: PersistEntity a => proxy a -> EntityDef,
where the EntityDef type contains information that relates the type to the
database encoding for the type. Let's get all the EntityDefs for the types
in scope:
entityDefs :: [EntityDef]
entityDefs =
map
(\(SomeDictOf proxy) -> entityDef proxy)
$$(discoverInstances @PersistEntity)
The EntityDef for an entity include the documentation comments written for
the entity. So we can print out all the documentation for the database
tables.
Another intended use is to render generated code. We use the
aeson-typescript library to generate TypeScript code for our API. Without
this library, we maintain a list of types to generate code for. This list is
duplicated in the imports, as well as the data declarations.
import Model.Foo
import Model.Bar
import Model.Baz
import Model.Quux
renderTypeScript :: IO ()
renderTypeScript = do
writeToFile $ concat
[ writeType @Foo
, writeType @Bar
, writeType @Baz
, writeType @Quux
]
With discoverInstances, we can skip a lot of this work.
import Model.Foo
import Model.Bar
import Model.Baz
import Model.Quux
renderTypeScript :: IO ()
renderTypeScript = do
writeToFile $ concat
$ flip map $$(discoverInstances @TypeScript)
$ \(SomeDictOf (Proxy :: Proxy ty) ->
writeType @ty
The above two patterns are encapsulated in withInstances. We can rewrite
them like this:
entityDefs =
withInstances
$$(discoverInstances @PersistEntity)
$ \proxy -> entityDef proxy
renderTypeScript :: IO ()
renderTypeScript = do
writeToFile $ concat
$ withInstances $$(discoverInstances @TypeScript)
$ \(Proxy :: Proxy ty) ->
writeType @ty
Another use case is to load all models out of the database, to ensure that
serialization and deserialization logic works. forInstances is useful for
operating over instances effectfully.
loadAllModels :: SqlPersistM ()
loadAllModels = do
forInstances $$(discoverInstances @PersistEntity) \(Proxy :: Proxy a) -> do
selectList [] [] :: SqlPersistM [Entity a]
forInstances :: (Traversable t, Applicative f) => t (SomeDict c) -> (forall a. c a => Proxy a -> f r) -> f (t r) Source #
module SomeDictOf
Re-exports
module Data.Proxy