Here's a way that works more closely to your original version:

instance Enumerated a => Target a where
   convert n
       | n >= 0 && n < numConstrs = Just (constrs !! n)
       | otherwise = Nothing
    where
       constrs = constructors
       numConstrs = length constrs

Alternatively:

instance Enumerated a => Target a where
   convert n
       | n >= 0 && n < numConstrs = Just result
       | otherwise = Nothing
    where
       numConstrs = length (constructors `asTypeOf` [result])
       result = constructors !! n

However let me warn you that you aren't going to be happy with this instance when it comes time to use this.  Instead, you probably want one of the following:

defaultConvert :: Enumerated a => Int -> a
defaultConvert n
    | n >= 0 && n < numConstrs = Just (WithEnumerated (constrs !! n))
    | otherwise = Nothing
  where
    constrs = constructors
    numConstrs = length constrs

(a)
instance Target SomeEnumeratedType where convert = defaultConvert

(b)
newtype WithEnumerated a = WithEnumerated a
instance Enumerated a => Target (WithEnumerated a) where
    convert n = WithEnumerated (defaultConvert n)

OverlappingInstances basically never does what you want in the long run.

  -- ryan

On Thu, Sep 17, 2009 at 9:01 AM, Andy Gimblett <haskell@gimbo.org.uk> wrote:

On 17 Sep 2009, at 16:50, Daniel Fischer wrote:

Yes, the second appearance of 'constructors' is at an unspecified type.

instance (Enumerated a) => Target a where
  convert n
     | n < 0     = Nothing
     | otherwise = case drop n constructors of
                      (x:_) -> Just x
                      _ -> Nothing

would make it compile.

Neat trick.  It works: thanks!


But there'd be a risk that Target is unusable, depending on how instance resolution is
done.

Unusable?  How so?  Sorry, but I don't follow...


-Andy

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe