Felipe Lessa wrote:
Well, I guess it can't be compiled at all :(
[...]
T.lhs:4:12:
Duplicate instance declarations:
instance [incoherent] (Show a) => MaybeShow a
-- Defined at T.lhs:4:12-32
instance [incoherent] MaybeShow a -- Defined at T.lhs:7:12-22
Indeed, i
On Fri, Jun 11, 2010 at 08:12:43PM -0500, Antoine Latter wrote:
> > 1) Which extensions are required to make the code compile.
>
> OverlappingInstances (of course), and IncoherrentInstances, since
> neither instance is more specific than the other.
Well, I guess it can't be compiled at all :(
On Friday, June 11, 2010, Felipe Lessa wrote:
> On Sat, Jun 12, 2010 at 12:13:14AM +0200, Dupont Corentin wrote:
>> Thanks all, it works fine (see below).
>>
>> I lamentably try to make the same for show:
>> > showTypeable :: (Typeable a) => a -> String
>> > showTypeable x = case cast x of
>> >
Thanks for your response.
How would you do it? I design this GATD for a game i'm making:
> data Obs a where
> Player :: Obs Integer
> Turn :: Obs Integer
> Official :: Obs Bool
> Equ :: Obs a -> Obs a -> Obs Bool --woops!!
> Plus :: (Num a) => Obs a -> Obs a -> O
On Wednesday 09 June 2010 20:37:22, Dupont Corentin wrote:
> Hello,
>
> I am making a little GATD:
> > {-# LANGUAGE GADTs#-}
> >
> > data Obs a where
> > Equal :: Obs a -> Obs a -> Obs Bool
> > Plus :: (Num a) => Obs a -> Obs a -> Obs a
>
> (etc..)
>
> > instance Show t => Show (Obs t) wher
Hello,
I am making a little GATD:
> {-# LANGUAGE GADTs#-}
> data Obs a where
> Equal :: Obs a -> Obs a -> Obs Bool
> Plus :: (Num a) => Obs a -> Obs a -> Obs a
(etc..)
> instance Show t => Show (Obs t) where
> show (Equal a b) = (show a) ++ " Equal " ++ (show b)
> show (Plus a b)