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

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_polymorphi... 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-func... So, how can I do that nowadays? Thanks, Compl

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 12-04-2021 13:34, YueCompl via Haskell-Cafe 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_polymorphi...
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-func...
So, how can I do that nowadays?
Thanks, Compl
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (2)
-
Jaro Reinders
-
YueCompl