Here's
the code (it's a full, standalone file - you can copy it into Foo.hs
and run ghc to see the full error I'm facing). The error I get is that
when I try to recursively call geq on the unwrapped x and y, I can't
because ghc considers them to have different types - Quux a and Quux b.
However, the whole point of why I'm trying to call geq is to see if a
and b are the same, so I'm pretty confused.
Note that I'm making use of the generics-sop library, which is where NP and NS and I come from.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
module Foo where
import Data.GADT.Compare
import Generics.SOP
import qualified GHC.Generics as GHC
data Quux i xs where Quux :: Quux (NP I xs) xs
newtype GTag t i = GTag { unTag :: NS (Quux i) (Code t) }
instance GEq (GTag t) where
-- I don't know how to do this
geq (GTag (S x)) (GTag (S y)) =
let _ = x `geq` y
in undefined
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafeOnly members subscribed via the mailman list are allowed to post.