That is a lot, I'm not sure I understand that pattern synonym. Using `withTypeable` instead works for me:
holdEvent :: Dynamic -> Dynamic holdEvent (Dynamic tr x) = case tr of App ft at -> case ft `eqTypeRep` typeRep @EventSink of Just HRefl -> withTypeable at $ toDyn (hcHoldEvent x) Nothing -> error "to handle" _ -> error "to handle" Cheers, Erik On Mon, 12 Apr 2021 at 18:58, YueCompl <compl....@icloud.com> wrote: > Oh, forgot to mention that there is a warning I also don't understand by > far: > > ```log > *src/PoC/DynPoly.hs:40:3: **warning:** [**-Woverlapping-patterns**]* > Pattern match has inaccessible right hand side > In a case alternative: Dynamic (App eventSink TypeRep) evs' -> ... > * |* > *40 |* *Dynamic (App eventSink TypeRep) evs' ->* > * |** ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...* > ``` > I need to work out some extra stuff to test the solution in real case, > meanwhile this warning seems worrying ... > > On 2021-04-13, at 00:27, YueCompl via ghc-devs <ghc-devs@haskell.org> > wrote: > > Thanks Erik, > > With the help from Iceland_jack <https://www.reddit.com/user/Iceland_jack> > via /r/haskell <https://www.reddit.com/r/haskell> , I end up with a > working solution like this: > > ```hs > data TypeableInstance a where > -- data TypeableInstance :: forall k. k -> Type where > TypeableInstance :: Typeable a => TypeableInstance a > > typeableInstance :: forall (k :: Type) (a :: k). TypeRep a -> > TypeableInstance a > typeableInstance typeRep' = withTypeable typeRep' TypeableInstance > > pattern TypeRep :: forall k (a :: k). () => Typeable a => TypeRep a > pattern TypeRep <- > (typeableInstance -> TypeableInstance) > where > TypeRep = typeRep > > holdEvent :: Dynamic -> Dynamic > holdEvent !devs = case devs of > Dynamic (App eventSink TypeRep) evs' -> > case eqTypeRep (typeRep @EventSink) eventSink of > Just HRefl -> Dynamic TypeRep (hcHoldEvent evs') > Nothing -> error "not an EventSink" -- to be handled properly > _ -> error "even not a poly-type" -- to be handled properly > 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 > > ``` > > I'm still wrapping my head around it, for how the `pattern TypeRep` works > in this case. > > Or you think there exists a solution without using such a pattern? > > My function (hcHoldEvent) is polymorphic so not eligible to be wrapped as > a Dynamic in the first place, or there also some way to specialize it at > runtime? That'll be another interesting tool. > > Thanks with regards, > Compl > > On 2021-04-12, at 22:50, Erik Hesselink <hessel...@gmail.com> wrote: > > 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@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.reind...@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 <vladis...@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@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@haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> >> >> >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs@haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > > _______________________________________________ > ghc-devs mailing list > ghc-devs@haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > >
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs