Re: string to Integer

2000-04-07 Thread Jon Fairbairn

 Then, the question is why we write
   result = function operand1 operand2
 instead of
   operand1 operand2 function = result
 
 I actually think the latter is cooler.  :)

I think there may be cultural influences about word order and/
or writing direction creeping in here :-)
-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH+44 1223 570179 (after 14:00 only, please!)






Re: string to Integer

2000-04-07 Thread George Russell

Jon Fairbairn wrote:
 
  Then, the question is why we write
result = function operand1 operand2
  instead of
operand1 operand2 function = result
 
  I actually think the latter is cooler.  :)
 
 I think there may be cultural influences about word order and/
 or writing direction creeping in here :-)
There are mathematicians who put the function after its argument.
But I'm pretty sure they are in the minority.




Re: string to Integer

2000-04-07 Thread Frank Atanassow

Yuichi Tsuchimoto writes:
   Or look at o's and flippo's types:
   
(.)  :: ((a - b) - (c - a)) - (c - b)
flip (.) :: ((a - b) - (b - c)) - (a - c)
   
   Surely the second one is much cooler!
  
  Yes, indeed!
  
  Then, the question is why we write
result = function operand1 operand2
  instead of
operand1 operand2 function = result

As a question of notation, I think the difference is that you use the
diagrammatic notation (flip (.)) when you want to emphasize the process of
computing something (buzzword, "imperative"). If you read left-to-right then
you can see each stage of a transformation, in the order which it "logically"
occurs. On the other hand, the (.)-style notation emphasizes the declarative
viewpoint since, again reading left-to-right, you start with what you want
and refine down to what you're starting with.

In category theory one often writes commutative arrow diagrams to express
systems of equations. If you use the diagrammatic notation, it can be simpler
to follow paths in the diagram because, by convention, one prefers right- and
down-pointing arrows over left- or up-pointing ones.

If Haskell 98 had user-definable infix type expressions (and - wasn't part of
the syntax already), you could define the transpose of (-)

  type b - a = a - b

and then write the signature for (.) as follows:

  (c - a) - (c - b) - (b - a)

Using - in type signatures has the advantage that the first thing you see in
a signature is what is produced, rather than what is necessary to produce,
which is sometimes what you want when you have a set of algebraic functions
like John Hughes' pretty-printing library:

 text  :: Doc - String
 (+) :: Doc - Doc - Doc

However it does not work so nicely in Haskell since by convention we curry
everything, so the order of arguments is also reversed. If we used uncurried
functions more often the signature for cons

  cons :: List a - List a - a

would be more intuitive:

  cons :: List a - (a, List a)

(Incidentally, I think Roland Backhouse made this argument, i.e., that we
should prefer (-) to (-), although he was working with a relational calculus
rather than a functional one.)

-- 
Frank Atanassow, Dept. of Computer Science, Utrecht University
Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands
Tel +31 (030) 253-1012, Fax +31 (030) 251-3791





Re: string to Integer

2000-04-07 Thread Frank Atanassow

Frank Atanassow writes:
  Using - in type signatures has the advantage that the first thing you see in
  a signature is what is produced, rather than what is necessary to produce,
  which is sometimes what you want when you have a set of algebraic functions
  like John Hughes' pretty-printing library:
  
   text  :: Doc - String
   (+) :: Doc - Doc - Doc

On re-reading this I see my point was not so clear. What I wanted to indicate
is that the functions of an algebra have a common codomain, like Doc, so
putting it first in a signature emphasizes the commonality between
them. Combinator languages and monads (the extra operations are generally
typed as X - M Y, for a monad M) are pretty common in Haskell, so by that
token (-) might be preferable to (-).

OTOH, if we used coalgebras more heavily in Haskell we could make the opposite
case, that (-) is preferable, since coalgebras have a common domain.

-- 
Frank Atanassow, Dept. of Computer Science, Utrecht University
Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands
Tel +31 (030) 253-1012, Fax +31 (030) 251-3791





Re: string to Integer

2000-04-07 Thread Marcin 'Qrczak' Kowalczyk

Thu, 06 Apr 2000 22:23:10 +0200, Ralf Muschall [EMAIL PROTECTED] pisze:

 And if I call the label on the stones "integer_from_string"
 and "integer_from_intlist", unflipped (.) does as well.

In OCaml such functions are called int_of_string etc.

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a23 C+++$ UL++$ P+++ L++$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-





Re: string to Integer

2000-04-06 Thread George Russell

Ralf Muschall wrote:
 Where does the habit to use "flip (.)" in many FP people come
 from? 
I think it may come partly from category
theorists




Re: string to Integer

2000-04-06 Thread Ralf Muschall

Ronny Wichers Schreur schrieb:
 If you think of the (types of) functions as domino stones,
 |. makes them fit.

And if I call the label on the stones "integer_from_string"
and "integer_from_intlist", unflipped (.) does as well.

The same applies to the other answers: On could write
f . g (which is just f . g) as well as g . f and have
data flow to the left.

George's answer about category theroists also seems not to
solve the historical questions: Classical categorists write
f o g (as SMLers do), only those who write papers about
computer science (e.g. M. Fokkinga) use a semicolon to
express flipped composition.

My guess is that someone "invented" flip (.) and then it stuck
because it was cool, but I still fail to see why it was
considered cool. But it had to be a conscient decision --
(.) is older than the flipped version.

Ralf




Re: string to Integer

2000-04-06 Thread Ronny Wichers Schreur

Ralf Muschall wrote:

  And if I call the label on the stones "integer_from_string"
  and "integer_from_intlist", unflipped (.) does as well.

But then the question is which function name is more natural.
Arjen's choice of names reflects Haskell's syntax for function
types:

 intlist_to_integer
 ::   [Int]  - Integer

Or look at o's and flippo's types:

 (.)  :: ((a - b) - (c - a)) - (c - b)
 flip (.) :: ((a - b) - (b - c)) - (a - c)

Surely the second one is much cooler!


Cheers,

Ronny Wichers Schreur





Re: string to Integer

2000-04-06 Thread Ronny Wichers Schreur

I wrote:

  (.)  :: ((a - b) - (c - a)) - (c - b)
  flip (.) :: ((a - b) - (b - c)) - (a - c)

Hm, let me try  that again:

 (.)  :: (a - b) - (c - a) - (c - b)
 flip (.) :: (a - b) - (b - c) - (a - c)


Cheers,

Ronny Wichers Schreur





Re: string to Integer

2000-04-06 Thread Yuichi Tsuchimoto

   And if I call the label on the stones "integer_from_string"
   and "integer_from_intlist", unflipped (.) does as well.
 
 But then the question is which function name is more natural.
 Arjen's choice of names reflects Haskell's syntax for function
 types:
 
  intlist_to_integer
  ::   [Int]  - Integer
 
 Or look at o's and flippo's types:
 
  (.)  :: ((a - b) - (c - a)) - (c - b)
  flip (.) :: ((a - b) - (b - c)) - (a - c)
 
 Surely the second one is much cooler!

Yes, indeed!

Then, the question is why we write
  result = function operand1 operand2
instead of
  operand1 operand2 function = result

I actually think the latter is cooler.  :)

++
| Yuichi Tsuchimoto  |
| Compiler Technology Dept.,   Middleware Division,   Fujitsu Ltd.   |
++




string to Integer

2000-04-05 Thread Friedrich Dominicus

I was again playing around with Haskell to learn it a bit better. I do not
found a function to turn a String into an Integer

This is what I come up with:
string_to_int_list :: String - [Int]
-- filter out all Digits first and then turn it into a list 
-- of integers
string_to_int_list = filter (\ch - isDigit ch)  .| map (\ch - digitToInt ch)

int_list_to_integer:: [Int] - Integer
int_list_to_integer li = to_integer 0 li 
where
to_integer acc [] = acc
to_integer acc (x:xs) = to_integer (acc * 10 + toEnum x) xs 



infixl 9 .|
(.|) :: (a - b) - (b - c) - a - c
g .| f = f . g 

string_to_integer :: String - Integer
string_to_integer =  string_to_int_list .| int_list_to_integer

I guess it's nt all too bad style (comments appriciated)

But it does not work for negative numbers. I guess I can solve this just
isn't there a functions which takes e.g 
"-1" and turns that into an Integer? 

I do not found it
"-123" it should turn to '[-1,2,3]' 

Of course for negative numbers the accumulation would be bad too but that's
another story. So what I want is just function that extract all numbers out
of a String and that's it. I can't believe there isn't some function for
that. 

So my question is: Exists such a function or do I have to write it on my own? And the 
other is what would you
think would be a good Haskell soluton for turing a string to an Integer.

I'm using HUGS from Feb 2000

Regards
Friedrich







Re: string to Integer

2000-04-05 Thread Arjan van IJzendoorn

Hello Friedrich,

Turning a string into an integer is easy with the Prelude function 'read':

n :: Integer
n = read "-34232"

Your own function can be made to work for negative numbers by a simple
wrapper:

stringToInteger :: String - Integer
stringToInteger ('-':rest) = -string_to_integer rest
stringToInteger string = string_to_integer string

 string_to_integer :: String - Integer
 string_to_integer =  string_to_int_list .| int_list_to_integer

Bye,
 Arjan






Re: string to Integer

2000-04-05 Thread Friedrich Dominicus

 "AvI" == Arjan van IJzendoorn [EMAIL PROTECTED] writes:

   AvI Hello Friedrich,
   AvI Turning a string into an integer is easy with the Prelude function 'read':

   AvI n :: Integer
   AvI n = read "-34232"
Yes, other have told me. As I mailed back I was just too blind.

   AvI Your own function can be made to work for negative numbers by a simple
   AvI wrapper:

   AvI stringToInteger :: String - Integer
   AvI stringToInteger ('-':rest) = -string_to_integer rest
   AvI stringToInteger string = string_to_integer string
This is quite nice but anyway I do not like it. I can't tell the  reason, but 
it seems to me that this does not desrves an own function.

Regards
Friedrich









Re: string to Integer

2000-04-05 Thread Marcin 'Qrczak' Kowalczyk

Wed, 05 Apr 2000 19:37:06 +0200, Ralf Muschall [EMAIL PROTECTED] pisze:

 and the type declaration you gave seems to be the most general
 possible anyway, i.e. it does not carry any information.

It does: documentation.

It happens that in this case "flip (.)" is more clear documentation
for me than the type signature. But often the type signature alone
is sufficient to suggest the most natural meaning, e.g.
[(a,b)] - ([a],[b])
(a - c) - (b - c) - Either a b - c
[[a]] - [a]
(a - b - c) - (b - a - c)

ghc -Wall gives warnings for toplevel definitions without type
signatures.

 Where does the habit to use "flip (.)" in many FP people come from?

I don't know, I use non-flipped (.). But if we wrote function
application in the "argument + function" order, composition would
certainly be written backwards as well.

Although in "f . g" it seems that g will be computed first, actually
in a lazy language it is f who decides what to do earlier :-)

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a23 C+++$ UL++$ P+++ L++$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-





backwards stuff (was re: string to integer)

2000-04-05 Thread Peter Hancock


 "Marcin" == Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] writes:

 I don't know, I use non-flipped (.). But if we wrote function
 application in the "argument + function" order, composition would
 certainly be written backwards as well.

Actually, it makes good sense to think of "backwards application" 
as a kind of exponentiation, and backwards composition as a kind of 
multiplication.  Then "lifted" composition \c-(c^a)*(c^b) behaves like
addition, and (flip const) as zero.  

If anyone is interested in more details, look at
http://www.dcs.ed.ac.uk/~pgh/arithmetic.lhs.  It is
at least amusing, and sometimes even quite practical.
--
Peter Hancock




Re: string to Integer

2000-04-05 Thread Hamilton Richards

At 7:37 PM +0200 4/5/00, Ralf Muschall wrote:

Where does the habit to use "flip (.)" in many FP people come
from?

It's useful for composing several functions in pipeline fashion.

Simon Thompson (in his book _Haskell: the Craft of Functional Programming_)
defines a "forward composition" operator:

(.) :: (a-b) - (b-c) - (a-c)
(.) = flip (.)

A composition using this operator, e.g.,

f . g . h

is easily understood as a pipeline in which data flows from left to right.
Using ordinary composition (.), the same function would be written

h . g . f

which can be thought of as a pipeline only if one imagines data flowing
right to left.

--HR



--
Hamilton Richards Jr.Department of Computer Sciences
Senior Lecturer  Mail Code C0500
512-471-9525 The University of Texas at Austin
SHC 434  Austin, Texas 78712-1188
[EMAIL PROTECTED]
--






Re: string to Integer

2000-04-05 Thread Peter Hancock

 "Hamilton" == Hamilton Richards [EMAIL PROTECTED] writes,
about forwards (is it backwards?) composition:

 A composition using this operator, e.g.,

   f . g . h

 is easily understood as a pipeline in which data flows from left to right.
 Using ordinary composition (.), the same function would be written

   h . g . f

 which can be thought of as a pipeline only if one imagines data flowing
 right to left.

Well, the *demand* for data flows from left to right.  (Isn't
electric current in some sense the flow of demand for electrons??)
--
Peter Hancock




Re: string to Integer

2000-04-05 Thread Ronny Wichers Schreur

Arjan van IJzendoorn wrote the function:

  string_to_integer :: String - Integer 
  string_to_integer = string_to_int_list .| int_list_to_integer

Ralf Muschall answered:

  (|.) = flip (.)
  [..]
  Where does the habit to use "flip (.)" in many FP people
  come from?

If you think of the (types of) functions as domino stones,
|. makes them fit.

.-.
|  |  |
|  string _to_integer |
|  |  |
.-.
 .-.  .-.
 |  |  |  |  |  |
   = |  string _to_int_list|.|| int_list_to_integer |
 |  |  |  |  |  |
 .-.  .-.

Cheers,

Ronny Wichers Schreur