Re: Revised numerical prelude, version 0.02

2001-02-15 Thread Malcolm Wallace

Dylan Thurston writes:

 I'd like to start using something like this in my programs.  What are
 the chances that the usability issues will be addressed?  (The main
 one is all the fromInteger's, I think.)

Have you tried using your alternative Prelude with nhc98?  Offhand,
I couldn't be certain it would work, but I think nhc98 probably makes
fewer assumptions about the Prelude than ghc.

You will need something like

import qualified Prelude as NotUsed
import Dylan'sPrelude as Prelude

in any module that wants to use your prelude.  IIRC, nhc98 treats
'fromInteger' exactly as the qualified name 'Prelude.fromInteger',
so in theory it should simply pick up your replacement definitions.
(In practice, it might actually do the resolution of module 'as'
renamings a little too early or late, but the easiest way to find
out for certain is to try it.)

Regards,
Malcolm

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: Typing units correctly

2001-02-15 Thread Andrew Kennedy

First, I think there's been a misunderstanding. I was referring to 
the poster ("Christoph Grein") of
http://www.adapower.com/lang/dimension.html
when I said that "he doesn't know what he's talking about". I've 
not been following the haskell cafe thread very closely, but from 
what I've seen your (Dylan's) posts are well-informed. Sorry if 
there was any confusion.

As you suspect, negative exponents are necessary. How else would you 
give a polymorphic type to
  \ x - 1.0/x
?

However, because of the equivalence on type schemes that's not just 
alpha-conversion, many types can be rewritten to avoid negative 
exponents, though I don't think that this is particularly desirable.
For example the type of division can be written

  / :: Real (u.v) - Real u - Real v

or

  / :: Real u - Real v - Real (u.v^-1)

where u and v are "unit" variables.

In fact, I have since solved the simplification problem mentioned 
in my ESOP paper, and it would assign the second of these two 
(equivalent) types, as it works from left to right in the type. I
guess it does boil down to choosing a nice basis; more precisely
it corresponds to the Hermite Normal Form from the theory of 
integer matrices (more generally: modules over commutative rings).

For more detail see my thesis, available from

  http://research.microsoft.com/users/akenn/papers/index.html

By the way, type system pathologists might be interested to know
that the algorithm described in ESOP'94 doesn't actually work
without an additional step in the rule for let (he says shamefacedly). 
Again all this is described in my thesis - but for a clearer explanation
of this issue you might want to take a look at my technical report 
"Type Inference and Equational Theories".

Which brings me to your last point: some more general system that 
subsumes the rather specific dimension/unit types system. There's been
some nice work by Martin Sulzmann et al on constraint based systems 
which can express dimensions. See 

  http://www.cs.mu.oz.au/~sulzmann/

for more details. To my taste, though, unless you want to express all
sorts of other stuff in the type system, the equational-unification-based 
approach that I described in ESOP is simpler, even with the fix for let.

I've been promising for years that I'd write up a journal-quality (and 
correct!) version of my ESOP paper including all the relevant material
from my thesis. As I have now gone so far as to promise my boss that I'll
do such a thing, perhaps it will happen :-)

- Andrew.



 -Original Message-
 From: Dylan Thurston [mailto:[EMAIL PROTECTED]]
 Sent: Wednesday, February 14, 2001 7:15 PM
 To: Andrew Kennedy; [EMAIL PROTECTED]
 Subject: Re: Typing units correctly
 
 
 On Wed, Feb 14, 2001 at 08:10:39AM -0800, Andrew Kennedy wrote:
  To be frank, the poster that you cite doesn't know what he's talking
  about. He makes two elementary mistakes:
 
 Quite right, I didn't know what I was talking about.  I still don't.
 But I do hope to learn.
 
  (a) attempting to encode dimension/unit checking in an existing type
  system;
 
 We're probably thinking about different contexts, but please see the
 attached file (below) for a partial solution.  I used Hugs' dependent
 types to get type inference. This makes me uneasy, because I know that
 Hugs' instance checking is, in general, not decidable; I don't know if
 the fragment I use is decidable.  You can remove the dependent types,
 but then you need to type all the results, etc., explicitly.  This
 version doesn't handle negative exponents; perhaps what you say here:
 
  As others have pointed out, (a) doesn't work because the algebra of
  units of measure is not free - units form an Abelian group (if
  integer exponents are used) or a vector space over the rationals (if
  rational exponents are used) and so it's not possible to do
  unit-checking by equality-on-syntax or unit-inference by ordinary
  syntactic unification. ...
 
 is that I won't be able to do it?
 
 Note that I didn't write it out, but this version can accomodate
 multiple units of measure.
 
  (b) not appreciating the need for parametric polymorphism over
  dimensions/units.
  ...  Furthermore, parametric polymorphism is
  essential for code reuse - one can't even write a generic squaring
  function (say) without it.
 
 I'm not sure what you're getting at here; I can easily write a
 squaring function in the version I wrote.  It uses ad-hoc polymorphism
 rather than parametric polymorphism.  It also gives much uglier
 types; e.g., the example from your paper 
   f (x,y,z) = x*x + y*y*y + z*z*z*z*z
 gets some horribly ugly context:
 f :: (Additive a, Mul b c d, Mul c c e, Mul e c b, Mul d c a, 
 Mul f f a, Mul g h a, Mul h h g) = (f,h,c) - a
 
 Not that I recommend this solution, mind you.  I think language
 support would be much better.  But specific language support for units
 rubs me the wrong way: I'd much rather see a general notion of types
 with integer parameters, which you're allowed to 

Re: framework for composing monads?

2001-02-15 Thread Jan Kort


Andy Gill's Monad Template Library is good for that, but the link
from the Haskell library page is broken:

  http://www.cse.ogi.edu/~andy/monads/doc.htm

  Jan

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Downloading Hugs

2001-02-15 Thread zulf jafferi

hi,
 I tried to download the Hugs 98.after downloading Hugs 98,when i try to 
click on the Hugs icon it gives me an error saying COULD NOT
LOAD PRELUDE.i am using Windows 2000.
I would be much obliged if you could help me solve the problem.

cheers!!

_
Get Your Private, Free E-mail from MSN Hotmail at http://www.hotmail.com.


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



need help w/ monad comprehension syntax

2001-02-15 Thread Konst Sushenko



hello,

i am having 
troublegetting my program below to work.
i think i 
implemented the monad methods correctly, but
the function 
'g' does not type as i would expect. Hugs
thinks that 
it is just a list (if i remove the explicit
typing). i 
want it to be functionally identical to the
function 
'h'.

what am i 
missing?

thanks
konst


 newtype 
State s a = ST (s - (a,s))

 unST 
(ST m) = m

 
instance Functor (State s) where  fmap f m = ST (\s 
- let (a,s') = unST m s in (f a, s'))

 
instance Monad (State s) where  return a = ST (\s 
- (a,s))  m = f = ST (\s - let 
(a,s') = unST m s in unST (f a) s')

 --g :: 
State String Char g = [ x | x - return 'a' ]

 h :: 
State String Char h = return 'a'



need help w/ monad comprehension syntax

2001-02-15 Thread Tom Pledger

Konst Sushenko writes:
 | what am i missing?
 :
 |  --g :: State String Char
 |  g = [ x | x - return 'a' ]

Hi.

The comprehension syntax used to be for monads in general (in Haskell
1.4-ish), but is now (Haskell 98) back to being specific to lists.

Does it help if you use do-notation instead?

Regards,
Tom

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Primitive types and Prelude shenanigans

2001-02-15 Thread William Lee Irwin III

On Wed, Feb 14, 2001 at 02:19:39PM -0800, Simon Peyton-Jones wrote:
 The most immediate and painful stumbling block in Haskell 98 is that
 numeric literals, like 3, turn into (Prelude.fromInt 3), where
 "Prelude.fromInt" really means "the fromInt from the standard Prelude"
 regardless of whether the standard Prelude is imported scope.

 Some while ago I modified GHC to have an extra runtime flag to let you
 change this behaviour.  The effect was that 3 turns into simply
 (fromInt 3), and the "fromInt" means "whatever fromInt is in scope".
 The same thing happens for
   - numeric patterns
   - n+k patterns (the subtraction is whatever is in scope)
   - negation (you get whatever "negate" is in scope, not Prelude.negate)

For the idea for numeric literals I had in mind (which is so radical I
don't intend to seek much, if any help in implementing it other than
general information), even this is insufficient. Some analysis of the
value of the literal would need to be incorporated so that something
like the following happens:

literal "0" gets mapped to zero :: AdditiveMonoid t = t
literal "1" gets mapped to one :: MultiplicativeMonoid t = t
literal "5" gets mapped to (fromPositiveInteger 5)
literal "-9" gets mapped to (fromNonZeroInteger -9)
literal "5.0" gets mapped to (fromPositiveReal 5.0)
literal "-2.0" gets mapped to (fromNonZeroReal -2.0)
literal "0.0" gets mapped to (fromReal 0.0)

etc. A single fromInteger or fromIntegral won't suffice here. The
motivation behind this is so that some fairly typical mathematical
objects (multiplicative monoid of nonzero integers, etc.) can be
directly represented by numerical literals (and primitive types).

I don't for a minute think this is suitable for general use, but
I regard it as an interesting (to me) experiment.

On Wed, Feb 14, 2001 at 02:19:39PM -0800, Simon Peyton-Jones wrote:
 (Of course, this is not Haskell 98 behaviour.)   I think I managed to
 forget to tell anyone of this flag.  And to my surprise I can't find
 it any more! But several changes I made to make it easy are still
 there, so I'll reinstate it shortly.  That should make it easy to
 define a new numeric class structure.

It certainly can't hurt; even if the code doesn't help directly with
my dastardly plans, examining how the handling of overloaded literals
differs will help me understand what's going on.

On Wed, Feb 14, 2001 at 02:19:39PM -0800, Simon Peyton-Jones wrote:
 So much for numerics.  It's much less obvious what to do about booleans.
 Of course, you can always define your own Bool type.  But we're going to
 have to change the type that if-then-else uses, and presumably guards too.
 Take if-then-else.  Currently it desugars to 
   case e of
 True - then-expr
 False - else-expr
 but your new boolean might not have two constructors.  So maybe we should 
 simply assume a function  
   if :: Bool - a - a - a
 and use that for both if-then-else and guards  I wonder what else?

I had in mind that there might be a class of suitable logical values
corresponding to the set of all types suitable for use as such. As
far as I know, the only real restriction on subobject classifiers
for logical values is that it be a pointed set where the point
represents truth. Even if it's not the most general condition, it's
unlikely much can be done computationally without that much. So
since we must be able to compare logical values to see if they're
that distinguished truth value:

\begin{pseudocode}
class Eq lv = LogicalValue lv where
definitelyTrue :: lv
\end{pseudocode}

From here, ifThenElse might be something like:

\begin{morepseudocode}
ifThenElse :: LogicalValue lv = lv - a - a - a
ifThenElse isTrue thenValue elseValue =
case isTrue == definitelyTrue of
BooleanTrue - thenValue
_   - elseValue
\end{morepseudocode}

or something on that order. The if/then/else syntax is really just
a combinator like this with a mixfix syntax, and case is the primitive,
so quite a bit of flexibility is possible given either some "hook" the
mixfix operator will use or perhaps even means for defining arbitrary
mixfix operators. (Of course, a hook is far easier.)

The gains from something like this are questionable, but it's not
about gaining anything for certain, is it? Handling weird logics
could be fun.

On Wed, Feb 14, 2001 at 02:19:39PM -0800, Simon Peyton-Jones wrote:
[interesting example using otherwise in a pattern guard elided]
 And we'll get warnings from the pattern-match compiler.  So perhaps we
 should guarantee that (if otherwise e1 e2) = e1.  

I'm with you on this, things would probably be too weird otherwise.

On Wed, Feb 14, 2001 at 02:19:39PM -0800, Simon Peyton-Jones wrote:
 You may say that's obvious, but the point is that we have to specify
 what can be assumed about an alien Prelude.

There is probably a certain amount of generality 

Re: Primitive types and Prelude shenanigans

2001-02-15 Thread Fergus Henderson

On 15-Feb-2001, William Lee Irwin III [EMAIL PROTECTED] wrote:
 Some reasonable assumptions:

I disagree about the reasonableness of many of your assumptions ;-)

   (1) lists are largely untouchable

I want to be able to write a Prelude that has lists as a strict data
type, rather than a lazy data type.

   (4) I/O libs will probably not be toyed with much (monads are good!)
   (5) logical values will either be a monotype or a pointed set class
   (may be too much to support more than a monotype)

I think that that replacing the I/O libs is likely to be a much more
useful and realistic proposition than replacing the boolean type.

   (9) probably no one will try to alter application syntax to operate
   on things like instances of class Applicable

That's a separate issue; you're talking here about a language
extension, not just a new Prelude.

   (10) the vast majority of the prelude changes desirable to support
   will have to do with the numeric hierarchy

s/numeric hierarchy/class hierarchy/

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
|  of excellence is a lethal habit"
WWW: http://www.cs.mu.oz.au/~fjh  | -- the last words of T. S. Garp.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe