[Haskell-cafe] OOP vs type classes Re: type gurus, can you please help?

2006-08-16 Thread Bulat Ziganshin
Hello Bulat,

Monday, August 14, 2006, 10:37:37 AM, you wrote:

 i'm started to write article about type classes. can you, type gurus,
 please check this initial text for correctness in explaining
 differences between classes and type classes?

i continue to develop this text. below is list of differences i
recalled, or may be a list of TC features. please critique it, add new
list entries (it's especially important), add/correct examples and
explanations. it's just a sketch now. i also put it to the
http://haskell.org/haskellwiki/Haskell_inside/OOP_vs_type_classes
after all critique will be accepted, i will try to turn this into
one more mini-tutorial



1. of course, there is no data fields inheritance and data fields itself
(so type classes more like to interfaces than to classes itself)

2. type can appear at any place in function signature: be any
parameter, inside parameter, in a list (possibly empty), or in a result

class C a where
f :: a - Int
g :: Int - a - Int
h :: Int - (Int,a) - Int
i :: [a] - Int
j :: Int - a
new :: a

it's even possible to define instance-specific constants (look at 'new').

if function value is instance-specific, OOP programmer will use
static method while with type classes you need to use fake
parameter:

class FixedSize a where
  sizeof :: a - Int
instance FixedSize Int8 where
  sizeof _ = 1
instance FixedSize Int16 where
  sizeof _ = 2

main = do print (sizeof (undefined::Int8))
  print (sizeof (undefined::Int16))

  

3. Inheritance between interfaces (in class declaration) means
inclusion of base class dictionaries in dictionary of subclass:

class (Show s, Monad m s) = Stream m s where
sClose :: s - m ()

means

type StreamDictionary m s = (ShowDictionary s, MonadDictionary m s, s-m())

There is upcasting mechanism, it just extracts dictionary of a base
class from a dictionary tuple, so you can run function that requires
base class from a function that requires subclass:

f :: (Stream m s) =  s - m String
show ::  (Show s) =  s - String
f s = return (show s)

But downcasting is absolutely impossible - there is no way to get
subclass dictionary from a superclass one



4. Inheritance between instances (in instance declaration) means
that operations of some class can be executed via operations of other
class. i.e. such declaration describe a way to compute dictionary of
inherited class via functions from dictionary of base class:

class Eq a where
  (==) :: a - a - Bool
class Cmp a where
  cmp :: a - a - Comparision
instance (Cmp a) = Eq a where
  a==b  =  cmp a b == EQ

creates the following function:

cmpDict2EqDict :: CmpDictionary a - EqDictionary a
cmpDict2EqDict (cmp) = (\a b - cmp a b == EQ)

This results in that any function that receives dictionary for Cmp class
can call functions that require dictionary of Eq class



5. selection between instances are done at compile-time, based only on
information present at this moment. so don't expect that more concrete
instance will be selected just because you passed this concrete
datatype to the function which accepts some general class:

class Foo a where
  foo :: a - String

instance (Num a) = Foo a where
  foo _ = Num

instance Foo Int where
  foo _ = int


f :: (Num a) =  a - String
f = foo

main = do print (foo (1::Int))
  print (f (1::Int))

Here, the first call will return int, but second - only Num.
this can be easily justified by using dictionary-based translation
as described above. After you've passed data to polymorphic procedure
it's type is completely lost, there is only dictionary information, so
instance for Int can't be applied. The only way to construct Foo
dictionary is by calculating it from Num dictionary using the first
instance.



6. for eqList :: (Eq a) = [a] - [a] - Bool types of all elements
in list must be the same, and types of both arguments must be the same
too - there is only one dictionary and it know how to handle variables
of only one concrete type!

7. existential variables pack dictionary together with variable (looks
very like the object concept!) so it's possible to create polymorphic
containers (i.e. holding variables of different types). but
downcasting is still impossible. also, existentials still don't allow
to mix variables of different types (their personal dictionaries still
built for variables of one concrete type)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


OOP vs type classes Re[2]: [Haskell-cafe] type gurus, can you please help?

2006-08-16 Thread Bulat Ziganshin
Hello Gabriel,

Tuesday, August 15, 2006, 10:36:28 PM, you wrote:

 | Moreover, Haskell type classes supports inheritance. Run-time
 | polymorphism together with inheritance are often seen as OOP
 | distinctive points, so during long time i considered type classes as a
 | form of OOP implementation. but that's wrong! Haskell type classes
 | build on different basis, so they are like C++ templates with added
 | inheritance and run-time polymorphism! And this means that usage of
 | type classes is different from using classes, with its own strong and
 | weak points.

 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.

i can't agree. the differences between TC inheritance/polymorphism and
C++ classes are substantial. i listed them in next part of tutorial which
you should see alongside this message. you can also see paper at
http://homepages.cwi.nl/~ralf/gpce06/ which is all about consequences
of differences between classes and type classes for software
development


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: Why does Haskell have the if-then-else syntax?

2006-08-16 Thread Benjamin Franksen
Mike Gunter wrote:
I had hoped the History of Haskell paper would answer a question
I've pondered for some time: why does Haskell have the if-then-else
syntax?  The paper doesn't address this.  What's the story?

For what it's worth, I have been asking myself the same question several
times. If/then/else syntax could be replaced by a regular (lazy) function
without any noticeable loss. Almost every time I use if/then/else I end up
changing it to a case expression on teh underlying data (which is almost
never Bool); the only exception being simple one liners, and for those a
function would be even more concise.

IMHO, the next standardized version of Haskell, however named, should
abandon the special if/then/else syntax so we'll have at least /one/ item
where the language becomes smaller and simpler.

Remember: Perfection is reached not when there is nothing more to add, but
rather when there is nothing more to take away.

On another note, I remember reading a paper proposing to generalize
if/then/else to arbitrary (so-called) dist-fix operators, using something
like partial backquoting, as in

`if condition `then` true_branch `else` false_branch fi`

Can't remember the exact title of the paper, nor the details, but it was
something to do with adding macros to Haskell.

Cheers,
Ben

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


Re: OOP vs type classes Re[2]: [Haskell-cafe] type gurus, can you please help?

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

| Hello Gabriel,
| 
| Tuesday, August 15, 2006, 10:36:28 PM, you wrote:
| 
|  | Moreover, Haskell type classes supports inheritance. Run-time
|  | polymorphism together with inheritance are often seen as OOP
|  | distinctive points, so during long time i considered type classes as a
|  | form of OOP implementation. but that's wrong! Haskell type classes
|  | build on different basis, so they are like C++ templates with added
|  | inheritance and run-time polymorphism! And this means that usage of
|  | type classes is different from using classes, with its own strong and
|  | weak points.
| 
|  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.
| 
| i can't agree. 

You're welcome :-)

| the differences between TC inheritance/polymorphism and
| C++ classes are substantial. i listed them in next part of tutorial which
| you should see alongside this message.

sorry, I did not see that tutorial.

| you can also see paper at
| http://homepages.cwi.nl/~ralf/gpce06/ which is all about consequences
| of differences between classes and type classes for software
| development

Thanks for the reference.  Nothing in that paper explores what I
suggested.  I don't see how it contradicts what I said.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2006-08-16 Thread Tamas K Papp
Hi,

I am a newbie learning Haskell.  I have used languages with functional
features before (R, Scheme) but not purely functional ones without
side-effects.

Most of the programming I do is numerical (I am an economist).  I
would like to know how to implement the iterative algorithm below in
Haskell.

f is an a-a function, and there is a stopping rule 
goOn(a,anext) :: a a - Bool which determines when to stop.  The
algorithm looks like this (in imperative pseudocode):

a = ainit

while (true) {
  anext - f(a)
  if (goOn(a,anext))
 a - anext
  else
 stop and return anext
}

For example, f can be a contraction mapping and goOn a test based on
the metric.  I don't know how to do this in a purely functional
language, especially if the object a is large and I would like it to
be garbage collected if the iteration goes on.

Thank you,

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


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

2006-08-16 Thread Chris Kuklewicz

Tamas K Papp wrote:

Hi,

I am a newbie learning Haskell.  I have used languages with functional
features before (R, Scheme) but not purely functional ones without
side-effects.

Most of the programming I do is numerical (I am an economist).  I
would like to know how to implement the iterative algorithm below in
Haskell.

f is an a-a function, and there is a stopping rule 
goOn(a,anext) :: a a - Bool which determines when to stop.  The

algorithm looks like this (in imperative pseudocode):

a = ainit

while (true) {
  anext - f(a)
  if (goOn(a,anext))
 a - anext
  else
 stop and return anext
}

For example, f can be a contraction mapping and goOn a test based on
the metric.  I don't know how to do this in a purely functional
language, especially if the object a is large and I would like it to
be garbage collected if the iteration goes on.

Thank you,

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


iterUntil :: (a - a - Bool) - (a - a) - a - a
iterUntil goOn f aInit =
  let loop a =
let a' = f a
in if goOn a a'
 then loop a'-- tail recursive (so a will be collected)
 else a'
  in loop aInit

--
Chris
___
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-16 Thread Christian Maeder
You might use the Prelude function until:
  until :: (a - Bool) - (a - a) - a - a

  until ( 3) (+ 2) 0 = 4

or for your purpose:
   until (\ a - not (goOn(a, f(a))) f ainit

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Auntil
http://www.haskell.org/onlinereport/prelude-index.html
http://www.haskell.org/onlinereport/standard-prelude.html#$vuntil

HTH Christian

Tamas K Papp schrieb:
 Hi,
 
 I am a newbie learning Haskell.  I have used languages with functional
 features before (R, Scheme) but not purely functional ones without
 side-effects.
 
 Most of the programming I do is numerical (I am an economist).  I
 would like to know how to implement the iterative algorithm below in
 Haskell.
 
 f is an a-a function, and there is a stopping rule 
 goOn(a,anext) :: a a - Bool which determines when to stop.  The
 algorithm looks like this (in imperative pseudocode):
 
 a = ainit
 
 while (true) {
   anext - f(a)
   if (goOn(a,anext))
a - anext
   else
  stop and return anext
 }
 
 For example, f can be a contraction mapping and goOn a test based on
 the metric.  I don't know how to do this in a purely functional
 language, especially if the object a is large and I would like it to
 be garbage collected if the iteration goes on.
 
 Thank you,
 
 Tamas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The Q Programming Language can do symbolic manipulation -- Haskell?

2006-08-16 Thread Robert Dockins


On Aug 15, 2006, at 11:43 PM, Casey Hawthorne wrote:


The Q Programming Language can do symbolic manipulation -- Haskell?

The Q Programming Language can do the following:

sqr X = X*X

==sqr 5
25

==sqr (X+1)
(X+1)*(X+1)



Can Haskell do symbolic manipulation?



Well, there's always the sledgehammer (http://www.haskell.org/ghc/ 
docs/latest/html/users_guide/template-haskell.html)




Or are term-rewriting and the lambda calculus sufficiently far enough
apart concepts?
--
Regards,
Casey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


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

2006-08-16 Thread Antti-Juhani Kaijanaho
Tamas K Papp wrote:
 f is an a-a function, and there is a stopping rule 
 goOn(a,anext) :: a a - Bool which determines when to stop.  The
 algorithm looks like this (in imperative pseudocode):
 
 a = ainit
 
 while (true) {
   anext - f(a)
   if (goOn(a,anext))
a - anext
   else
  stop and return anext
 }
 
 For example, f can be a contraction mapping and goOn a test based on
 the metric.  I don't know how to do this in a purely functional
 language, especially if the object a is large and I would like it to
 be garbage collected if the iteration goes on.

The idea is to make the iteration variables arguments to a
tail-recursive function:

let foo a | goOn a anext = foo anext
  | otherwise= anext
where anext = f a
in foo ainit


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


[Haskell-cafe] Int-[Char] conversion

2006-08-16 Thread Tamas K Papp
Hi,

I am working through Hal Daume's tutorial, trying to do the exercises.
I can't figure out how to output an integer with putStrLn (or any
other way), I think I need an Int - [Char] conversion but couldn't
find it.  Specifically, in Exercise 3.10, I have the product of
numbers in pp, and would like to do 

putStrLn (Product:  ++ convertnumbertostring(pp))

but I don't know which function does this...

Sorry for the extremely dumb question.

Thanks,

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


[Haskell-cafe] Re: Int-[Char] conversion

2006-08-16 Thread Jón Fairbairn
Tamas K Papp [EMAIL PROTECTED] writes:

 Hi,
 
 I am working through Hal Daume's tutorial, trying to do the exercises.
 I can't figure out how to output an integer with putStrLn (or any
 other way), I think I need an Int - [Char] conversion but couldn't
 find it.  Specifically, in Exercise 3.10, I have the product of
 numbers in pp, and would like to do 
 
 putStrLn (Product:  ++ convertnumbertostring(pp))
 
 but I don't know which function does this...

You could try Hoogle URL: http://haskell.org/hoogle/ ,
though entering Int - [Char] isn't very helpful, if you put
in Int - String, you get 'show' as the second hit, and
that's the function you want.

-- 
Jón Fairbairn [EMAIL PROTECTED]


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


Re: [Haskell-cafe] The Q Programming Language can do symbolic manipulation -- Haskell?

2006-08-16 Thread Greg Buchholz
Casey Hawthorne wrote:
 
 The Q Programming Language can do the following:
 
 sqr X = X*X
 
 ==sqr 5
 25
 
 ==sqr (X+1) 
 (X+1)*(X+1)
 
 Can Haskell do symbolic manipulation?

Typeful symbolic differentiation of compiled functions

http://www.haskell.org/pipermail/haskell/2004-November/014939.html

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


Re: [Haskell-cafe] Re: Int-[Char] conversion

2006-08-16 Thread Neil Mitchell

Hi,


You could try Hoogle URL: http://haskell.org/hoogle/ ,
though entering Int - [Char] isn't very helpful,


A known issue, Hoogle 4 will know about [Char] = String, and will
also be tweaked to give show first in this instance.

Thanks

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


[Haskell-cafe] Questions on threads and IO

2006-08-16 Thread Creighton Hogg
Hello Haskell'rs,

I've been playing with threads and I tried to do a toy example (that used java) from a class.
When run, the program should print a prompt and accept commands just like a linux shell. It doesn't have to do anything
fancy, just spawn new threads that make system calls when commands are entered at the prompt.
The problem is that the UI doesn't work very well. It will seem fine
at first, but in order to get back a prompt you have to hit enter one
more time than you should. I've tried playing with the buffering
settings but it seems to cause the same problem no matter what. The
problem seems to be coming from calls of the form
(forkIO . system_) ls /usr/bin
Just entering this into ghci I get the same thing where I need to hit enter *again* in order to get back to the ghci prompt.
I'm sure this is something silly on my part, but it is rather confusing.

import Control.Concurrent
import System
import System.IO

main = do
 putStr 
 z - getLine
 runCommands z
 main

genWords :: Char - String - [String]
genWords c s = gwhelper c s [] []

gwhelper :: Char - String - [String] - String - [String]
gwhelper c [] acc temp = acc ++ [(reverse temp)]
gwhelper c (x:xs) acc temp | x /= c = gwhelper c xs acc (x:temp)
 | otherwise = gwhelper c xs (acc++[(reverse temp)]) []


runCommands s = mapM_ (forkIO .system_) (genWords '' s)

system_ :: String - IO ()
system_ s = do
 system s
 return ()
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Int-[Char] conversion

2006-08-16 Thread ivan gomez rodriguez

Neil Mitchell wrote:

Hi,


You could try Hoogle URL: http://haskell.org/hoogle/ ,
though entering Int - [Char] isn't very helpful,


A known issue, Hoogle 4 will know about [Char] = String, and will
also be tweaked to give show first in this instance.

Thanks

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


You can use show :: (Show a) = a - String
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The Q Programming Language can do symbolic manipulation -- Haskell?

2006-08-16 Thread Chris Kuklewicz

Greg Buchholz wrote:

Casey Hawthorne wrote:

The Q Programming Language can do the following:

sqr X = X*X

==sqr 5
25

==sqr (X+1) 
(X+1)*(X+1)


Can Haskell do symbolic manipulation?


Typeful symbolic differentiation of compiled functions

http://www.haskell.org/pipermail/haskell/2004-November/014939.html




And a GADT version of differentiation:

http://haskell.org/hawiki/ShortExamples_2fSymbolDifferentiation

which also does some simplifications.  I have a version that I did not post that 
uses the hs-plugins:  It can take a function like


f x = x * log x + 7 * (-x) + (2**x) - (sin x)

and compute the derivative, simplify it, emit the haskell code for it,  compile 
it via hs-plugins, and be able to use it.


Of course, you can't INLINE a new function like that, but the performance is 
still very good.

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


Re: [Haskell-cafe] Questions on threads and IO

2006-08-16 Thread Chris Kuklewicz
It looks like a stdout buffering issue, plus a 'yield' issue.  forkIO does not 
spawn OS level threads (that is forkOS) so adding a yield helps the runtime:



import Control.Concurrent
import System
import System.IO

loop = do
   putStr  
   z - getLine
   runCommands z
   yield
   loop

main = do
 hSetBuffering stdout NoBuffering
 loop

genWords :: Char - String - [String]
genWords c s = gwhelper c s [] []

gwhelper :: Char - String - [String] - String - [String]
gwhelper c [] acc temp = acc ++ [(reverse temp)]
gwhelper c (x:xs) acc temp | x /= c =  gwhelper c xs acc (x:temp)
   | otherwise = gwhelper c xs (acc++[(reverse temp)]) 
[]


runCommands s = mapM_ (forkIO . system_) (genWords '' s)

system_ :: String - IO ()
system_ [] = return ()
system_ s = do
  system s
  return ()




Creighton Hogg wrote:

Hello Haskell'rs,

I've been playing with threads and I tried to do a toy example (that 
used java) from a class.
When run, the program should print a prompt and accept commands just 
like a linux shell.  It doesn't have to do anything
fancy, just spawn new threads that make system calls when commands are 
entered at the prompt.
The problem is that the UI doesn't work very well.  It will seem fine at 
first, but in order to get back a prompt you have to hit enter one more 
time than you should.  I've tried playing with the buffering settings 
but it seems to cause the same problem no matter what.  The problem 
seems to be coming from calls of the form

(forkIO . system_) ls /usr/bin
Just entering this into ghci I get the same thing where I need to hit 
enter *again* in order to get back to the ghci prompt.

I'm sure this is something silly on my part, but it is rather confusing.

import Control.Concurrent
import System
import System.IO

main = do
   putStr 
   z - getLine
   runCommands z
   main

genWords :: Char - String - [String]
genWords c s = gwhelper c s [] []

gwhelper :: Char - String - [String] - String - [String]
gwhelper c [] acc temp = acc ++ [(reverse temp)]
gwhelper c (x:xs) acc temp | x /= c =  gwhelper c xs acc (x:temp)
   | otherwise = gwhelper c xs (acc++[(reverse 
temp)]) []



runCommands s = mapM_ (forkIO .system_) (genWords '' s)

system_ :: String - IO ()
system_ s = do
  system s
  return ()




___
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] iterative algorithms: how to do it in Haskell?

2006-08-16 Thread ivan gomez rodriguez

Chris Kuklewicz wrote:

Tamas K Papp wrote:

Hi,

I am a newbie learning Haskell.  I have used languages with functional
features before (R, Scheme) but not purely functional ones without
side-effects.

Most of the programming I do is numerical (I am an economist).  I
would like to know how to implement the iterative algorithm below in
Haskell.

f is an a-a function, and there is a stopping rule goOn(a,anext) :: 
a a - Bool which determines when to stop.  The

algorithm looks like this (in imperative pseudocode):

a = ainit

while (true) {
  anext - f(a)
  if (goOn(a,anext))
   a - anext
  else
 stop and return anext
}

For example, f can be a contraction mapping and goOn a test based on
the metric.  I don't know how to do this in a purely functional
language, especially if the object a is large and I would like it to
be garbage collected if the iteration goes on.

Thank you,

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


iterUntil :: (a - a - Bool) - (a - a) - a - a
iterUntil goOn f aInit =
  let loop a =
let a' = f a
in if goOn a a'
 then loop a'-- tail recursive (so a will be collected)
 else a'
  in loop aInit


In Haskell you can do this

iterUntil :: (a - a - Bool) - (a - a) - a - a
iterUntil goOn f a  | goOn a anext = iterUntil goOn f anext
  | otherwise= anext
  where anext = f a


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


Re: [Haskell-cafe] Int-[Char] conversion

2006-08-16 Thread Jared Updike

putStrLn (Product:  ++ convertnumbertostring(pp))


Also, there is a predefined function called 'print' where

print x = putStr (convertnumbertostring x)
i.e.
print x = putStr (show x)

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


[Haskell-cafe] Haskell wiki: most popular pages

2006-08-16 Thread Bulat Ziganshin
Hello haskell-cafe,

The http://haskell.org/haskellwiki/Special:Popularpages page lists
most popular pages on haskell wiki. I think this list is very
useful because it shows us what are the questions about Haskell
people most interested and gives us hints what should be improved in
first place. The only catch is that most of popular pages are just
ones listed on the title page. But nevertheless... On the other side,
we can simplify title page by omitting links to page that are of
little interest for casual readers (such as History). We can also add
here links to most popular pages, such as GHC and Hitchhikers guide.
Below is beginning of this list:

Haskell (252,505 views)
Introduction (50,091 views) 
Libraries and tools (41,864 views) 
Books and tutorials (40,040 views) 
Language and library specification (32,773 views) 
Haskell in practice (31,698 views) 
Implementations (24,141 views) 
GHC (20,634 views) 
Haskell in 5 steps (16,707 views) 
Learning (14,088 views) 
Hitchhikers guide to Haskell (13,191 views) 
Future (12,754 views)

-- 
Best regards,
 Bulat  mailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Samba/FTP bindings

2006-08-16 Thread Ivan Tarasov
Is there some Haskell library which provides Samba bindings and some FTP client library bindings (e.g. ftplib3)?I started writing the bindings for some of the functions myself for my project but it looks like it is a lot of work and probably someone has done it already.
-- Best regards,Ivan Tarasov
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Local functional dependencies: solving show . read and XML generation problems

2006-08-16 Thread Niklas Broberg

Hi Oleg,

Thanks a lot for your reply. I see now where my attempt went wrong and
why it couldn't work in the first place, the instances will indeed
overlap. I'm not completely satisfied with your solution though, but
seeing how you did it has lead me to the solution I want. Details
below. :-)

] Fortunately, there is a solution that does not involve proxies or
] type annotations. We use a `syntactic hint' to tell the typechecker
] which intermediate type we want. To be more precise, we assert local
] functional dependencies. Thus we can write:
]
]  p c = build p [embed c]
]
]  test1 :: XML
]  test1 = p [[p [[p foo
]
] Our syntactic crutch is the list notation: [[x]]. We could have used a
] single pair of brackets, but we'd like to avoid overlapping
] instances (as is done in the following self-contained code).

While I appreciate the ingenuity of the solution, unfortunately I
cannot use it. First of all I don't want to require my users to write
double brackets everywhere, it makes the code a lot uglier IMO.
Another problem is that in my real library (as opposed to the
simplified example I gave here) I allow the embedding of lists, which
means that the [[x]] is not safe from overlap as it is in your
example. But I still see the general pattern here, the point is just
to get something that won't clash with other instances. I could define

 data X a = X a

 instance (TypeCast a XML) = Embed (X a) XML where
   embed (X a) = typeCast a

and write

 test1 = p (X $ p (X $ p foo))

Not quite so pretty, even worse than with the [[ ]] syntax.

However, I have an ace up my sleeve, that allows me to get exactly
what I want using your trick. Let's start the .lhs file first:

{-# OPTIONS_GHC -fglasgow-exts #-}
{-# OPTIONS_GHC -fallow-overlapping-instances #-}
{-# OPTIONS_GHC -fallow-undecidable-instances #-}
module HSP where

import Control.Monad.State
import Control.Monad.Writer
import TypeCast -- putting your six lines in a different module


Now, the thing I haven't told you in my simplified version is that all
the XML generation I have in mind takes place in monadic code. In
other words, all instances of Build will be monadic. My whole point of
wanting more than one instance is that I want to use one monad, with
an XML representation, in server-side code and another in client-side
code, as worked on by Joel Björnson.

Since everything is monadic, I can define what it means to be an
XML-generating monad in terms of a monad transformer:


newtype XMLGen m a = XMLGen (m a)
  deriving (Monad, Functor, MonadIO)


and define the Build and Embed classes as


class Build m xml child | m - xml child where
 build :: String - [child] - XMLGen m xml

class Embed a child where
 embed :: a - child


Now for the server-side stuff:


data XML = CDATA String | Element String [XML]
 deriving Show

newtype HSPState = HSPState Int -- just to have something
type HSP' = StateT HSPState IO
type HSP = XMLGen HSP'


Note that by including XMLGen we define HSP to be an XML-generation
monad. Now we can declare our instances.

First we can generate XML values in the HSP monad (we use HSP [XML] as
the child type to enable embedding of lists):


instance GenXML HSP' XML (HSP [XML]) where
 genElement s chs = do
xmls - fmap concat $ sequence chs
return (Element s xmls)


Second we do the TypeCast trick, with XMLGen as the marker type:


instance TypeCast (m x) (HSP' XML) =
Embed (XMLGen m x) (HSP [XML]) where
  embed (XMLGen x) = XMLGen $ fmap return $ typeCast x


And now we can safely declare other instances that will not clash with
the above because of XMLGen, e.g.:


instance Embed String (HSP [XML]) where
 embed s = return [CDATA s]

instance Embed a (HSP [XML]) = Embed [a] (HSP [XML]) where
 embed = fmap concat . mapM embed -- (why is there no concatMapM??)


This last instance is why I cannot use lists as disambiguation, and
also why I need overlapping instances. Now for some testing functions:


p c = build p [embed c]



test0 :: HSP XML
test0 = p foo



test1 :: HSP XML
test1 = p (p foo)



test2 :: HSP XML
test2 = p [p foo, p bar]


All of these now work just fine. We could end here, but just to show
that it works we do the same stuff all over again for the clientside
stuff (mostly dummy code, the clientside stuff doesn't work like this
at all, this is just for show):


data ElementNode = ElementNode String [ElementNode] | TextNode String
 deriving Show

type HJScript' = WriterT [String] (State Int)
type HJScript = XMLGen HJScript'

instance Build HJScript' ElementNode (HJScript ElementNode) where
 build s chs = do
xs - sequence chs
return $ ElementNode s xs

instance TypeCast (m x) (HJScript' ElementNode) =
Embed (XMLGen m x) (HJScript ElementNode) where
 embed (XMLGen x) = XMLGen $ typeCast x

instance Embed String (HJScript ElementNode) where
 embed s = return $ TextNode s


Testing the new stuff, using the same p as above:


test3 :: HJScript ElementNode
test3 = p foo


Re: [Haskell-cafe] Re: Why does Haskell have the if-then-else syntax?

2006-08-16 Thread ajb
G'day all.

Quoting Benjamin Franksen [EMAIL PROTECTED]:

 For what it's worth, I have been asking myself the same question several
 times. If/then/else syntax could be replaced by a regular (lazy) function
 without any noticeable loss.

I believe that if-then-else cannot be replaced by a regular function
for the same reason that regular function application and ($) are not
identical.  The loss may not be noticeable, but it's still a loss.

It could be replaced by a case-switch-on-Bool, though.

 IMHO, the next standardized version of Haskell, however named, should
 abandon the special if/then/else syntax so we'll have at least /one/ item
 where the language becomes smaller and simpler.

The de facto Haskell philosophy, if you read the history paper, is to
have a small core language with a lot of syntactic sugar.  The syntactic
sugar is specified by translation to the core language.

The small core ensures that Haskell remains simple.  If you discount
changes in the type system, the Haskell core language is as simple now
as it was in 1989.

 Remember: Perfection is reached not when there is nothing more to add, but
 rather when there is nothing more to take away.

Perfection is asymptotically approached when arbitrary restrictions are
removed and special cases are dumped in favour of general, theoretically
sound, principles.  Perfection will never be reached in a practical
programming language, but it may be asymptotically approached.

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


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

2006-08-16 Thread Chris Kuklewicz

[EMAIL PROTECTED] wrote:

G'day Tamas.

Quoting Tamas K Papp [EMAIL PROTECTED]:


f is an a-a function, and there is a stopping rule
goOn(a,anext) :: a a - Bool which determines when to stop.  The
algorithm looks like this (in imperative pseudocode):

a = ainit

while (true) {
  anext - f(a)
  if (goOn(a,anext))
 a - anext
  else
 stop and return anext
}


Here are a couple more suggestions.

First, this function scans an infinite list and stops when p x1 x2
is true for two adjacent elements x1 and x2:

findFixpoint p (x1:xs@(x2:_))
| p x1 x2   = x2
| otherwise = findFixpoint p xs

Then you just need to pass it [ainit, f ainit, f (f ainit), ...]:

findFixpoint dontGoOn (iterate f ainit)

Note that the function to pass to findFixpoint here is the condition
to use to _stop_.


The compiler may not deforest that list, so creating the list may be a small 
overhead of this method.




If you're comfortable with monads, it's possible to directly simulate
complex imperative control flow.  It's not recommended to do this
unless the flow is very complex, but here we are for the record:

import Control.Monad.Cont

-- I used a Newton-Raphson square root evaluation for testing,
-- but it has the same structure as your algorithm.
mysqrt :: Double - Double
mysqrt x
  = runCont (callCC loop) id
  where
ainit = x * 0.5

f x = 0.5 * (a + x/a)

goOn a1 a2 = abs (a1 - a2)  1e-5

loop break
  = loop' ainit
  where
loop' a
  = do
let anext = f a
if goOn a anext
 then loop' anext
 else break anext

callCC defines a point outside the loop that you can break to.
You simply call that function (called a continuation) and the
loop is broken.

Cheers,
Andrew Bromage


Note that f x should be f a above.  But I like it.  My version of the above 
looks like



import Control.Monad.Cont

mysqrt :: Double - Double
mysqrt x = doWhile goOn f aInit
  where
aInit = x * 0.5
f a = 0.5 * (a + x/a)
goOn a1 a2 = abs (a1 - a2)  1e-5

doWhile :: (a - a - Bool) - (a - a) - a - a
doWhile goOn f x0 = runCont (callCC withBreak) id
  where withBreak break = 
  let loop x = do let x' = f x

  when (not (goOn x x')) (break x')
  loop x'
  in loop x0



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


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

2006-08-16 Thread ajb
G'day all.

Quoting Chris Kuklewicz [EMAIL PROTECTED]:

 The compiler may not deforest that list, so creating the list may be a small
 overhead of this method.

And in return, you get:

- Code that is smaller than the imperative version, AND
- a reusable function, making the next incarnation of
  an algorithm like this even shorter.

For most interesting cases, the cost of f and goOn will surely dominate
anyway.

 Note that f x should be f a above.

Yes, you're right.  I abstracted out f after testing and before
posting.

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