[Haskell-beginners] Defining ExtensionClass (Maybe a) instance in xmonad.

Dmitriy Matrosov sgf.dma at gmail.com
Mon Jan 19 13:01:44 UTC 2015


Hi.

I've tried to define (Maybe a) instance for ExtensionClass from
XMonad/Core.hs
in such way, that extensionType value would use the same data constructor as
was used for the type a itself. But the code below typechecks only, if i add
(Show a) and (Read a) constraints to (Maybe a) instance definition, what
makes
such definition useless for types, which do not have these instances and do
not want to use PersistentExtension .

How can i define (Maybe a) instance without (Show a) and (Read a)
constraints?

> {-# LANGUAGE ExistentialQuantification #-}
> import Data.Typeable

> -- This one does not typecheck
> --instance ExtensionClass a => ExtensionClass (Maybe a) where
> instance (Show a, Read a, ExtensionClass a) => ExtensionClass (Maybe a)
where
>     initialValue = Nothing
>     extensionType x = let Just i = (Just initialValue) `asTypeOf` x
>                       in  case extensionType i of
>                             PersistentExtension _ -> PersistentExtension x
>                             StateExtension _ -> StateExtension x


Here is class definition from XMonad/Core.hs:

> class Typeable a => ExtensionClass a where
>     initialValue :: a
>     extensionType :: a -> StateExtension
>     extensionType = StateExtension

> data StateExtension =
>     forall a. ExtensionClass a => StateExtension a
>   | forall a. (Read a, Show a, ExtensionClass a) => PersistentExtension a

--
    Dmitriy Matrosov
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20150119/4a10ef9e/attachment.html>


More information about the Beginners mailing list