[Haskell-cafe] type variable in class instance

Ryan Ingram ryani.spam at gmail.com
Tue Sep 11 01:12:25 CEST 2012


By the way, if you *really* want to do it your way, you can inspect the
typeOf the event directly and look for your "Message" type (using
typeRepTyCon from Data.Typeable), then unsafeCoerce into Message () to
extract the String.

import Unsafe.Coerce
import Data.Typeable

tyConMessage :: TyCon
tyConMessage = typeRepTyCon $ typeOf ( undefined :: Message () )

getMessageContents :: Event e => e -> Maybe String
getMessageContents e
   | typeRepTyCon (typeOf e) == tyConMessage = Just $ case (unsafeCoerce e
:: Message ()) of Message s -> s
   | otherwise = Nothing

But I strongly recommend *not* doing it this way :)

  -- ryan

On Mon, Sep 10, 2012 at 4:03 PM, Ryan Ingram <ryani.spam at gmail.com> wrote:

> From the point of view of the language, Message () and Message Int and
> Message Player are all completely distinct types and may have different
> behavior--there's no way for it to "know" that they all have the same
> representation that only contains a String.
>
> The derived Typeable instance for "Message m" is really a derived instance
> of "Typeable1 Message" along with the generic instance "(Typeable1 f,
> Typeable a) => Typeable (m a)" in Data.Typeable.
>
> So you need to specify the type of message you want, or drop the type
> parameter from Message.
>
> A simpler answer, though, would just be to put the functions in the
> typeclass.
>
> class Event e where
>     viewEvent :: e -> IO ()
>
> instance Event Player where
>     viewEvent (Player a) = putStrLn $ show a
> instance Event (Message m) where
>     viewEvent (Message s) = putStrLn s
>
> In this case, the instance makes it clear that the type parameter is
> irrelevant and puts no constraints on it.  And the type of viewEvent is
> exactly the same as you were asking for: Event e => e -> IO ().
>
>   -- ryan
>
> On Mon, Sep 10, 2012 at 3:06 PM, Corentin Dupont <
> corentin.dupont at gmail.com> wrote:
>
>> Hi Stephen,
>> I wasn't aware of Data.Dynamic.
>> I tried:
>>
>> *viewEvent :: Dynamic -> IO ()
>> viewEvent event = do
>>    case fromDynamic event of
>>         Nothing -> return ()
>>
>>         Just (Message s) -> putStrLn $ show s
>> *
>>
>> But still got the same error (Ambiguous type variable `t0' in the
>> constraint:  (Typeable t0) arising from a use of `fromDynamic')...
>>
>> Best,
>> Corentin
>>
>>
>>
>> On Mon, Sep 10, 2012 at 11:33 PM, Stephen Tetley <
>> stephen.tetley at gmail.com> wrote:
>>
>>> Whilst dynamic typing isn't idiomatic for Haskell, it seems like
>>> you've decided you want it. So why not use Data.Dynamic rather than
>>> roll you're own dynamic typing with Typeable?
>>>
>>
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120910/f8a7b321/attachment.htm>


More information about the Haskell-Cafe mailing list