RFC: "Haskell for Perl Programmers" Presentation

2003-09-29 Thread Shlomi Fish

At our local Perl Mongers club we have decided to hold a series of
introductions to foreign language. Being a big fan of Haskell (except for
any practical use), I wrote a "Haskell for Perl Programmers" intro:

http://vipe.technion.ac.il/~shlomif/lecture/Perl/Haskell/slides/

It's more or less complete, but there may still be things to add or
remove. Note that until now I did not write too much about the typing
facilities of Haskell. I could, though.

Regards,

Shlomi Fish

------
Shlomi Fish[EMAIL PROTECTED]
Home Page: http://t2.technion.ac.il/~shlomif/

An apple a day will keep a doctor away. Two apples a day will keep two
doctors away.

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


OT: Project Idea: Aristo - A Framework for Embedding and Integrating High-Level Languages

2003-01-08 Thread Shlomi Fish

I just returned from a dinner a few members of the Linux Israeli scene had
with Richard Stallman (of GNU fame), as he his now visiting Israel. I got
the opportunity to talk with him, and asked him the GNU project insistance
of using guile for extensibility. He said the reason for that was that
converting any other language to Scheme was a good a choice out of the
fact Scheme was so simple, powerful and generic. I said converting Perl 5
code to Scheme would not be too trivial at all, and he said that was the
case for converting Perl to almost everything else. :-) (despite this
joke, I'm sure converting many languages to Scheme would be incredibly
problematic)

Then I noted that they should try the GIMP approach instead: and use a
procedural database to integrate several languages back-ends. Then, he
said that the type system would not be flexible enough for that. After a
while that it was a challenge: create a bridge in ANSI C, that will be
flexible enough to interoperate code between many virtual machines: perl
5, python, Ruby, Java, Haskell, O'Caml, etc.

The codename is dubbed "Aristo", which is the Hebrew pronouncation and
spelling of "Aristotle". (it's simpler and without the "totel" at the
end). Now what I need is some advice on designing a type system: OK, I can
have arrays of ints, and associative arrays from strings to ints, etc. But
an array of records whose one field is an array of ints, the other a
linked list of strings, the other an associative array from floats to this
record itself, is something I'd rather not have to do type interference
with. (usually you don't need such strict typing requirements).

Here are some of my ideas, so far. Let me know what you think:

1. Aristo can only be written in ANSI C. Any other language will be
unacceptable, as all implementations of the back-ends are written in ANSI
C.

2. Aristo should have a nice nested namespace organization, with import
and export features, package-scope globals etc. The gimp flat list (in
which namespace collision is maintained by prefixes) is not scalable.

3. There should be a union type which is a type identifier followed by the
type value, which could assume any value. It is possible some types will
not be unions and will be plain types without the type value.

4. A standard enum can be used to store the object meta-type, and a
standard pointer/long union can be used to store the data. Almost anything
will be done using indirection.

5. Types should be declared using a machine-readable type definition, that
can be understood by humans.

6. Maybe I can take a look at GIMP PDB for code and ideas, but probably
not much. From my impression it's more of an ad-hoc system for the GIMP.

7. A procedure can restrict the types that pass to it, but I'm not sure to
what extent.

8. I'll have to translate between conventions of different languages
inside each language back-end.

9. It's first implementation will probably not have all the functionality
I'd like it to have, but better to release early and release often.

Your ideas and comments are most welcome. At the moment Aristo is at the
pre-coding stage. (I'm just thinking about its design). But I'd rather
have something well-designed and well-scrutinized in mind before I start
actual coding.

Regards,

    Shlomi Fish





--
Shlomi Fish[EMAIL PROTECTED]
Home Page: http://t2.technion.ac.il/~shlomif/

He who re-invents the wheel, understands much better how a wheel works.



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



Re: Writing a counter function

2002-06-29 Thread Shlomi Fish


Just for the record, here is a Perl function that does this:

###
sub counter
{
my $a = shift;

my $next = sub {
my $to_add = shift ;
return counter($to_add+$a);
};

return ($a, $next);
}

my ($result,$next) = counter(5);
my ($result2, $next2) = $next->(100);
my ($result3, $next3) = $next2->(50);
my ($result4, $next4) = $next->(30);

print "\$result=$result\n\$result2=$result2\n\$result3=$result3\n\$result4=$result4\n";


Regards,

Shlomi Fish



------
Shlomi Fish[EMAIL PROTECTED]
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

He who re-invents the wheel, understands much better how a wheel works.

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



Re: Writing a counter function

2002-06-29 Thread Shlomi Fish

On Sat, 29 Jun 2002, Jon Fairbairn wrote:

> Shlomi Fish wrote:
> > No. But I want to generate an irregular series, which I determine the
> > intervals between two consecutive numbers myself. E.g:
> >
> > let (num1, next1) = (counter 5)
> > (num2, next2) = (next1 100)
> > (num3, next3) = (next2 50) in
> > [num1,num2,num3]
> >
> > Will have the numbers [5, 105, 155].
>
> What do you mean by "determine"?
>

_I_ want to determine which step to go to next. I'd like to pass a
parameter the counter each time, and each time get the next number as well
as a new counter.

Regards,

Shlomi Fish


> You can write
>
> sequence = iterate step_counter 0
>
> if the interval between successive numbers is determined by
> the current number, or
>
> sequence = map f [1..]
>
> if it's determined by the index in the sequence.
>
> or
>
> sequence =  map snd $ iterate step_counter (0,-7)
> step_counter (a,b) = (a+1, f a b)
>
> if it depends on both.
>
>
>   Jón
>



--
Shlomi Fish[EMAIL PROTECTED]
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

He who re-invents the wheel, understands much better how a wheel works.

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



Re: Writing a counter function

2002-06-29 Thread Shlomi Fish

On Sat, 29 Jun 2002, Hannah Schroeter wrote:

> Hello!
>
> On Sat, Jun 29, 2002 at 06:23:27PM +0300, Shlomi Fish wrote:
> > [...]
>
> > Actually, I'd like a more generalized counter. Something that would return
> > both the number and a handler to add another number, which in turn would
> > return the new sum and a new handler, etc.
>
> That's just what lazy lists are for. The "handler" thing is done
> automatically thanks to lazy evaluation.
>
> I.e. countFrom n = n : countFrom (n + 1)
> or just countFrom n = [n..]
>

No. But I want to generate an irregular series, which I determine the
intervals between two consecutive numbers myself. E.g:

let (num1, next1) = (counter 5)
(num2, next2) = (next1 100)
(num3, next3) = (next2 50) in
    [num1,num2,num3]

Will have the numbers [5, 105, 155].

Regards,

Shlomi Fish

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



--
Shlomi Fish[EMAIL PROTECTED]
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

He who re-invents the wheel, understands much better how a wheel works.

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



Re: Writing a counter function

2002-06-29 Thread Shlomi Fish

On Sat, 29 Jun 2002, Mark Carroll wrote:

> On Sat, 29 Jun 2002, Shlomi Fish wrote:
> (snip)
> > counter n = (n,(counter (n+1)))
> (snip)
>
> This doesn't work because you seem to be defining an infinitely deep tuple
> (1,(2,(3,(4,() which is naughty.
>
> I'm not really sure what alternative to suggest beyond [n .. ] without
> knowing more about what you are trying to do.
>

Actually, I'd like a more generalized counter. Something that would return
both the number and a handler to add another number, which in turn would
return the new sum and a new handler, etc.

Regards,

Shlomi Fish

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



--
Shlomi Fish[EMAIL PROTECTED]
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

He who re-invents the wheel, understands much better how a wheel works.

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



Writing a counter function

2002-06-29 Thread Shlomi Fish


I'm trying to write a counter function that would return a tuple whose
first element is the current value and whose second element is a new
counter. The following line:

counter n = (n,(counter (n+1)))

Generates the following error on Hugs and a similar one with ghci:

ERROR "counter.hs":6 - Type error in function binding
*** Term   : counter
*** Type   : a -> (a,b)
*** Does not match : a -> b
*** Because: unification would give infinite type

Is there any way to do it? I tried using data, type and newtype and none
of them worked.

Regards,

Shlomi Fish

------
Shlomi Fish[EMAIL PROTECTED]
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

He who re-invents the wheel, understands much better how a wheel works.

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



Generating the n! permutations in Haskell

2002-06-10 Thread Shlomi Fish


Included below is a Haskell Program I wrote to generate the n!
permutations of a set of n elements. There are comments that explain it
throughout the program.

Both of the algorithms that appear in the cut the knot site use
assignment, so are not very suitable for Haskell.

Regards,

Shlomi Fish

-- (gradual_transfer set empty_set)
--
-- Gradually pops elements out of set and [1..5] pushes them into
-- empty_set,
-- and makes a list of both stacks in their intermediate phases.
--
-- E.g:
-- gradual_transfer [1 .. 5] [] =
-- [([1,2,3,4,5],[]),([2,3,4,5],[1]),([3,4,5],[2,1]),
-- ([4,5],[3,2,1]),([5],[4,3,2,1])]
gradual_transfer :: [a] -> [a] -> [([a],[a])]
-- I stop when the list contains a single element, not when it contains
-- no elements at all. The reason for this is that gen_perms like it
-- better
-- this way, as it has no use of a zero element (a:as).
gradual_transfer (a:[]) ps = [((a:[]),ps)]
gradual_transfer (a:as) ps = ((a:as),ps):(gradual_transfer as (a:ps))

-- (dump ps as) is equivalent to (reverse ps) ++ as, only it should
-- be much faster.
dump :: [a] -> [a] -> [a]
dump [] as = as
dump (p:ps) as = dump ps (p:as)

gen_perms :: [a] -> [[a]]

gen_perms [] = [[]]

gen_perms set = [ (a:rest) |
(a:as,ps) <- (gradual_transfer set []),
rest <- gen_perms(dump ps as)
]


print_perms [] = return ()
print_perms (a:as) = do print a
print_perms as

main = print_perms (gen_perms [1 .. 8])





------
Shlomi Fish[EMAIL PROTECTED]
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

He who re-invents the wheel, understands much better how a wheel works.

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



Re: (no subject)

2001-03-27 Thread Shlomi Fish

On Tue, 27 Mar 2001, Atenea Azcue wrote:

> 
> Hello 
> 
> My name is Atenea .  I just want to ask you that how can i Creat a program 
> that just say "hello word" and another that can add a "matrix" if you
> can
>help me I would really going to apreciate please.  Thank you for your
> listening 
> 

It depends if your matrix is represented as a list of lists or a
two-dimensional array. For lists it is something like that:



plus (a,b) = a+b
plus_vec ([],[]) = []
plus_vec (a:as,b:bs) = (plus (a,b)):(plus_vec (as,bs))
vector_add a b = (map plus (zip a b))
matrix_add a b = (map plus_vec (zip a b))


It can be done a bit better using classes, but then it will be less easy
to understand.

For 2-D arrays, I believe there is an example in the tutorial that shows
matrix _mulitplication_, so addition should be quite trivial after
understanding that.

Check out: http://www.haskell.org/tutorial/

Regards,

Shlomi Fish

> 
> 
> -
> Do You Yahoo!?
> Yahoo! Mail Personal Address - Get email at your own domain with Yahoo! Mail.



------
Shlomi Fish[EMAIL PROTECTED] 
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

The prefix "God Said" has the extraordinary logical property of 
converting any statement that follows it into a true one.


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



Re: (no subject)

2001-03-27 Thread Shlomi Fish

On Tue, 27 Mar 2001, Atenea Azcue wrote:

> 
> Hello 
> 
> My name is Atenea :  I´m what to ask you who can I make a program in haskell 
> like une program that say hello word 
> 

main = putStr "Hello, World!"

Regards,

Shlomi Fish

> 
> 
> -
> Do You Yahoo!?
> Yahoo! Mail Personal Address - Get email at your own domain with Yahoo! Mail.



------
Shlomi Fish[EMAIL PROTECTED] 
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

The prefix "God Said" has the extraordinary logical property of 
converting any statement that follows it into a true one.


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



Re: (no subject)

2001-03-18 Thread Shlomi Fish

On Sat, 17 Mar 2001, mc991008 wrote:

> hello, i'm a student of computer science in a known university of 
> pakistan. in this 
> semester i'm doing a course on "programming methodology". in this 
> course i had 
> given a project on learning haskell, a functional language and to give 
> a comparison on 
> haskell with prolog. if u plz kindly guide me and help me out, i'll be 
> very thankful to u.
> looking forward soon from u

Read http://www.haskell.org/tutorial/ in order to learn Haskell. Can't
tell you about Prolog because I don't know it yet.

Regards,

Shlomi Fish

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



--
Shlomi Fish[EMAIL PROTECTED] 
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

The prefix "God Said" has the extraordinary logical property of 
converting any statement that follows it into a true one.


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



Boolean Primes Map (continued)

2000-12-24 Thread Shlomi Fish


Well, after some thought, I decided to try re-writing the boolean primes
map program only using a list instead of an array. I came up with this
program:


primes :: Int -> [Int]
primes how_much =  (iterate 2 initial_map) where
initial_map :: [Bool]
initial_map = (map (\x -> True) [ 0 .. how_much])
iterate :: Int -> [Bool] -> [Int]
iterate p (a:as) | p > mybound = process_map p (a:as)
 | a = p:(iterate (p+1) (mymark (p+1) step (2*p) as))
 | (not a) = (iterate (p+1) as) where
step :: Int
step = if p == 2 then p else 2*p
mymark :: Int -> Int -> Int -> [Bool] -> [Bool]
mymark cur_pos step next_pos [] = []
mymark cur_pos step next_pos (a:as) = 
if (cur_pos == next_pos) then
False:(mymark (cur_pos+1) step (cur_pos+step) as)
else
a:(mymark (cur_pos+1) step next_pos as)
mybound :: Int
mybound = ceiling(sqrt(fromIntegral(how_much)))
process_map :: Int -> [Bool] -> [Int]
process_map cur_pos [] = []
process_map cur_pos (a:as) | a = cur_pos:(process_map (cur_pos+1) as)
   | (not a) = (process_map (cur_pos+1) as)

I don't know too much about Haskell yet, so it is possible this program
can be further optimized using some Haskell built-ins.

Now, this program can scale to 100,000 and beyond, as opposed to the array
version which only got until 30,000 or 40,000. It's a pity Haskell doesn't
handle arrays very well, but I guess every language has its faults.

Regards,

Shlomi Fish


------
Shlomi Fish[EMAIL PROTECTED] 
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

The prefix "God Said" has the extraordinary logical property of 
converting any statement that follows it into a true one.


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



Boolean Primes Map (continued)

2000-12-24 Thread Shlomi Fish


Well, after some thought, I decided to try re-writing the boolean primes
map program only using a list instead of an array. I came up with this
program:


primes :: Int -> [Int]
primes how_much =  (iterate 2 initial_map) where
initial_map :: [Bool]
initial_map = (map (\x -> True) [ 0 .. how_much])
iterate :: Int -> [Bool] -> [Int]
iterate p (a:as) | p > mybound = process_map p (a:as)
 | a = p:(iterate (p+1) (mymark (p+1) step (2*p) as))
 | (not a) = (iterate (p+1) as) where
step :: Int
step = if p == 2 then p else 2*p
mymark :: Int -> Int -> Int -> [Bool] -> [Bool]
mymark cur_pos step next_pos [] = []
mymark cur_pos step next_pos (a:as) = 
if (cur_pos == next_pos) then
False:(mymark (cur_pos+1) step (cur_pos+step) as)
else
a:(mymark (cur_pos+1) step next_pos as)
mybound :: Int
mybound = ceiling(sqrt(fromIntegral(how_much)))
process_map :: Int -> [Bool] -> [Int]
process_map cur_pos [] = []
process_map cur_pos (a:as) | a = cur_pos:(process_map (cur_pos+1) as)
   | (not a) = (process_map (cur_pos+1) as)

I don't know too much about Haskell yet, so it is possible this program
can be further optimized using some Haskell built-ins.

Now, this program can scale to 100,000 and beyond, as opposed to the array
version which only got until 30,000 or 40,000. It's a pity Haskell doesn't
handle arrays very well, but I guess every language has its faults.

Regards,

Shlomi Fish


------
Shlomi Fish[EMAIL PROTECTED] 
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

The prefix "God Said" has the extraordinary logical property of 
converting any statement that follows it into a true one.



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



Re: finding primes

2000-12-20 Thread Shlomi Fish

On Thu, 21 Dec 2000, S.D.Mechveliani wrote:

> Hello,
> 
> On generating prime numbers, people wrote 
> 
> ...
> | import Array
> | primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where
> | primesMap   = accumArray (||) False (2,n) multList
> | [..]
> 
> 
> I think that it is good for functional programming to avoid arrays, 
> as possible. 
>

Yes. So I realized. It's a pity though, because sometimes arrays are very 
convenient.
 
> 
> Shlomi Fish <[EMAIL PROTECTED]>  writes
> 
> > [..]
> > primes :: Int -> [Int]
> >
> > primes how_much = sieve [2..how_much] where
> > sieve (p:x) = 
> > p : (if p <= mybound
> > then sieve (remove (p*p) x)
> > else x) where
> > remove what (a:as) | what > how_much = (a:as)
> >| a < what = a:(remove what as)
> >| a == what = (remove (what+step) as)
> >| a > what = a:(remove (what+step) as)
> > remove what [] = []
> > step = (if (p == 2) then p else (2*p)) 
> > sieve [] = []
> > mybound = ceiling(sqrt(fromIntegral how_much))
> >
> > I optimized it quite a bit, but the concept remained the same. 
> >
> > Anyway, this code can scale very well to 10 and beyond. But it's not
> > exactly the same algorithm.
> > [..]
> 
> 
> C.Runciman <[EMAIL PROTECTED]>  gives a paper reference 
> about this.
> 
> Aslo may I ask what do you mean by "can scale to 10",
> the value of a prime or its position No in the list?

I mean it can easily generate the list of primes from 2 up to 10. Not
10 separate primes.

> Anyway, here are my attempts:
> ---
> 1.
>   primes1 = s [(2::Int)..] :: [Int]
>  where  s (p:ns) = p: (s (filter (notm p) ns))
> notm p n = (mod n p) /= 0 
> 
>   main = putStr $ shows (primes1!!9000) "\n"
> 

This strikes me as the sieve version which I gave as the first example.
It's not very efficient because it uses modulo which is a costy operation.

> After compiling by  GHC-4.08 -O2
> it yields   93187  in  115 sec   on  Intel-586, 160 MHz.
> ---

> 2.
> The DoCon program written in Haskell (again, no arrays) gives
> about 10 sec (for Integer values). 
> Also it finds, for example, first 5 primes after 10^9 as follows:
> 
>   take 5 $ filter isPrime [(10^9 ::Integer) ..] 
>   -->
>   [17,19,100021,100033,100087]
> 
> This takes  0.05 sec.
> But DoCon uses a particular  isPrime  test method:
>   Pomerance C., Selfridge J.L., Wagstaff S.S.:
>   The pseudoprimes to 25*10^9.
>   Math.Comput., 1980, v.36, No.151, pp.1003-1026.
>  
> After 25*10^9 it becomes again, expensive.
>

Where can I find this DoCon program?

Regards,

Shlomi Fish
 
> 
> --
> Sergey Mechveliani
> [EMAIL PROTECTED]
> 
> 
> 
> 



--
Shlomi Fish[EMAIL PROTECTED] 
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

The prefix "God Said" has the extraordinary logical property of 
converting any statement that follows it into a true one.


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