type families and overlapping

Jorge Marques Pelizzoni jorge.pelizzoni at gmail.com
Wed Dec 17 13:25:26 EST 2008


Hi,

While playing with type families in GHC 6.10.1, I guess I bumped into
the no-overlap restriction. As I couldn't find any examples on that, I
include the following (non-compiling) code so as to check with you if
that's really the case:

-------------------------------------------
{-# OPTIONS -fglasgow-exts #-}
{-# LANGUAGE OverlappingInstances #-}
{-# LANGUAGE UndecidableInstances #-}

module Main where

class Expr t where
	type ExprRslt t :: *
	eval :: t -> ExprRslt t
	
instance Expr t where
	type ExprRslt t = t -- overlap?
	eval = id
		
data Vector a = Vector {width :: !Int, dat :: [a]}
data Subscript a = Subscript {vec :: (Vector a), ind :: !Int}

instance Expr (Subscript a) where
	type ExprRslt (Subscript a) = a
	eval sub = (dat.vec $ sub) !! ind sub
------------------------------------------------

So this means that classes with associated types cannot have default
instances at all? If so, could you possibly refer me to any material
explaining why?

Thanks in advance. Cheers,

Jorge.
-------------- next part --------------
A non-text attachment was scrubbed...
Name: TrimmedDown.hs
Type: application/octet-stream
Size: 993 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20081217/98225a9f/TrimmedDown.obj


More information about the Glasgow-haskell-users mailing list