Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-19 Thread Andy Gimblett


On 17 Sep 2009, at 18:01, Ryan Ingram wrote:


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


Aha - that's great, and it works without OverlappingInstances (but  
still with FlexibleInstances and UndecidableInstances - should that  
worry me?)


Just making sure constructors is only referenced once is the key, it  
seems.


Thanks!

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


Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-19 Thread Daniel Fischer
Am Samstag 19 September 2009 20:55:10 schrieb Andy Gimblett:
 On 17 Sep 2009, at 18:01, Ryan Ingram wrote:
  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

 Aha - that's great, and it works without OverlappingInstances (but
 still with FlexibleInstances and UndecidableInstances - should that
 worry me?)

FlexibleInstances need not worry anybody. They just remove a fairly arbitrary 
restriction 
of Haskell98 for instance declarations.

UndecidableInstances can be dangerous, but there are perfectly safe things 
which reauire 
UndecidableInstances, too.


 Just making sure constructors is only referenced once is the key, it
 seems.

Just making sure that every time it is referenced, it is referenced at the 
correct type.


 Thanks!

 -Andy

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


Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-19 Thread Edward Kmett
A few issues, you can remove the overlapping instances by using a newtype
wrapper to disambiguate which instance you want.

A little alarm bell goes off in my head whenever I read 'instance Foo a'.

newtype Wrapped a = Wrapped a

instance Target Foo where ...

instance Enumerated a = Target (Wrapped a) where ...

is probably a better idea over all.

As for the use of constructors. your problem is that it is ambiguous which
constructors you want to take the list of.

Try replacing constructors with a local variable. The choice of constructors
then will be fixed by the use of the argument from the Just branch and the
monomorphism restriction constraining you so that the list you take the
length of has the same type.

 instance (Enumerated a) = Target a where
 convert n | n `elem` [0..len-1] = Just $ cons !! n
   | otherwise = Nothing
 where
len = length cons
cons = constructors

You could also do it with some sort of

asListOf :: [a] - a - [a]
asListOf = const

convert n = result where
...
len = length cons
...
cons = constructors `asListOf` result

if relying on the MR makes you feel dirty.

-Edward

On Thu, Sep 17, 2009 at 9:40 AM, Andy Gimblett hask...@gimbo.org.uk wrote:

 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 

Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread José Pedro Magalhães
Hey Andy,

On Thu, Sep 17, 2009 at 15:40, Andy Gimblett hask...@gimbo.org.uk wrote:


 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?)


|constructors| is expressible in SYB:

{-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE FlexibleContexts #-}

 module Test where

 import Data.Data
 import Data.Generics.Aliases (extB)

 -- | Construct the empty value for a datatype. For algebraic datatypes, the
 -- leftmost constructor is chosen.
 empty :: forall a. Data a = a
 empty = general
   `extB` char
   `extB` int
   `extB` integer
   `extB` float
   `extB` double where
   -- Generic case
   general :: Data a = a
   general = fromConstrB empty (indexConstr (dataTypeOf general) 1)

   -- Base cases
   char= '\NUL'
   int = 0  :: Int
   integer = 0  :: Integer
   float   = 0.0:: Float
   double  = 0.0:: Double

 -- | Return a list of values of a datatype. Each value is one of the
 possible
 -- constructors of the datatype, populated with 'empty' values.
 constrs :: forall a. Data a = [a]
 constrs = general
   `extB` char
   `extB` int
   `extB` integer
   `extB` float
   `extB` double where
   -- Generic case
   general :: Data a = [a]
   general = map (fromConstrB empty)
   (dataTypeConstrs (dataTypeOf (unList general))) where
 unList :: Data a = [a] - a
 unList = undefined

   -- Base cases
   char= \NUL
   int = [0   :: Int]
   integer = [0   :: Integer]
   float   = [0.0 :: Float]
   double  = [0.0 :: Double]


|constrs| is similar to your |constructors|, but in this way you get it for
free for any datatype with a |Data| instance. Then I guess your |convert|
is:

convert :: forall a. Data a = Int - Maybe a
 convert n = let cs :: [a]
 cs = constrs
 in if (length cs  n) then (Just (cs !! n)) else Nothing


Note that ScopedTypeVariables are essential to typecheck this code.


Cheers,
Pedro
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Daniel Fischer
Am Donnerstag 17 September 2009 15:56:03 schrieb José Pedro Magalhães:
 Hey Andy,

 On Thu, Sep 17, 2009 at 15:40, Andy Gimblett hask...@gimbo.org.uk wrote:
  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?)
 
 |constructors| is expressible in SYB:
Wow.

What about

data Bar = X | Y | Z deriving (Show, Eq, Ord, Enum, Bounded)

instance Enumerated Bar where
constructors = [minBound .. maxBound]

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


Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread José Pedro Magalhães
Hello,

On Thu, Sep 17, 2009 at 16:05, Daniel Fischer daniel.is.fisc...@web.dewrote:

 Am Donnerstag 17 September 2009 15:56:03 schrieb José Pedro Magalhães:
  Hey Andy,
 
  On Thu, Sep 17, 2009 at 15:40, Andy Gimblett hask...@gimbo.org.uk
 wrote:
   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?)
  
  |constructors| is expressible in SYB:
 Wow.

 What about

 data Bar = X | Y | Z deriving (Show, Eq, Ord, Enum, Bounded)

 instance Enumerated Bar where
constructors = [minBound .. maxBound]

 ?


Oh yes, that will certainly work for this very simple datatype. However, one
cannot automatically derive instances of |Bounded| for datatypes with
non-nullary constructors.


Cheers,
Pedro


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

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


Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Andy Gimblett


On 17 Sep 2009, at 15:21, José Pedro Magalhães wrote:


  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?)
 
 |constructors| is expressible in SYB:
Wow.

What about

data Bar = X | Y | Z deriving (Show, Eq, Ord, Enum, Bounded)

instance Enumerated Bar where
   constructors = [minBound .. maxBound]

?

Oh yes, that will certainly work for this very simple datatype.  
However, one cannot automatically derive instances of |Bounded| for  
datatypes with non-nullary constructors.


That would be OK in this instance, I think; I'm already dealing with  
some of those cases by hand, but there were enough purely nullary ones  
that this seemed worth doing.


I don't know if that will work any better with Foo/convert,  
though... :-)


Thanks though Daniel - it's good to meet Enum and Bounded.

-Andy

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


Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Daniel Fischer
Am Donnerstag 17 September 2009 16:30:14 schrieb Andy Gimblett:
 On 17 Sep 2009, at 15:21, José Pedro Magalhães wrote:
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?)
   
   |constructors| is expressible in SYB:
 
  Wow.
 
  What about
 
  data Bar = X | Y | Z deriving (Show, Eq, Ord, Enum, Bounded)
 
  instance Enumerated Bar where
 constructors = [minBound .. maxBound]
 
  ?
 
  Oh yes, that will certainly work for this very simple datatype.
  However, one cannot automatically derive instances of |Bounded| for
  datatypes with non-nullary constructors.

Andy's original message hasn't found its way into my inbox yet (neither has 
yours which 
Andy here quotes), so I don't know what Andy wants to do.
From the part you quoted, I drew the conclusion that one thing Andy wanted was 
a more 
elegant way for the case of nullary constructors. For that, SYB is certainly 
overkill.
I haven't looked at your code, I suppose it also does something reasonable in 
the presence 
of non-nullary constructors, in which case the separate treatment of only 
nullary 
constructors would of course be unnecessary.


 That would be OK in this instance, I think; I'm already dealing with
 some of those cases by hand, but there were enough purely nullary ones
 that this seemed worth doing.

 I don't know if that will work any better with Foo/convert,
 though... :-)

I'll probably understand that when your original message arrives :-)


 Thanks though Daniel - it's good to meet Enum and Bounded.

 -Andy

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


Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Daniel Fischer
Am Donnerstag 17 September 2009 15:40:10 schrieb Andy Gimblett:


   instance (Enumerated a) = Target a where
   convert n | n `elem` [0..len-1] = Just $ constructors !! n
  
 | otherwise = Nothing
  
   where len = length constructors

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.
But there'd be a risk that Target is unusable, depending on how instance 
resolution is 
done.


 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?

Exactly.


 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


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


Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Andy Gimblett


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


Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Daniel Fischer
Am Donnerstag 17 September 2009 18:01:36 schrieb Andy Gimblett:
 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...


Cf. Section 7.6.3.3 of the user's guide:

When matching, GHC takes no account of the context of the instance declaration 
(context1 
etc). GHC's default behaviour is that exactly one instance must match the 
constraint it is 
trying to resolve. It is fine for there to be a potential of overlap (by 
including both 
declarations (A) and (B), say); an error is only reported if a particular 
constraint 
matches more than one.

The -XOverlappingInstances flag instructs GHC to allow more than one instance 
to match, 
provided there is a most specific one. For example, the constraint C Int [Int] 
matches 
instances (A), (C) and (D), but the last is more specific, and hence is chosen. 
If there 
is no most-specific match, the program is rejected.

So for the matching, you have now

instance Target a where ...

which matches everything. Add an instance declaration of the form

instance (SomeClass b) = Target b where ...

and you're hosed.
Though I think that wouldn't compile, at least not without IncoherentInstances.
Actually, I think now that with one-parameter type classes, if it compiles, it 
will most 
likely work, at least I don't see the problems one can create with 
multi-parameter type 
classes now.

 -Andy


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


Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Ryan Ingram
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 hask...@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

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