What's the modern way to apply a polymorphic function to a Dynamic value in GHC 8.8 and onwards?

Erik Hesselink hesselink at gmail.com
Mon Apr 12 14:50:14 UTC 2021


Your function is not `forall a. a -> f a`, as in your initial example, but
requires its argument to be an `EventSink`. The value you unwrap from the
`Dynamic` is any existential type, not necessarily an `EventSink`. You'll
have to compare the TypeReps (with something like `eqTypeRep`[1], or wrap
your function in a `Dynamic` and use `dynApply` [2], which does the
comparison for you.

Cheers,

Erik

[1]
https://hackage.haskell.org/package/base-4.15.0.0/docs/Type-Reflection.html#v:eqTypeRep
[2]
https://hackage.haskell.org/package/base-4.15.0.0/docs/Data-Dynamic.html#v:dynApply

On Mon, 12 Apr 2021 at 16:15, YueCompl via ghc-devs <ghc-devs at haskell.org>
wrote:

> Thanks to Vlad and Jaro, your solution of `apD` compiles, I think it
> should work.
>
> But unfortunately my real case is a little different / more complex, a MWE
> appears like this:
>
> ```hs
> holdEvent :: Dynamic -> Dynamic
> holdEvent (Dynamic t evs') =
> withTypeable t $ Dynamic typeRep (hcHoldEvent evs')
> where
> hcHoldEvent :: forall a. EventSink a -> IO (TimeSeries a)
> hcHoldEvent !evs = do
> !holder <- newIORef Nothing
> listenEvents evs $ writeIORef holder . Just
> return $ TimeSeries $ readIORef holder
>
> data EventSink a = EventSink
> { listenEvents :: (a -> IO ()) -> IO (),
> closeStream :: IO ()
> }
>
> instance Functor EventSink where
> fmap = undefined
>
> newtype TimeSeries a = TimeSeries {readTimeSeries :: IO (Maybe a)}
>
> instance Functor TimeSeries where
> fmap = undefined
>
> ```
>
> Now I'm clueless how to use the `withTypeable` trick to apply my
> polymorphic `hcHoldEvent` to `Dynamic`, naively written as in above, the
> error is:
>
> ```log
> *src/PoC/DynPoly.hs:20:49: **error:*
>     • Couldn't match expected type ‘EventSink a0’ with actual type ‘a’
>       ‘a’ is a rigid type variable bound by
>         a pattern with constructor:
>           Dynamic :: forall a.
>                      base-4.13.0.0:Data.Typeable.Internal.TypeRep a -> a
> -> Dynamic,
>         in an equation for ‘holdEvent’
>         at src/PoC/DynPoly.hs:19:12-25
>     • In the first argument of ‘hcHoldEvent’, namely ‘evs'’
>       In the second argument of ‘Dynamic’, namely ‘(hcHoldEvent evs')’
>       In the second argument of ‘($)’, namely
>         ‘Dynamic typeRep (hcHoldEvent evs')’
>     • Relevant bindings include
>         evs' :: a (bound at src/PoC/DynPoly.hs:19:22)
>         t :: base-4.13.0.0:Data.Typeable.Internal.TypeRep a
>           (bound at src/PoC/DynPoly.hs:19:20)
> *   |*
> *20 |*   withTypeable t $ Dynamic typeRep (hcHoldEvent *evs'*)
> *   |**                                                 ^^^^*
>
> ```
>
> Thanks with best regards,
> Compl
>
>
> On 2021-04-12, at 22:04, Jaro Reinders <jaro.reinders at gmail.com> wrote:
>
> I have no experience in this area, but this compiles:
>
> ```
> {-# LANGUAGE RankNTypes, ScopedTypeVariables #-}
> import Type.Reflection
> import Data.Dynamic
>
> appD :: forall f. Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic
> appD f (Dynamic rep (x :: a)) = withTypeable rep (toDyn (f x))
> ```
>
> Cheers,
>
> Jaro
>
>
>
> On 2021-04-12, at 21:06, Vladislav Zavialov <vladislav at serokell.io> wrote:
>
> Would something like this work for you?
>
>  import Type.Reflection
>  import Data.Dynamic
>
>  apD :: Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic
>  apD f (Dynamic t a) = withTypeable t $ Dynamic typeRep (f a)
>
> - Vlad
>
> On 12 Apr 2021, at 14:34, YueCompl via ghc-devs <ghc-devs at haskell.org>
> wrote:
>
> Dear Cafe and GHC devs,
>
>
> There used to be a "principled way with pattern match on the constructor":
>
> ```hs
> data Dynamic where
> Dynamic :: Typeable a => a -> Dynamic
>
> apD :: Typeable f => (forall a. a -> f a) -> Dynamic -> Dynamic
> apD f (Dynamic a) = Dynamic $ f a
> ```
> Source:
> https://www.reddit.com/r/haskell/comments/2kdcca/q_how_to_apply_a_polymorphic_function_to_a/
>
>
> But now with GHC 8.8 as in my case, `Dynamic` constructor has changed its
> signature to:
>
> ```hs
> Dynamic :: forall a. TypeRep a -> a -> Dynamic
> ```
>
> Which renders the `apD` not working anymore.
>
>
> And it seems missing dependencies now for an older solution Edward KMETT
> provides:
>
> ```hs
> apD :: forall f. Typeable1 f => (forall a. a -> f a) -> Dynamic -> Dynamic
> apD f a = dynApp df a
> where t = dynTypeRep a
>       df = reify (mkFunTy t (typeOf1 (undefined :: f ()) `mkAppTy` t)) $
>                 \(_ :: Proxy s) -> toDyn (WithRep f :: WithRep s (() -> f
> ()))
> ```
> Source:
> https://stackoverflow.com/questions/10889682/how-to-apply-a-polymorphic-function-to-a-dynamic-value
>
>
> So, how can I do that nowadays?
>
> Thanks,
> Compl
>
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
>
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20210412/b8d31b6e/attachment.html>


More information about the ghc-devs mailing list