Re[2]: [Haskell-cafe] Haskell wiki: most popular pages

2006-08-19 Thread Bulat Ziganshin
Hello Tim,

Friday, August 18, 2006, 8:23:16 PM, you wrote:

 I agree with that. The and = ... wasn't really an improvement over and
 xs = ... xs, and if the later is easier to read that's good.

the main goal here is readability, of course

 What happened to isSpace, toLower and toUpper (, from the tutorial)?

it seems that this list is incomplete. i don't found a lot of I/O
routines, such as interact or getContents

one more reason to move it to wiki :)

 I feel that Haskell is missing some basic string manipuation functions, like
 - replacing all occurances of one substring (or sublist) with another 
 string (or list).
 - tokenize a string by an arbitrary delimeter

MissingH library contains such routines, although it is gpl'ed

there is a (lazy) movement to establish such library, but noone still
started it. well, to write something new open-source programmer just
opens project and waits for contribution :)  who is darcs maintainer on
haskell.org?


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] C++ class = neutered (haskell class + haskellexistential)

2006-08-19 Thread Bulat Ziganshin
Hello Brian,

Friday, August 18, 2006, 8:54:08 PM, you wrote:
 http://haskell.org/haskellwiki/OOP_vs_type_classes
 although i mentioned not only pluses but also drawbacks of type
 classes: lack of record extension mechanisms (such at that implemented
 in O'Haskell) and therefore inability to reuse operation
 implementation in an derived data type...

 You can reuse ops in a derived data type but it involves a tremendous amount
 of boilerplate.

of course, but it's just OOP emulation. one can do the same in C, for
example.

i've added your letter to the page. but anyway, one of key OOP
ideas was extensible records, it was idea what distinguished OOP from
abstract data types approach



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] A backwards-compatible record proposal

2006-08-19 Thread Brian Hulley

Hi -
As I've been writing a Haskell program over the past few months the main 
problem I encounter is that record field names are not local to the record 
type, and any systematic way of making them local (eg by prepending 
_Tycon_) results in names that are just too clunky, and I feel that 
identifiers *must* use systematic naming conventions to get code that will 
be easy to understand and maintain.


Although it is relatively easy to think up a better record system, it has 
taken me up till now to discover how such a system could be integrated with 
Haskell as it is at the moment, since it's unlikely that the existing record 
system will ever disappear, at least not in the next few years, and in fact, 
there are some good points about the existing record system that I wouldn't 
like to lose.


I'll motivate the proposal then talk about how it could be implemented.

Motivation
===

Consider the following:

   data Vector3 a = Vector3{x :: a, y::a,  z::a }

   data Normal3 a = Normal3{x :: a, y::a, z::a }

We've got a problem because (x) has been introduced twice to the top level 
namespace. In the above example, it could be argued that I should have 
written:


   data Arr3 a = Arr3 {x::a, y::a, z::a}

   newtype Vector3 a = Vector3 (Arr3 a)
   newtype Normal3 a = Normal3 (Arr3 a)

but for the sake of argument, let's suppose we can't do this - perhaps one 
of the record types has some different fields as well.


A related problem is suppose I have:

   data Size = {width :: Int, height :: Int}

   data Rect = Rect{x1, y1, x2, y2::Int}

   width :: Rect - Int
   width Rect{x1,_,x2,_} = x2 - x1

because a record field of Size has the same name as a top level function.

This second conflict can be avoided by always using the rule that record 
fields begin with an underscore and all other variables don't.


So applying this to the first problem, we have:

   data Vector3 a = Vector3{_x :: a, _y::a,  _z::a }
   data Normal3 a = Normal3{_x :: a, _y::a, _z::a }

Of course we haven't solved it yet!

But now suppose we introduce a new piece of syntactic sugar, and write:

   data Vector3 a = Vector3{.x :: a, .y::a,  .z::a }
   data Normal3 a = Normal3{.x :: a, .y::a, .z::a }

ie putting a '.' before each field name. The intended meaning is that dotted 
field names do *not* generate top level functions. Instead they allow the 
compiler to generate instance decls as follows, where we've introduced a new 
form of identifier, the dotted id, which behaves as a postfix operator which 
binds more tightly than function application and can also be used as a class 
name (by the compiler only):


   class (.x) :: a b | a - b where
   (.x) :: a - b

   class (.y) :: a b | a - b where
   (.y) :: a - b

   class (.z) :: a b | a - b where
   (.z) :: a - b

For each dotted id, there is a class defined as above, which is available 
globally to the whole program as if a module containing an infinite set of 
class decls as above was exported by the Prelude.


In the module containing the data decl for the record, the compiler inserts 
the following:


   instance (.x) (Vector3 a) a where
   (.x) v = ... -- compiler generated code to access the field

Then within the rest of the program we can write:

   magSquared :: Num a = Vector3 a - a
   magSquared v = v.x*v.x + v.y*v.y + v.z*v.z

   -- explicit type when specific function is required
   vec_x = ((.x) :: (Vector3 a - a))

The advantage of this proposal is that it is completely backwards compatible 
with records as they are at the moment, and we can choose which fields we 
want to be dotted and which we want to just keep as normal top level 
functions.


The only extra thing we need to do is put a dot before the field names we 
want to access via the dotted syntax, but we in any case needed to use an 
underscore when we wanted a systematic way to avoid conflicts between field 
names and other top-level names so there is no extra effort involved.


Implementation
==

The above could almost be implemented just by parsing a source file 
containing uses of dotted fields and using a conversion like:


   data Rec a = Rec { .f :: a}

   let
   rec = Rec {.f = 78}-- dot is used here too
   p = rec.f * rec.f

==

   data Rec a = Rec a

   instance Dot__f (Rec a) a where
   __dot_f (Rec a) = a

   let
   rec = Rec 78
   p = __dot_f rec * __dot_f rec

So far so good, but the alert reader :-) will have noticed that we now have 
a *major* problem with abstraction because although we can write:


   module M (Rec) where ...

code in another module can still say rec.f because in Haskell, all instance 
decls in a module are always exported [1]. This problem may disappear in 
Haskell' [2]. http://hackage.haskell.org/trac/haskell-prime/ticket/19


Therefore I think the desugaring would need to take place in the compiler so 
the compiler could avoid exporting the compiler-generated instances when the 
fields are not present in the module 

[Haskell-cafe] Re: iterative algorithms: how to do it in Haskell?

2006-08-19 Thread Gene A

Hi,
 Here is a little thing I came up with to simulate the construct for
x:= n1 to n2 and for x:=n1 to n2 by n3  from purely imperative
world to use in Haskell,  I call the functions fromto  and fromtoby..
they also take a function which consumes the x component and uses it
in the computation.   Just syntactic sugar.. best to wean off of this
way of doing things.. but that is one of the nice things about
Haskell, you CAN do this sort of thing easily.

The definitions:
fromto :: forall b a. Enum a = a - a - (a - b) - [b]
fromto a b f = map f [a..b]

-- --

fromtoby :: forall a b.
   (Num a, Enum a) =
   a - a - a - (a - b) - [b]

fromtoby a b c f = map f [a,a+c..b]

-- --
Some applications using ghci with enhancements turned on...

*Iteration fromto 10 25 id
[10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25]  --raw list using id
*Iteration fromto 10 25 (2*)
[20,22,24,26,28,30,32,34,36,38,40,42,44,46,48,50]  -- list times 2

*Iteration fromtoby 1 12 2 id -- using id to show what the base list is
[1,3,5,7,9,11]
*Iteration fromtoby 1 12 2 (flip (^) 3)  -- cubing of the base list above..
[1,27,125,343,729,1331]

*Iteration fromtoby 12 42 3  id
[12,15,18,21,24,27,30,33,36,39,42]   -- raw list gen'd by  id
*Iteration fromtoby 12 42 3  (flip (**) 0.33)
[2.2894284849170297, 2.4662120741078493,  -- approx. cube roots
2.6207413939563993,2.7589241761011336,
2.884499140309247,2.9670416,
3.1072325056015817,3.2075343296219874,
3.3019272485002094,3.391211442600036,
3.4760266444533747]

Greetings from the Yuma Desert,
gene
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A backwards-compatible record proposal

2006-08-19 Thread Brian Hulley

Brian Hulley wrote:

In the module containing the data decl for the record, the compiler
inserts the following:

   instance (.x) (Vector3 a) a where
   (.x) v = ... -- compiler generated code to access the field


instance (.x) (Vector3 a) a where
   (.x) Vector3{.x = x} = x

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


Re: [Haskell-cafe] Re: iterative algorithms: how to do it in Haskell?

2006-08-19 Thread Henk-Jan van Tuyl

On Sat, 19 Aug 2006 10:28:33 +0200, Gene A [EMAIL PROTECTED] wrote:

*Iteration fromtoby 1 12 2 (flip (^) 3)  -- cubing of the base list  
above..


An easier way to write this:
fromtoby 1 12 2 (^3)

[...]

*Iteration fromtoby 12 42 3  (flip (**) 0.33)


fromtoby 12 42 3  (**0.33)



Greetings from the Yuma Desert,
gene
___


Greetings from Holland,
Henk-Jan van Tuyl

--
http://Van.Tuyl.eu/
--

Using Opera's revolutionary e-mail client:
https://secure.bmtmicro.com/opera/buy-opera.html?AID=789433

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


Re: [Haskell-cafe] automatic instance derivation

2006-08-19 Thread Bulat Ziganshin
Hello Greg,

Saturday, August 19, 2006, 3:42:45 AM, you wrote:

 -- Is something like this possible?
 derive Show Val2

yes, in proposal :)

well, the best practical way i know is to use Template Haskell / DrIFT.
I can give your a TH module which generates Show instances. So, using
it will as easy as

import THShow

$(deriveShow Val2)

of course, TH is GHC-only solution. you can prefer DrIFT what is a
general preprocessor and afair it contains a lot of prewritten
instance-generation modules


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Haskell wiki: most popular pages

2006-08-19 Thread Tamas K Papp
On Fri, Aug 18, 2006 at 04:46:14PM +0400, Bulat Ziganshin wrote:
 Hello Tim,
 
 Friday, August 18, 2006, 4:26:46 PM, you wrote:
 
  break p = span (not . p)
 
 it's definitely better
 
  and = foldr () True
 
 i think that definitions with omitted arguments can be more hrd to
 understand to newbie haskellers, especiallyones who not yet know the
 language. as Tamas suggests, this page can be used to present to such
 newbies taste of Haskell so listing all the parameters may allow to
 omit unnecessary complications in this first look into language

I think I learned to understand and appreciate omitted arguments from
Hal Daume's Yet Another Haskell Tutorial.  The exercises there are
just great.

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


RE: [Haskell-cafe] HTTPS in Haskell

2006-08-19 Thread Pasqualino 'Titto' Assini
Hi Adam,

I believe that this is simply to detect that the WASH CGI script is being
invoked using HTTPS while running into a Web server (say Apache) that
supports it.

   titto


 -Original Message-
 From: [EMAIL PROTECTED] [mailto:haskell-cafe-
 [EMAIL PROTECTED] On Behalf Of Adam Peacock
 Sent: 19 August 2006 02:34
 To: Haskell-Cafe@haskell.org
 Subject: Re: [Haskell-cafe] HTTPS in Haskell
 
 On 8/18/06, Pasqualino 'Titto' Assini [EMAIL PROTECTED] wrote:
 
  Is there any implementation of HTTPS/SSL in Haskell?
 
 
 
  This would seem to be critical to develop commercial web applications.
 
 WASH has a run time function ( runWithOptions ) that has type:
 
 runWithOptions :: CGIOptions - CGI () - IO ()
 
 with...
 
 type CGIOptions = [CGIOption]
 
 data CGIOption =
 
 AutoHttps -- autodetect Https by checking for port number 443 and env var
 HTTPS
 ...
 
 Taken from:
 
 http://www.informatik.uni-freiburg.de/~thiemann/WASH/doc/WASH-CGI-CGI.html
 
 Adam.
 ___
 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] A backwards-compatible record proposal

2006-08-19 Thread Bernard James POPE
On Sat, Aug 19, 2006 at 09:21:34AM +0100, Brian Hulley wrote:
 Therefore I think the desugaring would need to take place in the compiler 
 so the compiler could avoid exporting the compiler-generated instances when 
 the fields are not present in the module export list.

I'm not entirely sure I understand you here, but something to consider is 
how well the sytem can be handled by something which is not a compiler,
but a code transformer. Something like Hat or buddha.

For tools like these, it is important that a desugared program is still a
valid (source level) program. (Haskell 98 is close to this, but not 100% 
- unfortunately). 

Desugaring sometimes introduces new code into a program (for instance
the deriving rules), a program transforming tool will most likely have to
apply its transformation to that introduced code. Therefore, to transform
a Haskell program you have to desugar it (somewhat) first. We want 
the result to remain a valid Haskell program, so it can be accepted by
an ordinary compiler.

(Please forgive me if your scheme already allows this). 

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


Re: [Haskell-cafe] Re: iterative algorithms: how to do it in Haskell?

2006-08-19 Thread Lennart Augustsson

On Aug 19, 2006, at 05:14 , Henk-Jan van Tuyl wrote:



[...]

*Iteration fromtoby 12 42 3  (flip (**) 0.33)


fromtoby 12 42 3  (**0.33)


And why approximate so much?

fromtoby 12 42 3 (** (1/3))

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


[Haskell-cafe] Re: iterative algorithms: how to do it in Haskell?

2006-08-19 Thread Gene A

Hi Lennart,

 This morning when I posted..it was about 2:30am and had been up a
long time... bad habits.. I sent a message to Henk-Jan to that effect,
but didn't send to the entire list.. anyway thanks to both for the
followups... I still tend to sometimes do things the hard way in
Haskell.  Started trying to learn it starting in I think Nov-Dec. of
2005, so not too awfully long, but with a lot of other things soaking
up time, not as far along as I wished to be in even this amount of
time... Most interesting language I have used yet.

but yes not sure why not the precision.. but I think when I tried
that with the way I had the thing in the original, I used  (**) 1/3
and got an error message which I was too tired to even read,..and just
changed it to 0. or whatever  however many 3's , and just
got it posted.. I don't think that those functions are of much use,
the thing was that when I wrote them, not at 2AM in the morning, I
remember thinking just how easy it was to do pretty much anything you
want with this language.. Off topic, but one of my tests of a
language, old habit this, is as soon as I know enough to be dangerous,
I try writing a forth interpreter in it.  I have started such a thing,
a module I call Hforth, and it is operational, but do to the nature of
lists not holding homogeneos values in Haskell everything has to be
stored with String values.  This has the result of having to apply
show function to store numerics to the stack and then to use the read
function to convert back when popping the stack.. .. hmm still
tired... Anyway the upshot is that a very rudimentary interpreter is
up and running to do simple things with just builtins so far, but was
built in a matter of some fairly small number of hours.  Doesn't
support line editing yet, so really not too good, but does support
pushing strings and concatenation and some other things that are more
tedious to write as primatives in other languages..  The only other
language that was as easy to get to this stage with was scheme.

Sorry for the ramble,
gene

On 8/19/06, Lennart Augustsson [EMAIL PROTECTED] wrote:

On Aug 19, 2006, at 05:14 , Henk-Jan van Tuyl wrote:


 [...]
 *Iteration fromtoby 12 42 3  (flip (**) 0.33)

 fromtoby 12 42 3  (**0.33)

And why approximate so much?

fromtoby 12 42 3 (** (1/3))



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


[Haskell-cafe] Problem getting started with graphics library in GHC on Windows

2006-08-19 Thread Tomi Maila
Hi,

I'm a Haskell newbie. I've been studying Haskell by reading the book The
Haskell School of Expression. Most of the example in the book use
graphics library SOEGraphics. Windows GHC didn't find the library, but I
assumed that the new name for the library is Graphics.SOE which seemed
to properly loaded.

The problem is that I fail to get the Graphics library to work properly.
Instead GHC freezes if I use the graphics library in interactive mode
and if I compile into a binary the binary freezes. The problem is not
only with Graphics.SOE but also with more general Graphics.HGL.

If I execute the Hello World program presented in Graphics.HGL
documentation front page,  GHC interactive mode freezes after opening
the window  but before drawing any text on the window.  Compiled binary
never even opens a window but freezes before that. Examples in HSOE (the
book) behave the exactly the same way. I get not error messages what so
ever. The example I refer to above is below.

 module Main where

 import Graphics.HGL

 main :: IO ()
 main = runGraphics $
withWindow_ Hello World Window (300, 200) $ \ w - do
drawInWindow w $ text (100, 100) Hello World
drawInWindow w $ ellipse (100, 80) (200, 180)
getKey w


 
The question is what I could be doing wrong or is Graphics library just
incompatible with my environment. I'm using GHC 6.4.2 on Windows XP SP2.
I've been developing using Eclipse 3.2 with EclipseFP plugin. However
I've also tried to compile on command line. Could somebody help me over
(no I'm not moving to Linux...)

Cheers,

Tomi

-- 
Tomi Maila
Research scientist

Bio- ja ympäristötieteiden laitos   Department of Biological 
Biotieteellinen tiedekunta  and Environmental Sciences
PL 65 (Viikinkaari 1)   P.O. Box 65 (Viikinkaari 1)
00014 HELSINGIN YLIOPISTO   00014 UNIVERSITY OF HELSINKI
puhelin (09) 191 59837  tel. +358-9-191 59837
matkapuh. 040 554 9024  mobile. +358-40-554 9024

http://www.helsinki.fi/~tmaila/ 


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


[Haskell-cafe] Useful: putCharLn {inspire by the Int-[Char] thread

2006-08-19 Thread Gene A

The thread on the use of show and print to display an Int value,
brought up a problem I had early on... the one of cleanly displaying a
Char value, on a line all by itself.. My first attempts:

This was just plain hard to read: with the character t being where it was:

Prelude putChar $ head this and that
tPrelude
---
So I tried this and of course ... type mismatch:

Prelude putStrLn $ head this and that
interactive:1:16:
   Couldn't match `String' against `Char'
 Expected type: [String]
 Inferred type: [Char]
   In the first argument of `head', namely `this and that'
   In the second argument of `($)', namely `head this and that'
--
So I did this... to manually turn it to a string and it does work, but
a little cumbersome to work into other function calls:
Prelude putStrLn $ (head this and that):[]
t
-
so the definition of putCharLn came to life {may be in some library already
and I just haven't found it yet.. but it is in my toolbox now}:

Prelude let putCharLn c = putStrLn (c:[])
Prelude
and an application of it:

Prelude putCharLn $ head this and that
t
---
now I also have the char to string conversion alone:

c2Str c = c:[]

Prelude let c2Str c = c:[]
Prelude c2Str 'A'
A
--
Now this is almost too trivial a thing to mention these gizmos...
what with all the monadic constructions that greater minds  toss
about on this list.. and I am trying to get understanding of that
still, but 
sometimes we just accept the unacceptable little irritants
rather than just code a solution, no matter how simple it is.
There are probably troves of simple workarounds out there
that seem too trivial to mention but hey, share 'em...
might hit a guy like me that says. now why didn't I think to do that?

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


Re: [Haskell-cafe] Useful: putCharLn {inspire by the Int-[Char] thread

2006-08-19 Thread Neil Mitchell

Hi


c2Str c = c:[]


This function is often known as box, its much more general than char
to string, it puts any single element in a list like box

Thanks

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


Re: [Haskell-cafe] Useful: putCharLn {inspire by the Int-[Char] thread

2006-08-19 Thread Niklas Broberg

 c2Str c = c:[]

This function is often known as box, its much more general than char
to string, it puts any single element in a list like box


... or 'return', which is in the Prelude already, but which is even
more general, it puts any single element into any (dare I say it)
monad, where a list is one example. :-)

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


[Haskell-cafe] Re: iterative algorithms: how to do it in Haskell?

2006-08-19 Thread Lennart Augustsson

There are much better ways than storing strings on the stack.
Like using a data type with constructors for the different types that
you can store.

-- Lennart

On Aug 19, 2006, at 11:51 , Gene A wrote:


Hi Lennart,

 This morning when I posted..it was about 2:30am and had been up a
long time... bad habits.. I sent a message to Henk-Jan to that effect,
but didn't send to the entire list.. anyway thanks to both for the
followups... I still tend to sometimes do things the hard way in
Haskell.  Started trying to learn it starting in I think Nov-Dec. of
2005, so not too awfully long, but with a lot of other things soaking
up time, not as far along as I wished to be in even this amount of
time... Most interesting language I have used yet.

but yes not sure why not the precision.. but I think when I tried
that with the way I had the thing in the original, I used  (**) 1/3
and got an error message which I was too tired to even read,..and just
changed it to 0. or whatever  however many 3's , and just
got it posted.. I don't think that those functions are of much use,
the thing was that when I wrote them, not at 2AM in the morning, I
remember thinking just how easy it was to do pretty much anything you
want with this language.. Off topic, but one of my tests of a
language, old habit this, is as soon as I know enough to be dangerous,
I try writing a forth interpreter in it.  I have started such a thing,
a module I call Hforth, and it is operational, but do to the nature of
lists not holding homogeneos values in Haskell everything has to be
stored with String values.  This has the result of having to apply
show function to store numerics to the stack and then to use the read
function to convert back when popping the stack.. .. hmm still
tired... Anyway the upshot is that a very rudimentary interpreter is
up and running to do simple things with just builtins so far, but was
built in a matter of some fairly small number of hours.  Doesn't
support line editing yet, so really not too good, but does support
pushing strings and concatenation and some other things that are more
tedious to write as primatives in other languages..  The only other
language that was as easy to get to this stage with was scheme.

Sorry for the ramble,
gene

On 8/19/06, Lennart Augustsson [EMAIL PROTECTED] wrote:

On Aug 19, 2006, at 05:14 , Henk-Jan van Tuyl wrote:


 [...]
 *Iteration fromtoby 12 42 3  (flip (**) 0.33)

 fromtoby 12 42 3  (**0.33)

And why approximate so much?

fromtoby 12 42 3 (** (1/3))




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


[Haskell-cafe] Re: A backwards-compatible record proposal

2006-08-19 Thread Brian Hulley

Gene A wrote:

On 8/19/06, Brian Hulley [EMAIL PROTECTED] wrote:
{...
magSquared v = v.x*v.x + v.y*v.y + v.z*v.z
...}

Hi,
  Won't the use of the dot lend confusion to the eye of the
beholder.. that as in the code fragment about that v.y or v.z is
implying function composition  I'll admit to being pretty new to
Haskell, but that is what it would look like to me.  Could, I think
cause some confusion to others reading a program with this construct,
and might fool some of the tools that some others have mentioned..
Would seem that parser could or would make that mistake?


Hi Gene,

In v.x or v   .x then .x is a single lexeme, whereas in v . x or v.   x 
the v and x are ids and the . is a symbol. In other words, the parser 
sees:


   v.x [VarId, DottedField]
   v.x [VarId, DottedField]
   v.x [VarId, VarSym, VarId]
   v  .  x [VarId, VarSym, VarId]

This works because the lexer just obeys the maximal munch rule ie reading 
from left to right eating up as many characters as possible to form each 
lexeme.


It's probably slightly confusing when seen as plain text, but if you used an 
editor that fontifies VarId's differently from DottedField's, the difference 
would be easily visible.


I think it would also become quite natural just as we already have:

   123.42vs123  .  42
   A.B.C.p  vsA.B.C   .   p

As you pointed out f.g at the moment means function composition. However 
there seems afaics to be an informal convention that spaces are always 
placed around the dot when used as an operator, since of course F.g means 
the g in module F as opposed to F . g. Therefore my proposal is not 
entirely backwards compatible, though there could perhaps be a compiler flag 
to prevent old code from being broken, or a tool to insert the required 
spaces into old code.


Best regards,
Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Useful: putCharLn {inspire by the Int-[Char] thread

2006-08-19 Thread Henk-Jan van Tuyl

On Sat, 19 Aug 2006 19:21:36 +0200, Gene A [EMAIL PROTECTED] wrote:

[...]

Prelude putStrLn $ (head this and that):[]


Or you could use:
  putStrLn [head This and that]

--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
--

Using Opera's revolutionary e-mail client:
https://secure.bmtmicro.com/opera/buy-opera.html?AID=789433

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


Re: [Haskell-cafe] automatic instance derivation

2006-08-19 Thread Greg Fitzgerald
 well, the best practical way i know is to use Template Haskell / DrIFTThat's too bad. I was hoping we could trivially solve Tim Newsham's XML problem by importing HaXml, automatically deriving Data and Typeable for HaXml's 'Content' data type, and then use 'everywhereM' from 
Data.Generics.Schemes to do his stateful XML transformation.-Greg

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


Re: [Haskell-cafe] A backwards-compatible record proposal

2006-08-19 Thread Brian Hulley

Bernard James POPE wrote:

On Sat, Aug 19, 2006 at 09:21:34AM +0100, Brian Hulley wrote:

Therefore I think the desugaring would need to take place in the
compiler so the compiler could avoid exporting the
compiler-generated instances when the fields are not present in the
module export list.


I'm not entirely sure I understand you here,


For example,

   module M (Rec) where

   data Rec a = Rec {f :: a}

means that the components of Rec are visible in module M but not from any 
other module ie Rec is an abstract data type. However if a dotted field was 
used, as in:


   module M (Rec) where

   data Rec a = Rec {.f :: a}

we'd also like the fields of Rec to be inaccessible from outside, but since 
(.f) is a global typeclass, and module M contains an instance of (.f) (Rec 
a) a, and since any module which imports M always sees all instances that M 
sees, in particular it would see the instance (.f) (Rec a) a and therefore 
be able to inspect values of (Rec a) thus breaking the module abstraction 
barrier.


The problem is that the inability to prevent instances from being exported 
from a module breaks the abstraction, so all though everything in the 
proposal can be desugared into plain Haskell (with MPTC/FD) the caveat is 
that we would lose abstraction with this simple method.


However I think it could be solved by a more complex desugaring:

   module M (Rec, use) where

   data Rec a = Rec {f :: a}

   use :: Rec a - (a,a)
   use r = (r.f, r.f)

by introducing a newtype and adding wrappers to functions as follows:

   module M (Rec, use) where

   import DotClasses.Dot_f-- every class has its own module (*)

   data Rec' a = Rec a
   newtype Rec a = Rec (Rec' a)

   instance Dot__f  (Rec' a) a where
   __dot_f (Rec' x) = x

   use :: Rec a - (a,a)
   use (Rec r) = use' r

   use' :: Rec' a - (a,a)
   use' r = (r.f, r.f)

All code in the source module that uses Rec is renamed to syntactically 
isomorphic code using Rec' instead, and exported functions are replaced by 
wrappers to renamed versions of the original functions. Any code outside the 
module can only see Rec and not Rec' so the abstraction is preserved.



but something to
consider is how well the sytem can be handled by something which is
not a compiler, but a code transformer. Something like Hat or buddha.

For tools like these, it is important that a desugared program is
still a valid (source level) program. (Haskell 98 is close to this,
but not 100% - unfortunately).

Desugaring sometimes introduces new code into a program (for instance
the deriving rules), a program transforming tool will most likely
have to apply its transformation to that introduced code. Therefore,
to transform a Haskell program you have to desugar it (somewhat)
first. We want
the result to remain a valid Haskell program, so it can be accepted by
an ordinary compiler.


With the more complex desugaring described above the result would be 
ordinary Haskell code (though not H98 due to MPTC and FD for the Dot_* 
classes).


(*) Since it might be unwieldy to try to build a single module containing 
all the dot classes used in an entire program and all libraries, a simple 
solution is to just have a separate directory to store dot classes then the 
rule would be when the desugaring tool encounters a dotted field in a data 
decl, it would check to see if the module DotClasses.Dot_f already exists, 
and if it doesn't, then it would create the module:


   module DotClasses.Dot_f where

   class Dot_f a b | a - b
   __dot_f :: a - b

Each dotted field that appears in any code in a module would give rise to an 
import DotClasses.Dot_ directive.
(If the module used libraries that were not also desugared then the ensure 
Dot_ module created operation would have to be done for all dotted fields 
used anywhere in the module, not just in data decls.)


Thus there appears to be a fairly straightforward algorithm for desugaring 
to code that could be readily accepted without needing to change the 
compiler (or other tools) after all. Of course the usefulness of error 
messages etc would be improved if the tools could deal with unsugared 
source.


Best regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] A backwards-compatible record proposal

2006-08-19 Thread Brian Hulley

Ooops! ;-)

Brian Hulley wrote:

   module M (Rec, use) where

   import DotClasses.Dot_f-- every class has its own module (*)

   data Rec' a = Rec a
   newtype Rec a = Rec (Rec' a)

   instance Dot__f  (Rec' a) a where


 instance Dot_f  (Rec' a) a where


   __dot_f (Rec' x) = x

   use :: Rec a - (a,a)
   use (Rec r) = use' r

   use' :: Rec' a - (a,a)
   use' r = (r.f, r.f)


 use' r = (__dot_f r, __dot_f r)


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


Re: [Haskell-cafe] A backwards-compatible record proposal

2006-08-19 Thread Brian Hulley

Brian Hulley wrote:

However I think it could be solved by a more complex desugaring:


The proposed desugarings allow us to either make all dotted fields in a 
record visible, or none of them visible, but I don't think there exists a 
desugaring that would allow some to be visible while others were hidden.


However this wouldn't be a problem because we could just have the rule that 
if people want to use dotted fields, they must either export all the fields 
in the record or no fields in the record (including non-dotted fields).


This restriction could later be relaxed when tools/compilers etc implemented 
dotted fields directly.


I don't think it's that important as I've never encountered a situation 
where I wanted to make only part of a record visible - I suppose I'm just an 
all or nothing person ;-)


Apologies for the multiple posts,
Brian.

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


Re: [Haskell-cafe] rand* why not of type State g a

2006-08-19 Thread Henning Thielemann

On Sun, 13 Aug 2006, Marc Weber wrote:

 the rand* function are examples for a typical state usage,  arent' they?
 Is there any reasoon why they are not defined 
   RandomGen g = State g a
 rather than
   RandomGen g = (a,a) - g - (a,g)
 ?

It's probably because Control.Monad.State belongs to the MTL which is
outside Prelude. Nonetheless I find it also more convenient to use the
State monad for random number generators:
 http://darcs.haskell.org/htam/src/Stochastic.hs
 http://www.haskell.org/pipermail/haskell-cafe/2005-May/009775.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rand* why not of type State g a

2006-08-19 Thread David Menendez
Henning Thielemann writes:

 
 On Sun, 13 Aug 2006, Marc Weber wrote:
 
  the rand* function are examples for a typical state usage,  arent'
they?
  Is there any reasoon why they are not defined 
RandomGen g = State g a
  rather than
RandomGen g = (a,a) - g - (a,g)
  ?
 
 It's probably because Control.Monad.State belongs to the MTL which is
 outside Prelude.

On the other hand, if you are using MTL, you'd probably want a more
general signature, like:

(RandomGen g, MonadState g m) = m a
-- 
David Menendez [EMAIL PROTECTED] | In this house, we obey the laws
http://www.eyrie.org/~zednenem  |of thermodynamics!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] C++ class = neutered (haskell class + haskell existential)

2006-08-19 Thread Gabriel Dos Reis
John Meacham [EMAIL PROTECTED] writes:

| On Tue, Aug 15, 2006 at 08:36:28PM +0200, Gabriel Dos Reis wrote:
|  Roughly Haskell type classes correspond to parameterized abstract
|  classes in C++ (i.e. class templates with virtual functions 
|  representing the operations).  Instance declarations correspond to
|  derivation and implementations of those parameterized classes.
| 
| There is a major difference though, in C++ (or java, or sather, or c#,
| etc..) the dictionary is always attached to the value, the actual class
| data type you pass around.

I suspect that most of the confusion come from the fact that people
believe just because virtual functions are attached to objects, 
they cannot attach them to operations outside classes.  That, to my
surprise, hints at a deeper misappreciation of both type classes and
so-called OO technology.  Type classes are more OO than one might
realize. 

The dictionary can be attached to the operations (not just to the values) by
using objects local to functions (which sort of matierialize the
dictionary).  Consider

// Abstract class for a collection of classes that implement
// the Num mathematical structure
templatetypename T
  struct Num {
  virtual T add(T, T) const = 0;
  };

// Every type must specialize this class template to assert
// membership to the Num structure.  
templatetypename T struct Num_instance;

// The operation + is defined for any type that belongs to Num.
// Notice, membership is asserted aby specializing Num_instance.
templatetypename T
  T operator+(T lhs, T rhs)
  {
 const Num_instanceT instance;  
 return instance.add(lhs, rhs);
  }

// Foo is in Num
struct Num_instanceFoo : NumFoo {
   Foo add(Foo a, Foo b) const { ... }
};


The key here is in the definition of operator+ which is just a formal
name for the real operation done by instance.add().

I appreciate that inferring and building the dictionary (represented
here by the instance local to operator+T) is done automatically by
the Haskell type system.
That is  one of the reasons why the type class notation is a nice sugar.
However, that should not distract from its deerper OO semantics.


[...]

| in haskell you can do
| 
| class Monoid a where
| mempty :: a
| 
| in OOP, this cannot be done because where does the dicionary come from?

See above.  I believe a key in my suggestion was paramaterized
abstract classes, not just abstract classes.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] C++ class = neutered (haskell class + haskell existential)

2006-08-19 Thread Gabriel Dos Reis
Bulat Ziganshin [EMAIL PROTECTED] writes:

| Hello Thomas,
| 
| Friday, August 18, 2006, 7:57:13 AM, you wrote:
| 
|  There is a major difference though, in C++ (or java, or sather, or c#,
|  etc..) the dictionary is always attached to the value, the actual class
|  data type you pass around. in haskell, the dictionary is passed
|  separately and the appropriae one is infered by the type system. C++
|  doesn't infer, it just assumes everything will be carying around its
|  dictionary with it.
| 
|  C++ programmers deal with this using a number of techniques, mostly
|  involving templates.
| 
| Haskell type classes are closer to templates/generics than to classes
| itself

I believe Haskell type classes are closer to *parameterized abstract
classes* than to classes.

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


Re: [Haskell-cafe] C++ class = neutered (haskell class + haskell existential)

2006-08-19 Thread Gabriel Dos Reis
Bulat Ziganshin [EMAIL PROTECTED] writes:

| Hello John,
| 
| Friday, August 18, 2006, 5:16:45 AM, you wrote:
| 
|  There is a major difference though, in C++ (or java, or sather, or c#,
|  etc..) the dictionary is always attached to the value, the actual class
|  data type you pass around. in haskell, the dictionary is passed
|  separately and the appropriae one is infered by the type system.
| 
| your letter is damn close to that i wrote in
| http://haskell.org/haskellwiki/OOP_vs_type_classes
| although i mentioned not only pluses but also drawbacks of type
| classes: lack of record extension mechanisms (such at that implemented
| in O'Haskell) and therefore inability to reuse operation
| implementation in an derived data type, lack of downcasting mechanism
| (which bites me all the way), requirement to rebuild dictionaries in
| polymorphic operations what is slow enough

I would appreciate if you could revise the comparison based on the
material I just sent, that illustrates my earlier comments.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe