Re: Meta-point: backward compatibility

2008-04-30 Thread Aaron Denney
On 2008-04-30, Ross Paterson [EMAIL PROTECTED] wrote:
 On Thu, Apr 24, 2008 at 08:18:10PM +, Aaron Denney wrote:
 And there is a lot that clearly isn't battle tested in a reasonable new
 form, though the current practice is widely agreed upon to be broken.
 Examples include all monads having fail, rather than only those in a
 subclass, monad not being a subclass of functor, and the whole numeric
 hierarchy issue (which I don't think can be properly designed unless we
 know whether it's going to be FDs or ATs, though, of course, designing
 it for either would provide valuable experience for the limitations
 of both),

 I don't think any of these need involve multi-parameter type classes
 (we don't need vector spaces in the Prelude), but they're often presented
 as use cases for things like class aliases.  Even then, the numeric
 hierarchy is probably easier to fix that the others: one can define a
 finer-grain hierarchy with the existing classes as a facade, and leave
 clients untouched.  The change would be felt by the minority defining
 instances of numeric classes, but they are exactly the people who find
 the present hierarchy inadequate.

Class aliases (or the ability to add superclasses) would certainly help
in letting many of these things be more easily tested.

I suppose we don't need vector spaces.  Nor do we need rationals,
complex numbers, or even arbitrarily large integers.  Nevertheless,
there is a huge benefit to having the interfaces for them there.

-- 
Aaron Denney
--

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


Re: patch applied (haskell-prime-status): add Make $ left associative, like application

2008-04-23 Thread Aaron Denney
On 2008-04-23, Sittampalam, Ganesh [EMAIL PROTECTED] wrote:
 There's plenty of code out there that doesn't have the benefit
 of a vigilant user community ready to spring into action. For
 example, Credit Suisse has several tens of thousands of lines of 
 code written by internal users who are not Haskell experts, and
 it would be rather hard to explain to them that they needed to 
 go through it all and fix it.

What makes them need to update to Haskell' instead of sticking with
Haskell '98?

-- 
Aaron Denney
--

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


Re: patch applied (haskell-prime-status): add Make $ left associative, like application

2008-04-22 Thread Aaron Denney
On 2008-04-22, Simon Marlow [EMAIL PROTECTED] wrote:
 Chris Smith wrote:
 I know it would break 
 nearly every single piece of Haskell code I've ever written.  As such, 
 I'm biased toward thinking it's an extremely bad idea.

 Absolutely.  Given that, we'd need a *very* good reason to make the change.

Surely we don't expect the majority of Haskell code to work unchanged as
Haskell' code?

-- 
Aaron Denney
--

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


Re: Some clarity please!

2008-03-13 Thread Aaron Denney
On 2008-03-13, Ketil Malde [EMAIL PROTECTED] wrote:
 Aaron Denney [EMAIL PROTECTED] writes:

 Well, the way the report specifies that max's default definition
 is.  I'd actually favor making that not an instance function at
 all, and instead have max and min be external functions.

 If you permit a naïve question:

 Prelude :i Ord
 class (Eq a) = Ord a where
   compare :: a - a - Ordering
   () :: a - a - Bool
   (=) :: a - a - Bool
   () :: a - a - Bool
   (=) :: a - a - Bool
   max :: a - a - a
   min :: a - a - a

 ..while all functions could be easily derived from 'compare'.  Or from
 the Eq instance's (==) and (), say.

 What is the reason for this?  Efficiency?  (Which couldn't be handled
 equally well by RULES?)  Otherwise, it looks like an invitation for
 writing inconsistent instances.

My impression (which may not be entirely accurate) is not primarily for
efficiency (though that is one reason), but for ease of implementation.

It may be easier in some cases to think through the various cases of
compare, or to just figure out what (=) is.  Either of these is
sufficient (perhaps in combination with (==) from the superclass).

You can write things so that any of (), (=), (), or (=) are
sufficient, but for writing the default compare, it's easiest to know
ahead of time which you are basing it on, so definitions don't get
circular.

max and min seem to have neither justification going for them, although
I suppose it's technically possible to write compare in terms of them
and (==).

I don't think GHC's RULES were around when Haskell 98 was being formalized,
nor is it clear that one compiler's method should let other efficiency
concerns go by the wayside.

Of course, it would be nice to be able to write (==) in terms of
compare.  While doable manually there's no way to default it to that
smartly.  There are similar issues with Functor and Monad.  ISTR
some discussion about this on the list previously.

-- 
Aaron Denney
--

___
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


Re: digit groups

2006-10-30 Thread Aaron Denney
On 2006-10-26, Jon Fairbairn [EMAIL PROTECTED] wrote:
 On 2006-10-25 at 20:57- Aaron Denney wrote:
 On 2006-10-25, Jon Fairbairn [EMAIL PROTECTED] wrote:
  No. A small alteration to the lexical syntax for the sake of
  improved readability seems perfectly justifiable as long as
  it doesn't make the lexical syntax /significantly/ more
  complicated or harder to learn.
 
 Sure.  But some of us don't find it terribly readable. 

 I'm not sure what you are saying here. Assessing readability
 by introspection is terribly unreliable. Unfamiliarity with
 the presentation of numbers with underlines is likely to
 make them feel a bit awkward to begin with, but habituation
 is likely to change that.

Fair enough, I don't actually find it less readable, merely quite ugly.
I might indeed get used to it.

 I think the ~~ operator hack gets 90% of the benefit for
 those who want it.

 I thought my earlier message adequately demonstrated that it
 does /not/.

You demonstrated some corner cases that weren't convincing at all.

 Another case: if you change “square
 123479010987” to “square 123_479_010_987” to improve
 readability it still means the same thing. If you change it
 to “square 123~~479~~010~~987” it doesn't.

This is a bit more convincing.

-- 
Aaron Denney
--

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


Re: Small note regarding the mailing list

2006-09-02 Thread Aaron Denney
On 2006-09-02, Philippa Cowderoy [EMAIL PROTECTED] wrote:
 On Sat, 2 Sep 2006, isaac jones wrote:

 On Tue, 2006-08-29 at 14:04 +0200, Christophe Poucet wrote:
  Hello,
  
  Just a small request.  Would it be feasible to tag the Haskell-prime
  list in a similar manner as Haskell-cafe?
 
 I'd rather not.  If you want to be able to filter, you can use the
 Sender field which will always be:
 Sender: [EMAIL PROTECTED]
 

 This isn't really enough if you're scan-reading a pile of stuff - are 
 there any particularly good reasons to avoid the tags? They're pretty much 
 standard practice.

They take away valuable space that can be used for informative messages.

If you want to filter it out, don't do it by hand, that's what computers
are for.

-- 
Aaron Denney
--

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


Re: Small note regarding the mailing list

2006-09-02 Thread Aaron Denney
On 2006-09-02, Philippa Cowderoy [EMAIL PROTECTED] wrote:
 On Sat, 2 Sep 2006, Aaron Denney wrote:

 On 2006-09-02, Philippa Cowderoy [EMAIL PROTECTED] wrote:
  On Sat, 2 Sep 2006, isaac jones wrote:
 
  On Tue, 2006-08-29 at 14:04 +0200, Christophe Poucet wrote:
   Hello,
   
   Just a small request.  Would it be feasible to tag the Haskell-prime
   list in a similar manner as Haskell-cafe?
  
  I'd rather not.  If you want to be able to filter, you can use the
  Sender field which will always be:
  Sender: [EMAIL PROTECTED]
  
 
  This isn't really enough if you're scan-reading a pile of stuff - are 
  there any particularly good reasons to avoid the tags? They're pretty much 
  standard practice.
 
 They take away valuable space that can be used for informative messages.
 

 I rarely see a subject I can't read the whole of in a single line anyway, 
 though.

Well, I've seen it happen on occasion.

 If you want to filter it out, don't do it by hand, that's what computers
 are for.
 

 That's not the problem, though. The occasional problem is not accidentally 
 thinking oh, that's spam and deleting a post because you don't recognise 
 the poster and the subject line looks vaguely spamlike. And the spammers 
 have found ways of dealing with bayesian filters by now. If I whitelist 
 and then scan through a spam folder once in a while that makes things even 
 worse, because the proportion of spam in the spam folder is that much 
 higher.

I misspoke -- I shouldn't have said out.  Send mailing list
traffic to seperate mail folders, with seperate new mail indicators, and
everything is golden.

-- 
Aaron Denney
--

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


Re: map and fmap

2006-08-20 Thread Aaron Denney
On 2006-08-20, John Hughes [EMAIL PROTECTED] wrote:

 From: Jon Fairbairn [EMAIL PROTECTED]

 To
 reinforce what Aaron said, if a programme works now, it'll
 still work if map suddenly means fmap.

 Well, this isn't quite true, is it? Here's an example:

 class Foldable f where
   fold :: (a - a - a) - a - f a - a

 instance Foldable [] where
   fold = foldr

 example = fold (+) 0 (map (+1) (return 2))

 example has the value 3 (of course), but if you replace map by fmap then the 
 code no longer compiles.

Solely due to the compiler no longer seeing that list is the only
intermediate type allowed.  But you have to admit this code is a bit
forced.  People won't be combining things quite this way, and will be
passing in values rather than bare returns.

 In any case, I'm dubious about this as a criterion. I would guess that the 
 majority if compiler runs for beginners (and perhaps for the rest of us 
 too!) end in a type error, not a successful compilation, so arguably the 
 quality of error messages when a type-check fails is more important than 
 which programs compile.

Right, like I said, we need to work on better error messages.

-- 
Aaron Denney
--

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


Re: Class System current status

2006-05-14 Thread Aaron Denney
On 2006-05-13, Manuel M T Chakravarty [EMAIL PROTECTED] wrote:
 Stephanie Weirich:
 Simon Peyton-Jones wrote:
  My suggestion is this:
 
  * Specify MPTCs in the main language
 
  * Specify FDs in an Appendix (with some reasonably conservative
 interpretation of FDs). 
 
  * A Haskell' implementation should implement the Appendix, and
 programmers can write programs against it.  But
 we are advertising specifically that we aren't sure, one way
 or the other, whether FDs will stay in the language for ever
 

 Simon,
 
 Why is an Appendix is better than just a footnote in the Standard that 
 says we aren't sure, one way or the other, whether FDs will stay in the 
 language for ever.  Why do we need this extra structure?

 IMHO the right thing is to decouple finalising an FD/AT appendix from
 finalising the main body of Haskell'.  This is clearly more easily
 realised when the delayed material is out-of-line.

Meh.  I'd really like a revised numeric prelude to be able to use MPTCs
with FDs.

-- 
Aaron Denney
--

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


Re: WordPtr,IntPtr,IntMax,WordMax

2006-05-01 Thread Aaron Denney
On 2006-04-29, Manuel M T Chakravarty [EMAIL PROTECTED] wrote:
 Am Donnerstag, den 06.04.2006, 16:37 -0700 schrieb John Meacham:
 On Thu, Apr 06, 2006 at 04:28:01PM -0700, John Meacham wrote:
  I was curious if ghc could support the following basic types, they will
  likely just be aliases of existing types.
  
  WordPtr uintptr_t
  WordMax uintmax_t
  IntPtr  intptr_t
  IntMax  intmax_t
  
  all these C types are defined by ISO C so should be available,
  otherwise, they are easy enough to generate in ghcs autoconf script.
  
  jhc provides these under these names in Data.Word and Data.Int.
  they would be useful for writing jhc/ghc portable low level code, and
  writing 32/64 bit safe code.
 
 oh, I forgot the all important conversion routines,
 
 ptrToWordPtr :: Ptr a - WordPtr
 wordPtrToPtr :: WordPtr - Ptr a
 
 ptrToIntPtr :: Ptr a - IntPtr
 intPtrToPtr :: IntPtr - Ptr a
 
 jhc makes these available in Jhc.Addr, but if ghc decides to provide
 them in a common spot (Foreign.Ptr maybe?)
 
 then I will have jhc follow suit.
 
 I'd also propose these be added to the FFI standard.

 I collect additions to the FFI on the Haskell' wiki:

   http://hackage.haskell.org/trac/haskell-prime/wiki/ForeignFunctionInterface

 I added a note about these types.  Any other ISO C types that we should
 include?

complex foo.

-- 
Aaron Denney
--

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


Re: FFI, safe vs unsafe

2006-04-11 Thread Aaron Denney
On 2006-04-11, Ross Paterson [EMAIL PROTECTED] wrote:
 On Tue, Apr 11, 2006 at 09:13:00AM +0100, Simon Marlow wrote:
  - the default should be... concurrent reentrant, presumably, because
that is the safest.  (so we need to invert the notation).

 I think the name concurrent has a similar problem to safe: it reads
 as an instruction to the implementation, rather than a declaration by the
 programmer of the properties of a particular function; as Wolfgang put it,
 this function might spend a lot of time in foreign lands.

I'd like to second this.

-- 
Aaron Denney
--

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


Re: Pre-emptive or co-operative concurrency (was: Concurrency)

2006-03-28 Thread Aaron Denney
On 2006-03-28, Malcolm Wallace [EMAIL PROTECTED] wrote:
 Another piece of terminology to clear up.  By non-blocking foreign
 call, you actually mean a foreign call that *can* block.  As a
 consequence of the fairness policy, you wish to place the requirement on
 implementations that such a blocking foreign call _should_not_
 block progress of other Haskell threads.  The thread-nature of the
 foreign call is blocking.  The Haskell-API nature is desired to be
 non-blocking.

*glyph of enlightenment*.
Ah, no wonder a lot of the discussion and docs didn't seem to make sense.

-- 
Aaron Denney
--

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


Re: bringing discussions to a close

2006-03-28 Thread Aaron Denney
On 2006-03-29, isaac jones [EMAIL PROTECTED] wrote:
 On Tue, 2006-03-28 at 21:16 -0500, Jim Apple wrote:
 On 3/28/06, isaac jones [EMAIL PROTECTED] wrote:
  The only topics that should remain open are concurrency and
  the class system.
 
 What happene to bullet 3, perhaps standard libraries?

 We're still trying to figure out exactly what the 3rd topic should be.
 I don't want to hold up discussion on the other topics, though.
 Standard libraries is at the top of my list right now because it has
 hardly been discussed.

A lot of the design decisions for standard libraries do depend on
details of the class system, as well.

-- 
Aaron Denney
--

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


Re: Re[2]: important news: refocusing discussion

2006-03-27 Thread Aaron Denney
On 2006-03-28, Taral [EMAIL PROTECTED] wrote:
 On 3/27/06, Ross Paterson [EMAIL PROTECTED] wrote:
 How about STM (minus retry/orElse) and TVars as the portable interface?
 They're trivial for a single-threaded implementation, and provide a
 comfortable interface for everyone.

 +1 on STM as the core interface. Why do you suggest omitting retry/orElse?

-1.  STM is a cool little abstraction making it easy to write dead-lock
free code.  I haven't wrapped my head around writing _quick_ dead-lock free
code, where as the MVar model has all sorts of abstractions built that
make that, well, not _easy_, but the difficulties are understood.

-- 
Aaron Denney
--

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


Re: the MPTC Dilemma (please solve)

2006-03-20 Thread Aaron Denney
On 2006-03-20, Manuel M T Chakravarty [EMAIL PROTECTED] wrote:
 IMHO if we consider deprecating a feature in Haskell'' again,
 we should not include it in Haskell', but leave it as an optional extra
 that some systems may experimentally implement and some may not.

Possibly true, but it still needs to be standardized so that it will
work the same on different implementations.

-- 
Aaron Denney
--

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


Re: Ranges and the Enum class

2006-03-20 Thread Aaron Denney
On 2006-03-20, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
 Am Freitag, 17. März 2006 18:49 schrieb Ross Paterson:
 [...]

 Also, toEnum and fromEnum would make more sense mapping from and to
 Integer.

 Why do we need toEnum and fromEnum at all?  As far as I know, they are merely 
 there to help people implement things like enumFrom.

Which could still be useful.

 It's often not clear 
 how toEnum and fromEnum should look like.  How should they be implemented for 
 Time.Day, for example?  Should the days corresponds to the integers 0 to 6 or 
 1 to 7?

I believe that 0 to n-1 is the standard representation that deriving Enum 
currently
uses.

 It seems that succ and pred are unused. 

 No, I use them.  In my opinion, it makes much more sense to write succ n than 
 n + 1.

Agreed, for non-arithmetical types.

-- 
Aaron Denney
--

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


Re: Ranges and the Enum class

2006-03-18 Thread Aaron Denney
On 2006-03-18, Jim Apple [EMAIL PROTECTED] wrote:
 On 3/18/06, Aaron Denney [EMAIL PROTECTED] wrote:
 Rational _could_ be added here by the diagonal representation, but
 probably sohuldn't.

 We could also add an actual enumeration of rationals, as in
 http://web.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/rationals.pdf

 It would be quite confusing to write, say, [1%2 .. 3%2] and get 2%1
 and 1%3 in the middle!

Right, hence my desire to make it a sequence, but not Enumerable, since
it has quite a few different quasi-natural ways of doing so.

-- 
Aaron Denney
--

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


Re: Ranges and the Enum class

2006-03-18 Thread Aaron Denney
On 2006-03-18, Aaron Denney [EMAIL PROTECTED] wrote:
 class ArithmeticSequence a where
 stepFrom  :: a - [a]-- [n..]
 stepFromBy:: a - a - [a]   -- [n,n'..]
 stepFromTo:: a - a - [a]   -- [n..m]
 stepFromByTo  :: a - a - a - [a]  -- [n,n'..m]

Whoops, it was a big thinko to change Then to By here.
These should be stepFromThenTo, etc.

-- 
Aaron Denney
--

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


Ranges and the Enum class

2006-03-17 Thread Aaron Denney
Sometime back on one of the other Haskell lists, there was a proposal
to not have the floating types instances of Enum and instead have some
other class to which [a, b..c] desugars.  That is, rename enumFromThen
and friends and put them in another class.  Put simply, Float and Double
should not support succ and pred (unless, perhaps, they map to the next
greater/lesser representable number, which would also be confusing).
I can even see an argument for not allowing Float or Double to be used
for ranges either, as the steps may not be exact, which in practice
turns out to be very confusing.

This is a wart I would really like to see get fixed.

-- 
Aaron Denney
--

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


Re: Ranges and the Enum class

2006-03-17 Thread Aaron Denney
On 2006-03-17, Ross Paterson wrote:
 Speaking of confusing, try

   [0, 0.3 .. 2]::[Rational]

Right.  I had forgotten that -- Rational is exact, yet has the weird
closest endpoint behavior of Float and Double.

 Also, toEnum and fromEnum would make more sense mapping from and to
 Integer.  It seems that succ and pred are unused.

So, I think I'll put together a proposal, well two.
Okay, three.

First, change toEnum and fromEnum to Integer.

Then there is a choice between:
(1): Remove Double, Float, and Rational from Enum.  They're no longer
usable in arithmetic sequences.

Pro: Very easy to do.
 Sequences can still be constructed by starting with
 integers, and scaling to convert.
Con: Loses some functionality (though it's questionable
 functionality given rounding).

(2): Split Enum into the classes Enum and ArithmeticSequence
and change what the various [..] desugars to.

class Enum a where
succ, pred :: a - a
toEnum :: Integer - a
fromEnum   :: a - Integer

I believe succ and pred aren't used directly by anything else, but I do like
having them.

instance Integer, Int

Rational _could_ be added here by the diagonal representation, but
probably sohuldn't.

class ArithmeticSequence a where
stepFrom  :: a - [a]-- [n..]
stepFromBy:: a - a - [a]   -- [n,n'..]
stepFromTo:: a - a - [a]   -- [n..m]
stepFromByTo  :: a - a - a - [a]  -- [n,n'..m]

instance Int, Integer, Float, Double, Rational.

(a) Make all of them have the closest endpoint behavior.
(b) Make all of them have strict no more than behavior.

Pros: Clearly divides two seperate uses, while keeping functionality.
  Can re-introduce relationship between Ix and Enum?
Cons: Yet another typeclass.
  Slightly misleading name, as non-arithmetic structures _should_ be
  supported.  Also a bit long.
  But doing so automatically is tricky, as toEnum and fromEnum are no
  longer accessible
  Keeps questionable functionality of non-exact arithmetic sequences.

Personally, I'm for 2(a), but I think even (1) is an improvement.

It's a pity we can't make Enum a subclass of ArithmeticSequence that
provides the methods of its superclass.  Would it be possible to have
data ... (deriving ArithmeticSequence) check if (Num a, Ord a) is
defined and use (+), else if Enum a is defined, use fromEnum/toEnum to
go through Integer, else fail.

Where I suppose defined must mean defined in this module.  Hmm.  That's
kind of ugly.  I can see why these were combined, but it's still really
ugly.

Steppable might be a better name.

Comments anyone?

-- 
Aaron Denney
--

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


Re: Export lists in modules

2006-02-23 Thread Aaron Denney
On 2006-02-21, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
 Am Dienstag, 21. Februar 2006 04:41 schrieb John Meacham:
 on this note, I thought it would be nice to do a 'mostly unqualified'
 import.

 import Foo qualified(foo,bar)

 which will have the effect of

 import Foo hiding(foo,bar)
 import qualified Foo(foo,bar)

 since usually you can import a whole module unqualified except for a few
 troublemakers.

 John

 On the other hand, sometimes it makes sense to have a mostly qualified 
 import.  For example, if you import Data.Set or Data.Map you might want only 
 the type constructors to be imported unqualified and the rest to be imported 
 qualified.

import qualified Foo

unqualify1 = Foo.unqualify1
unqualify2 = Foo.unqualify2
...

(That is, this is already pretty easy to do.)

-- 
Aaron Denney
--

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


Re: Priorities

2006-02-03 Thread Aaron Denney
On 2006-02-03, John Goerzen [EMAIL PROTECTED] wrote:
 On Fri, Feb 03, 2006 at 05:56:41PM +0100, Tomasz Zielonka wrote:
 On Fri, Feb 03, 2006 at 10:03:08AM -0600, John Goerzen wrote:
  I know, of course, that Java green threads and Haskell forkIO threads
  are called threads, but I personally believe its misleading to call it
  concurrency -- they're not doing more than one thing at a time.
 
 Aren't you thinking about Parallellism?

 No.

 http://en.wikipedia.org/wiki/Concurrency_%28computer_science%29
 In computer science, concurrency is a property of systems which
 consist of computations that execute overlapped in time

 You're not doing anything simultaneously (overlapped in time) when
 you're using poll and select (only).  To do something simultaneously in
 Unix, you'd have to either use fork() or start a thread.

That was his point.  Threading is a way of structuring a program.
Parallelism is a strategy for exploiting that structuring (and others).

-- 
Aaron Denney
--

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


Re: The dreaded M-R

2006-01-26 Thread Aaron Denney
On 2006-01-26, John Hughes [EMAIL PROTECTED] wrote:
 I don't think it's hard. I would just teach students to define
 functions with =, and variables with :=. I tell my students to write
 type signatures at the beginning anyway, so they don't risk being
 bitten by the M-R anyway. Beginning students just do what you tell
 them, and they already think of function and variable definitions as
 different. Learning a different syntax for one of them would not be a
 problem.

 Once they've mastered basic programming and start getting interested
 in things like overloading, then you have to explain how the M-R
 works. I'd much rather explain =/:= than try to teach them how you
 know whether a definition is shared or not right now.

And this gets back to what the target audience for Haskell' is
question.  Since I'm not a CS student, and I'm not teaching CS students,
this whole argument is rather unconvincing to me.

-- 
Aaron Denney
--

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