Re: Relax the restriction on Bounded derivation

2007-04-18 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Ravi Nanavati wrote:
> On 4/17/07, Neil Mitchell <[EMAIL PROTECTED]> wrote:
>>
>> Hi,
>>
>> >From Section 10 of the Haskell report, regarding automatic derivation:
>>
>> to derive Bounded for a type: "the type must be either an enumeration
>> (all constructors must be nullary) or have only one constructor."
>>
>> This seems a very artificial restriction - since it allows you to be
>> in any one of two camps, but no where in between. It also means that
>> Either doesn't derive Bounded, while it could easily do so:
>>
>> instance (Bounded a, Bounded b) => Bounded (Either a b) where
>> minBound = Left minBound
>> maxBound = Right maxBound
>>
>> So I propose that this restriction be lifted, and that the obvious
>> extension be given such that minBound is the lowest constructor with a
>> pile of minBounds, and maxBound is the highest constructor with a pile
>> of maxBound.
> 
> 
> In general, I like the idea of of allowing more flexible derivation of
> Bounded, but I'm worried your specific proposal ends up mandating the
> derivation of Bounded instances for types that aren't really "bounded"
> (used
> in a deliberately loose sense). Consider the following type:
> 
> data Foo = A Char | B Integer | C Int
> 
> On some level, there's no real problem in creating a Bounded instance as
> follows (which is how I interpret your proposal):
> 
> instance Bounded Foo
>  minBound  =  A (minBound :: Char)
>  maxBound =  C (maxBound :: Int)
> 
> On the other hand, there's a real sense in which the type isn't actually
> "bounded". For instance, if it was also an instance of Enum, enumerating
> all
> of the values from minBound to maxBound might not terminate. I'm not sure
> what to do about the scenario. Should we (unnecessarily) insist that all of
> the arguments of all of the constructors be Bounded to avoid this? Should
> Bounded more explicitly document what properties the minBound, maxBound and
> the type should satisfy? Or something else?

IMO, Bounded only needs to satisfy (if Foo is in Ord)
forall a::Foo, a >= minBound && a <= maxBound
.
I want to be able to define bounded for
data ExtendedInteger = NegativeInfinity | PlainInteger Integer |
PositiveInfinity
.  Preferably by deriving, because it's easier.
If we require properties of Enum... Enum _already_ has problems with
instances like Integer where fromEnum :: a -> Int only has a limited
possible output; there is little reasonable meaning for (fromEnum
(10 :: Integer))
(hugs: Program error: arithmetic overflow)

(Float and Double *aren't* in Bounded. Then again, Haskell98 doesn't
require them to contain non-_|_ values of +-infinity.)

Furthermore, there are bounded things that aren't enumerable anyway (I
think) (such as some lattices), so it would be odd to add that
restriction just because the type might also be in Prelude.Enum.

However there is a good argument for having some sort of bounded-enum
class for things that have a finite number of discrete positions. These
have log(number of possibilities) information content and can (in
theory) be serialized with such a number of bits known from the type.
Designing such a class could be interesting...

Rather, I would ask "Must any inhabitant of a type in Enum be reachable
by pred or succ from an arbitrary inhabitant of the type?"  For example,
I could declare an instance of Enum that contradicted that:
data Something = Some Integer | Another Integer
where pred and succ always stayed within the same constructor, and for
fromEnum/toEnum I would just find some way to encode some common (i.e.
relatively small magnitude, just as the usual instance Enum Integer is
limited this way) values of Something into an Int. Or are
fromEnum/toEnum supposed to obey some sort of properties, when they are
defined, relative to the rest of the methods? I would guess not, given
the comment
- -- NOTE: these default methods only make sense for types
- --   that map injectively into Int using fromEnum
- --  and toEnum.
(hugs: fromEnum (2.6 :: Double) ---> 2)


Cheers,
Isaac
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGJgjWHgcxvIWYTTURAlL/AJ97SilRhmd8B59TAAX+Hcyjly5oHQCff0fa
5B4Y9m0Zb3vQtilZr4lRQs0=
=Qn2+
-END PGP SIGNATURE-
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Relax the restriction on Bounded derivation

2007-04-18 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Isaac Dupree wrote:
> However there is a good argument for having some sort of bounded-enum
> class for things that have a finite number of discrete positions. These
> have log(number of possibilities) information content and can (in
> theory) be serialized with such a number of bits known from the type.
> Designing such a class could be interesting...

In particular, this hypothetical class could be derived more generally
than Enum:
data Blah a b = Baz Int a Bool | Quux | Qx b
derived instance (Finite a, Finite b) => Finite (Blah a b)
since Int and Bool are in this class.

Isaac
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGJg8lHgcxvIWYTTURAln7AJ49TOSqXbx4GNzYti0GVuYBDPjDXQCfcDQz
BPbBk1M9cZRS24Dt6b+0inQ=
=X+1X
-END PGP SIGNATURE-
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Relax the restriction on Bounded derivation

2007-04-18 Thread Aaron Denney
On 2007-04-18, Isaac Dupree <[EMAIL PROTECTED]> wrote:
> (Float and Double *aren't* in Bounded. Then again, Haskell98 doesn't
> require them to contain non-_|_ values of +-infinity.)

And they're only in Enum to support the [a..b] syntax, whose semantics
can't really sanely be supported for Float and Double anyways.

> Furthermore, there are bounded things that aren't enumerable anyway (I
> think) (such as some lattices), so it would be odd to add that
> restriction just because the type might also be in Prelude.Enum.

I'd really like to see one.  Unless you're just talking about
a set with a partial order, in which case, yes, many are bounded.
e.g. reals in [0, 1], as when being used for probabilities.

> Rather, I would ask "Must any inhabitant of a type in Enum be reachable
> by pred or succ from an arbitrary inhabitant of the type?"

That would make sense to me (when restricted to non-bottom inhabitants),
and is essentially the objection that many have to Float and Double
being in Enum.

> For example,
> I could declare an instance of Enum that contradicted that:
> data Something = Some Integer | Another Integer
> where pred and succ always stayed within the same constructor, and for
> fromEnum/toEnum I would just find some way to encode some common (i.e.
> relatively small magnitude, just as the usual instance Enum Integer is
> limited this way) values of Something into an Int. Or are
> fromEnum/toEnum supposed to obey some sort of properties, when they are
> defined, relative to the rest of the methods? I would guess not, given
> the comment
> - -- NOTE: these default methods only make sense for types
> - --   that map injectively into Int using fromEnum
> - --  and toEnum.
> (hugs: fromEnum (2.6 :: Double) ---> 2)
>
>
> Cheers,
> Isaac

The default implementation for the class assumes 
fromEnuw (succ x) = 1 + fromEnum x
and similar things.

That's a pretty strong argument that all types should obey that.

-- 
Aaron Denney
-><-

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