
Hi all. This email is in literate Haskell; you should be able to load it into ghci and verify what I'm saying (nb: it won't compile without alteration: see below). I'm trying to do something which may anyway be stupid / not the best approach to what I'm trying to achieve; however, it's not working and I can't see why not. So I'm asking for help on two fronts: 1) Why is this failing? 2) Maybe more usefully, how should I actually be doing this? It seems an ugly approach; a voice in my head is saying "scrap your boilerplate", but I've no idea yet if that's actually applicable here; should I look at it? On with the show... I need these for "subclass" stuff later on...
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverlappingInstances #-} {-# LANGUAGE UndecidableInstances #-}
module Ambig where
I wish to define a number of algebraic data types with the ability to turn Int values into instances of those types. So I define a typeclass saying this is possible. I use Maybe so I can encode the existence of out-of-range Int values, which will vary from target type to target type.
class Target a where convert :: Int -> Maybe a
E.g. here's a type Foo which only wants values between 1 and 10:
data Foo = Foo Int deriving (Show) instance Target Foo where convert n | n `elem` [1..10] = Just $ Foo n | otherwise = Nothing
(That's a simple example; some are rather more complex. How to do this isn't what I'm asking about, really.) So we have, for example: *Ambig> (convert 1) :: Maybe Foo Just (Foo 1) *Ambig> (convert 11) :: Maybe Foo Nothing Now, some of those algebraic data type types happen to be enumerations; in this case, my idea is to list the constructors, with the rule that each constructor's position in the list is the Int which gets converted into that constructor.
class Enumerated a where constructors :: [a]
E.g. here's a type Bar with three constructors:
data Bar = X | Y | Z deriving (Show) instance Enumerated Bar where constructors = [X, Y, Z]
(This is certainly ugly. Any suggestions?) Now we get to the crux. If a type is an instance of Enumerated, it should also be a Target, because we should be able to convert from Int just by list lookup. But we include a bounds check, naturally...
instance (Enumerated a) => Target a where convert n | n `elem` [0..len-1] = Just $ constructors !! n | otherwise = Nothing where len = length constructors
So I would _hope_ that then, e.g., we'd have: *Ambig> (convert 0) :: Maybe Bar Just X *Ambig> (convert 1) :: Maybe Bar Just Y *Ambig> (convert 3) :: Maybe Bar Nothing Sadly, this function doesn't compile, dying with an "Ambiguous type variable" error: Ambig.lhs:75:29: Ambiguous type variable `a' in the constraint: `Enumerated a' arising from a use of `constructors' at Ambig.lhs:74:29-40 Probable fix: add a type signature that fixes these type variable(s) If we replace "length constructors" with "3" (say), it compiles (but is useless). Adding a type signature doesn't help: it's "misplaced" in that context. If I break it out of the instance declaration so I can add one, I still get the same problem:
convert' :: (Enumerated a, Target a) => Int -> Maybe a convert' n | n `elem` [0..len-1] = Just $ constructors !! n | otherwise = Nothing where len = length constructors
I guess I see roughly what's going on; the question is "which constructors instance is meant?", right? In the "Just" part it's OK, because it can be inferred from the function's return type (right?). But in the guard we don't have that help, so it could be any Enumerated instance? Any advice appreciated! Particularly if this is just a dumb approach. For context, this is related to deserialisation of binary data (they'll actually be Word8's, not Int's) into a variety of data structures. Hmmm, maybe I should just be using Data.Binary... Many thanks, -Andy