Safe Haskell | Unsafe |
---|---|
Language | Haskell2010 |
This module provides a compatibility layer of withDict
and WithDict
for GHC <9.4.
For GHC <9.4, the definitions of WithDict
and withDict
are slightly different from those of GHC >= 9.4 to prevent user-defined instances.
To actually make withDict
work, you have to invoke the accompanying GHC Plugin exposed from GHC.Magic.Dict.Plugin. For example:
{-# LANGUAGE RankNTypes, ScopedTypeVariables, TypeApplications, ConstraintKinds #-}
{-# GHC_OPTIONS -fplugin GHC.Magic.Dict.Plugin #-}
module MyModule where
import GHC.Magic.Dict.Compat
class Given a where
given :: a
give :: a -> (Given a => r) -> r
give = withDict
@(Given a) @a
For GHC >=9.4, this module just re-exports the module GHC.Magic.Dict and the plugin is just a no-op - so you can safely use this package without concerning break anything in newer GHCs.
Synopsis
- class WithDict cls meth
- withDict :: forall cls meth {rr :: RuntimeRep} (r :: TYPE rr). WithDict cls meth => meth -> (cls => r) -> r
Documentation
withDict :: forall cls meth {rr :: RuntimeRep} (r :: TYPE rr). WithDict cls meth => meth -> (cls => r) -> r Source #
provides a way to call a type-class–overloaded function
withDict
d ff
by applying it to the supplied dictionary d
.
withDict
can only be used if the type class has a single method with no
superclasses. For more (important) details on how this works, see
Note [withDict]
in GHC.Tc.Instance.Class in GHC.