The madness of implicit parameters: cured?

2003-08-02 Thread Ben Rudiak-Gould
When I first learned about implicit parameters I thought they were a great
idea. The honeymoon ended about the time I wrote some code of the form
let ?foo = 123 in expr2, where expr2 used ?foo implicitly, and debugging
eventually unearthed the fact that ?foo's implicit value was not being set
to 123 in expr2. That was enough to scare me off of using implicit
parameters permanently.

More recently, I've realized that I really don't understand implicit
parameters at all. They seemed simple enough at first, but when I look at
an expression like

f x = let g y = ?foo in g

I realize that I have no idea what f's type should be. Is it

(?foo :: c) = a - b - c

or is it

a - ((?foo :: c) = b - c)

? As far as I can tell, these are not the same type: you can distinguish
between them by partially applying f with various different values of ?foo
in the implicit environment. GHC tells me that f has the former type, but
I still have no idea why: is it because g has an implicit ?foo parameter
and f implicitly applies its own ?foo to g before returning it? Why would
it do that? Or is it because ?foo is here interpreted as referring to an
implicit parameter bound in the call of f, instead of in g? That doesn't
make sense either.

The final straw was:

Prelude let ?x = 1 in let g = ?x in let ?x = 2 in g
1
Prelude let ?x = 1 in let g () = ?x in let ?x = 2 in g ()
2

This is insanity. I can't possibly use a language feature which behaves in
such a non-orthogonal way.

Now the interesting part: I think I've managed to fix these problems. I'm
afraid that my solution will turn out to be just as unimplementable as my
original file I/O proposal, and that's very likely in this case since I'm
far from grokking Haskell's type system. So I'm going to present my idea
and let the gurus on this list tell me where I went wrong. Here we go.

First, discard the current implicit-parameter scheme entirely. (I'll
eventually build up to something very similar.)

Now introduce the idea of explicit named parameters to Haskell. This
requires three extensions: a new kind of abstraction, a new kind of
application, and a way of representing the resulting types.

The abstraction could be done with a new lambda form, but instead I'll use
a special prefix on identifiers which are to be considered named
parameters, namely the character #. The new application form will be
[F] { #x = [G] } where [F] and [G] are expressions. [F] must evaluate to a
function with an explicit named parameter #x.

The type notation for a named parameter will be (#name :: type). They can
appear only on the left side of a -. Named parameters can only be passed
by name, so their order relative to positional parameters and each other
doesn't matter; therefore we may as well bubble them up to the head of
the list of arguments. In fact, we could put them in the context with the
type classes, but I won't do so.

Examples:

cons :: (#elem :: a) - (#list :: [a]) - [a]
cons #elem #list = #elem : #list

cons { #elem = 'h', #list = ello }-- legal

cons 'h' ello -- illegal: named params must be passed by name

cons { #list = ello } -- legal, has type (#elem :: Char) - String

cons { #list = ello, #elem = 'h' }-- legal

cons { #list = ello } { #elem = 'h' } -- legal

append :: (#right :: [a]) - [a] - [a]
append left #right = ...-- named args gravitate left

Now introduce the idea of auto-lifted named parameters. I'll distinguish
these from ordinary named parameters by using an @ prefix instead of #.
These are exactly the same as ordinary named parameters except that if
they appear in the type on the right hand side of an application node,
they are implicitly lifted to the whole node. For example, if [F] has an
auto-lifted parameter @p, and [G] has auto-lifted parameters @p and @q,
then [F][G] is implicitly converted to something like
[EMAIL PROTECTED] @q - [F] { @p = @p } ( [G] { @p = @p, @q = @q } ).

Finally, introduce the following syntax:

* As an expression, ?x is short for [EMAIL PROTECTED] - @x.

* On the left hand side of the = sign in a named application, ?x is
  the same as @x.

* For backward compatibility, let ?x = [E] in [F] should be treated
  as equivalent to [F] { ?x = [E] }.

Now we have something almost the same as the current implicit-parameter
system, except that it behaves in a much safer and saner way.

For example, looking at the confusing expressions from the beginning again:

f x = let g y = ?foo in g

This obviously has type (?foo :: c) - a - b - c. It doesn't
matter where the ?foo parameter appears in the type because it will
always be referred to explicitly, by name, exactly once in each
call of f.

let ?x = 1 in let g = ?x in let ?x = 2 in g

This reduces as follows:

  let ?x = 1 in let g = ?x in let ?x = 2 in g
  ( let g = [EMAIL PROTECTED] - @x in g { @x = 2 } ) { @x = 1 }

Re: *safe* coerce, for regular and existential types

2003-08-02 Thread oleg

 Does this technique extend to polymophic types?
Yes, of course. The type F a b in the earlier message was polymorphic.

 Let's say we have the following type:

  data D a = C | D a

 Is it possible to index the type D a?

I have just lifted the polymorphic Maybe -- which is isomorphic to
your type. 
ti maybe_decon (Just True)
ti maybe_decon (Just 'a')
give different results. (ti maybe_decon Nothing) can give either the
same or different indices for different concrete types of
Nothing. It's all up to you. For each new datatype, the user has to
provide two functions: one to deconstruct the datatype into a
polymorphic array of values of already indexable types, and the other
is to re-construct the datatype from the array. As long as the user
can do that -- in _any_ way he wishes -- the mapping is
established. Incidentally, there is no need to add any new type
instances or add new alternatives to datatype declarations. There is
no need to extend the type heap either.

I could post the code but I need to write explanations and perhaps
change a few identifier names to something more meaningful. Alas, it's
already almost 2am, and I want to go home...
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: *safe* coerce: four methods compared

2003-08-02 Thread Ralf Laemmel
[EMAIL PROTECTED] wrote:
 
 This is a Related Work section of the previous message.

 ... again cunning stuff omitted ...


I buy most of this
but IMHO you should make very clear 
that there is not just a single safeCoerce, but the TI/init_typeseq
argument has to be constructed and supplied by the programmer
in a way that (s)he decides what array of types can be handled.
So if you wanted to use your approach to scrap boilerplate [1],
say deal with many datatypes, this becomes quite a burden.
Think of actually building initial type sequences. Think of
how combinators need to be parameterised to take type sequences.
(That's what I called a CWA yesterday.)

On the other hand, you mention this duality between type classes
vs. type heaps. Yes, I would say that type classes and type case
are somewhat dual. You provide a type case. What I like about your
type case vs. the approach taken in [1] is that your type case will
be very precise. That is, you don't say one can just try anything
what is Typeable but you rather restrict questions to the types 
in the supplied initial type sequence. This is certainly beneficial
for applications other than scraping boilerplate.

Ralf

[1}  Scrap your boilerplate: a practical design pattern for generic
programming 
 by Ralf Lämmel and Simon Peyton-Jones, 
 appeared in Proceedings of TLDI 2003, ACM Press 
 http://www.cs.vu.nl/boilerplate/#paper

-- 
Ralf Laemmel
VU  CWI, Amsterdam, The Netherlands
http://www.cs.vu.nl/~ralf/
http://www.cwi.nl/~ralf/
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Haskell for educative games

2003-08-02 Thread Andre W B Furtado
Does anyone know if Haskell is/was used to develop educative games? Do you
recommend some papers on the subject?

Thanks a lot,
-- Andre Furtado
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Laziness

2003-08-02 Thread Jon Fairbairn
On 2003-08-02 at 14:36PDT Dominic Steinitz wrote:
 Could someone explain to me why this doesn't work
 
 test l =
hs
   where
  hs = map (\x - [x]) [0..abs(l `div` hLen)]
  hLen   = length $ head hs
 
 whereas this does
 
 test l =
hs
   where
  hs = map (\x - [x]) (0:[1..abs(l `div` hLen)])
  hLen   = length $ head hs
 
 I would have thought laziness would allow the compiler to
 know that hs would contain at least one element and
 therefore calculate hLen.

Laziness isn't enough to tell it that. It would also have to
know that abs never returns an answer less than zero 
([0 .. -1] == []).

All the compiler knows is that abs returns an integer.

  Jón

PS I don't know the general policy, but I for one dislike
getting emails in HTML unless it's /absolutely/ necessary for
the content. Multipart/alternative doesn't help much either.


-- 
Jón Fairbairn [EMAIL PROTECTED]


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


Re: The madness of implicit parameters: cured?

2003-08-02 Thread Derek Elkins
On Sat, 2 Aug 2003 00:45:07 -0700 (PDT)
Ben Rudiak-Gould [EMAIL PROTECTED] wrote:

 When I first learned about implicit parameters I thought they were a
 great idea. The honeymoon ended about the time I wrote some code of
 the formlet ?foo = 123 in expr2, where expr2 used ?foo implicitly,
 and debugging eventually unearthed the fact that ?foo's implicit value
 was not being set to 123 in expr2. That was enough to scare me off of
 using implicit parameters permanently.
 
 More recently, I've realized that I really don't understand implicit
 parameters at all. They seemed simple enough at first, but when I look
 at an expression like
 
 f x = let g y = ?foo in g
 
 I realize that I have no idea what f's type should be. Is it
 
 (?foo :: c) = a - b - c
 
 or is it
 
 a - ((?foo :: c) = b - c)

Do you have problems finding the type of

f x = let g y = 4 in g
?
it works -EXACTLY- the same way.

 
 ? As far as I can tell, these are not the same type: you can
 distinguish between them by partially applying f with various
 different values of ?foo in the implicit environment. 

If you do apply f you get (?foo :: c) = b - c.

GHC tells me
 that f has the former type, but I still have no idea why: is it
 because g has an implicit ?foo parameter and f implicitly applies its
 own ?foo to g before returning it? Why would it do that? Or is it
 because ?foo is here interpreted as referring to an implicit parameter
 bound in the call of f, instead of in g? That doesn't make sense
 either.

The constraint should just be thought of as an extra explicit
parameter, or think of it as using the same mechanism dictionary
passing for type classes uses. Implicit parameters aren't
as flexible as full dynamic scoping would be.  For example,

f g = let ?foo = 5 in g ()
g x = ?foo

f g :: {foo :: a) = a 
NOT
f g :: Num a = a
i.e. it doesn't evaluate to 5.  So you can't bind the free implicit
variables of a passed in HOF (basically you can't have type ({?foo :: t
= a - t) - b), and similarly you can't return HOF's with free
implicit parameters (no type a - ({?foo :: t = t - b))

If I'm not way rusty with CL, here are similar examples with full
dynamic scoping,
 (defvar *x* 0)
*X*
 (defun f (g) (let ((*x* 5)) (funcall g)))
F
 (defun g () *x*)
G
 (f #'g)
5
 (defun f (x) (defun g (y) *x*))
F
 (let ((*x* 1)) (f 'a))
G
 (funcall * 'b)
0
 (let ((*x* 2)) (funcall ** 'b))
2


 The final straw was:
 
 Prelude let ?x = 1 in let g = ?x in let ?x = 2 in g
 1
 Prelude let ?x = 1 in let g () = ?x in let ?x = 2 in g ()
 2
 
 This is insanity. I can't possibly use a language feature which
 behaves in such a non-orthogonal way.

Compare,

let g = () in (g 'a' 'b',g 1 2)

let g x y = x  y in (g 'a' 'b',g 1 2)

the problem with this is again -EXACTLY- the same because implicit
parameters behave very much like class constraints, because class
constraints pretty much ARE implicit parameters.  The problem here is
the monomorphism restriction.  This applies to implicit parameters as
well for the same reasons (and because implicit
parameters are very likely handled by the same code.)  In fact, if you
use -fno-monomorphism-restriction, your examples above give you the same
numbers.
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 5.04.3
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Loading package haskell98 ... linking ... done.
Prelude :set -fglasgow-exts
Prelude let ?x = 1 in let g = ?x in let ?x = 2 in g
1
Prelude let ?x = 1 in let g () = ?x in let ?x = 2 in g ()
2
Prelude :set -fno-monomorphism-restriction
Prelude let ?x = 1 in let g = ?x in let ?x = 2 in g
2
Prelude let ?x = 1 in let g () = ?x in let ?x = 2 in g ()
2

Whether your additions would be worthwhile anyways, I haven't really
thought about.

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


-------|ÓÅ»ÝÐéÄâÖ÷»ú£¡|------

2003-08-02 Thread webmaster

Ç×°®µÄÅóÓÑ£º
ÄúºÃ£¡
ÕâÊÇÀ´×ÔÏÃÃÅÊб¦Áé¿Æ¼¼ÍøÂçÓÐÏÞ¹«Ë¾µÄÎʺ¸ÐлÄúÊÕ¿´Õâ·âÓʼþ¡£ÎÒÃÇÕæ³ÏµÄÏ£Íû
ÄúÄܳÉΪÎÒÃÇÔÚ¹óµØÇøµÄÖØÒª»ï°é¡£ÎÒÃÇÊÇÒ»¼Ò²ÉÓÃÊÀ½ç¸ßм¼Êõ½á¾§£¬Ñо¿¡¢ÍƹãºÍ·¢Õ¹
м¼Êõ£¬ÖÂÁ¦ÓÚ»¥ÁªÍøÐÅÏ¢·þÎñ¡¢ÓòÃû×¢²á·þÎñºÍÐéÄâÖ÷»ú·þÎñµÄ¸ßм¼ÊõÆóÒµ¡£ÏêÇéÇëä¯
ÀÀ:http://www.host-china.com 
¹«Ë¾×Ô2003ÄêÆðÈ«Á¦½ø¾ü¹ú¼Ê»¥ÁªÍø·þÎñÁìÓò£¬ÕûºÏÍƳöÁËÒÔϲúÆ·¡£ËùÓпռ䶼֧³Ö
Êý¾Ý¿â£¨linux+PHP+Mysql;NT+asp+acess£©¡£Õ⽫»áÊÇÄú³¬ÖµµÄÑ¡Ôñ¡£
1.30M¿Õ¼ä+30MÆóÒµÓÊ¾Ö + ËÍÒ»¹ú¼ÊÓòÃû £¬¹¦ÄÜÈ«Ã棬½öÊÛ198Ôª/Äê¡£
2.120M¿Õ¼ä£«120MÆóÒµÓÊÏ䣫1¸ö¹ú¼ÊÓòÃû£¬¹¦ÄÜÈ«Ã棬½öÊÛ330Ôª/Äê¡£
3.200M¿Õ¼ä£«50MÆóÒµÓÊÏ䣫1¸ö¹ú¼ÊÓòÃû£¬¹¦ÄÜÈ«Ã棬½öÊÛ450Ôª/Äê¡£
4.300M¿Õ¼ä£«50MÆóÒµÓÊÏ䣫1¸ö¹ú¼ÊÓòÃû£¬¹¦ÄÜÈ«Ã棬½öÊÛ580Ôª/Äê¡£

¾¡¹ÜÎÒÃǾ¡Á¦ÎªÄúÌṩ×îºÃµÄ·þÎñ¡££¬µ«²»Åųý³öÏÖʧÎó¡£Èç¹ûÊÇÕâÑù£¬ÎÒÃÇÄþÔ¸½ÓÊÜ
Í˿Ҳ²»»áÒòΪÄÄÅÂÒ»µãµãµÄ²»ÂúÒâ¶øÈÃÄú²»¿ªÐÄ¡£ËùÒÔÎÒÃdzÐŵ£ºÖ÷»ú²»ÂúÒⰴʵ¼ÊÓà
¶îÍË¿î¡£Çë²»ÒªÖ±½Ó»Ø¸´,»Ø¸´Çë·¢:[EMAIL PROTECTED]

×££º¿ªÐÄ£¡Ë³Àû£¡
webmaster of http://www.host-china.com 
ÏÃÃÅÊб¦Áé¿Æ¼¼ÍøÂçÓÐÏÞ¹«Ë¾
http://www.host-china.com
µç»°£º0592-5915491£¨ÈÈÏߣ©   0592-5652685¡¡
´«Õ棺0592-5652687
ÁªÏµÈË£ºÀîÏÈÉú ½ðС½ã
¡¡







































































---
·ÐµãȺ·¢Óʼþ,À´×ÔÈí¼þ¹¤³Ìר¼ÒÍø(http://www.21cmm.com)

½øCMMÍøУ(http://www.21cmm.com)£¬³ÉÏîÄ¿¹ÜÀíר¼Ò
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe