[Haskell-cafe] Capturing typeclass dictionaries from constructors

Viktor Dukhovni ietf-dane at dukhovni.org
Fri Aug 5 05:44:47 UTC 2022


On Fri, Aug 05, 2022 at 01:58:20PM +1000, Clinton Mead wrote:

> I've asked the following question on StackOverflow, but I thought here
> might be a good place for it also. Sorry for the crosspost but I'm never
> sure what the best place to ask Haskell questions is:
> 
> https://stackoverflow.com/questions/73244177/capturing-typeclass-dictionaries
> 

With minor changes it works:

    λ> :set -package constraints
    λ> :load foo.hs
    λ> :set -XTypeApplications
    λ> f3 (mkFoo3 @Alice)
    "Silly Alice"

Code below.  Which is not to say that this is a best-practice design.
For many use-cases of runtime typing, the "Dynamic" API:

    https://www.microsoft.com/en-us/research/wp-content/uploads/2016/08/dynamic.pdf
    https://hackage.haskell.org/package/base-4.16.3.0/docs/Data-Dynamic.html

is likely a better fit.  Of course since TypeReps can't capture class
instancess (Haskell is not C++) dynamic class instances need additional
machinery.  See related:

    https://stackoverflow.com/questions/38521481/haskell-dynamic-typerep-extract-instance-of-a-typeclass-without-knowing-the-ful

-- 
    Viktor.

{-# LANGUAGE
  AllowAmbiguousTypes,
  GADTs,
  ScopedTypeVariables,
  TypeApplications
  #-}

import Data.Constraint (Dict(Dict), withDict)
import Data.Proxy (Proxy)

class C a where
    silly :: String

data Alice
instance C Alice where
    silly = "Silly Alice"

data Foo1 where
    Foo1 :: Dict (C a) -> Foo1
f1 :: Foo1 -> String
f1 (Foo1 (dict :: Dict (C a))) = withDict dict $ silly @a

data Foo2 where
    Foo2 :: C a => Proxy a -> Foo2
f2 :: Foo2 -> String
f2 (Foo2 (_ :: Proxy a)) = silly @a

data Foo3 where
    Foo3 :: forall a. C a => Foo3
mkFoo3 :: forall a. C a => Foo3
mkFoo3 = Foo3 @a

f3 :: Foo3 -> String
f3 (Foo3 @a) = silly @a


More information about the Haskell-Cafe mailing list