Re: [Haskell-cafe] Data.ByteString.dropWhile

2007-07-10 Thread Thomas Conway

So the following isn't as clever as the line-noise Don posted, but
should be in the ball-park.

dropFromEnds p = dropWhile p . dropWhileEnd p

dropWhileEnd p bs = take (findFromEndUntil (not p) bs) bs

takeWhileEnd p bs = drop (findFromEndUntil p bs) bs

{- findFromEndUntil is in ByteString.hs, but is not exported -}

T.
--
Dr Thomas Conway
[EMAIL PROTECTED]

Silence is the perfectest herald of joy:
I were but little happy, if I could say how much.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.ByteString.dropWhile

2007-07-10 Thread Donald Bruce Stewart
drtomc:
 So the following isn't as clever as the line-noise Don posted, but
 should be in the ball-park.

Low level loops are irksome, but guaranteed to be quick :P

 dropFromEnds p = dropWhile p . dropWhileEnd p
 
 dropWhileEnd p bs = take (findFromEndUntil (not p) bs) bs
 
 takeWhileEnd p bs = drop (findFromEndUntil p bs) bs
 
 {- findFromEndUntil is in ByteString.hs, but is not exported -}

Yep, looks reasonable. With a bit of inlining (check the core) and you'll get
the same code anyway. Always good to roll a QuickCheck or two for this
kind of stuff, since off-by-one errors are rather easy.

This should get you into a testable state:

import qualified Data.ByteString  as S
import Test.QuickCheck.Batch
import Test.QuickCheck
import Text.Show.Functions
import System.Random

instance Arbitrary Word8 where
arbitrary = choose (97, 105)
coarbitrary c = variant (fromIntegral ((fromIntegral c) `rem` 4))

instance Random Word8 where
  randomR = integralRandomR
  random = randomR (minBound,maxBound)

integralRandomR :: (Integral a, RandomGen g) = (a,a) - g - (a,g)
integralRandomR  (a,b) g = case randomR (fromIntegral a :: Integer,
 fromIntegral b :: Integer) g of
(x,g) - (fromIntegral x, g)

-- define a model in [Word8]
tidy_model f = reverse . dropWhile f . reverse . dropWhile f

-- and check it
prop_tidy_ok f xs = tidy_model f xs == (S.unpack . tidy f . S.pack) xs

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


Re: [Haskell-cafe] xkcd #287 NP-Complete

2007-07-10 Thread Marc A. Ziegert
Am Dienstag, 10. Juli 2007 00:25 schrieb Albert Y. C. Lai:
 http://xkcd.com/c287.html

 It disappoints me that there is no solution if each item is used at most 
 once. However, do change the code to allow multiple uses, then there are 
 many solutions.

i see only two solutions.

let menu = [215, 275, 335, 355, 420, 580]
let run x menu = [[c]|c-menu,c==x]++[c:cs|c-menu,cx,cs-run (x-c) (dropWhile 
(/=c) menu)]
run 1505 menu

-
[[215,215,215,215,215,215,215],[215,355,355,580]]



pgp7aTVudNFDt.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] no-coding functional data structures via lazyness

2007-07-10 Thread Jonathan Cast
On Tuesday 10 July 2007, Dave Bayer wrote:
 On Jul 9, 2007, at 6:52 PM, Donald Bruce Stewart wrote:
  bayer:
  Learning Haskell, the Prelude.ShowS type stood out as odd, exploiting
  the implementation of lazy evaluation to avoid explicitly writing an
  efficient concatenable list data structure.
 
  See also
  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/
  dlist-0.3

 Thanks; I added a link to the dlist package from my discussion of
 this idiom on the Wiki page
   http://www.haskell.org/haskellwiki/Prime_numbers

 On Jul 9, 2007, at 3:19 PM, Jonathan Cast wrote:
  I think we usually call it `exploiting laziness'. . .

 My motivation in asking for a name was to be able to find other
 Haskell one-liners adequately replacing chapters of data structure
 books for problems of modest scale, e.g. finding the 5,000,000th
 prime. So far, I know concatenable lists, and heaps.  Is there a Wiki
 page where someone teaches this principle for a dozen other classic
 data structures? Your one-liner made me laugh, but it didn't help
 me in googling, I would have preferred a one-liner teaching me
 another classic data structure, or an explanation of why burrowing
 into the GHC implementation gives such a speed advantage over a
 carefully written explicit data structure.

 People in other camps don't really get lazy evaluation, even many
 of our ML neighbors. It would pay to communicate this better to the
 outside world.

Unfortunately, I'm afraid all I can do at this point is wish you luck in your 
search.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system madness

2007-07-10 Thread Daniil Elovkov

2007/7/10, Andrew Coppin [EMAIL PROTECTED]:


I stand in awe of people who actually understand what universal and
existential actually mean... To me, these are just very big words that
sound impressive.



The following is only my own understanding, please correct me if it's
totally wrong!
(and sorry for confusion if it is)

Another thing that might help is looking at non-functional values:

forall a. [a] is the _intersection_ of types [a] where 'a' runs over
all possible types.
That is, the only non-bottom value of forall a. [a] is the empty list [].
So, [4,5] doesn't belong to this type, nor does ['H','e','y'].

exists a. [a] constains [4,5] and Hey and []. So, it's tempting to
say, that it is the sum of types [a] where 'a' runs over all possible
types, but I may be lacking theoretic background here...

However, in Haskell both of those are designated by the forall word,
because as a consumer you treat them in the same way. That is, you
can't (safely) make any assumptions about 'a'. In case of forall it
simply doesn't make sense, in case of exists Haskell doesn't give you
the means to know what 'a' was really used when the value was created.

So, if you have types forall a. Class a = [a] and exists a. Class a
= [a], in both cases all that you can do with the value is

1) what you can do with lists
2) what you can do with instances of Class (that's for elements of the list)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell and GnuPG?

2007-07-10 Thread Magnus Therning
Continuing my life up-side-down¹ I'm looking for a Haskell wrapper
around GPGME.  Is there such a beast?

/M

¹) That's the life where I turn to Haskell before turning to Python.

-- 
Magnus Therning (OpenPGP: 0xAB4DFBA4)
[EMAIL PROTECTED] Jabber: [EMAIL PROTECTED]
http://therning.org/magnus


pgpYVzDRsqK2o.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] xkcd #287 NP-Complete

2007-07-10 Thread Henning Thielemann

On Tue, 10 Jul 2007, Donald Bruce Stewart wrote:

 These smaller NP problems really love the list monad. here's roconnor's
 solution from #haskell:

 import Control.Monad

 menu = [(Mixed Fruit,215),(French Fries,275)
,(Side Salad,335),(Hot Wings,355)
,(Mozzarella Sticks,420),(Sampler Plate,580)]

 main = mapM_ print
 [ map fst y
 | i - [0..]
 , y - replicateM i menu
 , sum (map snd y) == 1505 ]

Shouldn't we stay away from integer indices on lists?

[ map fst y |
y - concat (iterate (liftM2 (:) menu) [[]]),
sum (map snd y) == 1505]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell and GnuPG?

2007-07-10 Thread Donald Bruce Stewart
magnus:
 Continuing my life up-side-down? I'm looking for a Haskell wrapper
 around GPGME.  Is there such a beast?
 

Don't think there's such a binding yet. Would make a good contribution
though!

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


Re: [Haskell-cafe] xkcd #287 NP-Complete

2007-07-10 Thread Donald Bruce Stewart
lemming:
 
 On Tue, 10 Jul 2007, Donald Bruce Stewart wrote:
 
  These smaller NP problems really love the list monad. here's roconnor's
  solution from #haskell:
 
  import Control.Monad
 
  menu = [(Mixed Fruit,215),(French Fries,275)
 ,(Side Salad,335),(Hot Wings,355)
 ,(Mozzarella Sticks,420),(Sampler Plate,580)]
 
  main = mapM_ print
  [ map fst y
  | i - [0..]
  , y - replicateM i menu
  , sum (map snd y) == 1505 ]
 
 Shouldn't we stay away from integer indices on lists?
 
 [ map fst y |
 y - concat (iterate (liftM2 (:) menu) [[]]),
 sum (map snd y) == 1505]

Also, wouldn't it be nice to bring back monad comprehensions...

Bring them back! No one's scared any more!

-- Don

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


[Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Tony Morris
Is there a performance penalty to be paid when using CPS instead of
pattern matching? CPS often feels more concise but I suspect that it
incurs a cost because of the accumulating stack that pattern matching
wouldn't.

When you you use maybe :: b - (a - b) - Maybe a - b instead of
pattern matching a returned Maybe value?

Is there something a bit more concrete on this issue?

-- 
Tony Morris
http://tmorris.net/

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


Re: [Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Donald Bruce Stewart
tmorris:
 When you you use maybe :: b - (a - b) - Maybe a - b instead of
 pattern matching a returned Maybe value?
 
 Is there something a bit more concrete on this issue?

You mean, versus using 'case' or sugar for case?
It'll just inline to the same code.

For example:

maybe 10 (\n - n + 1) bigexpr

 = {inline maybe}

(\n f x - case x of
Nothing - n
Just x  - f x) 10 (\n - n + 1) bigexpr

 = {reduce}

case bigexpr of
Nothing - 10
Just x  - x+1

So use 'maybe' if its clearer -- it doesn't cost anything.

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


Re: [Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Tony Morris
Thanks Don,
Is your explanation specific to maybe? Or does that apply to all functions?

Suppose the following function for lists:

f :: [a] - b - (a - [a] - b) - b

...instead of pattern matching [] and (x:xs)

Tony Morris
http://tmorris.net/



Donald Bruce Stewart wrote:
 tmorris:
 When you you use maybe :: b - (a - b) - Maybe a - b instead of
 pattern matching a returned Maybe value?

 Is there something a bit more concrete on this issue?
 
 You mean, versus using 'case' or sugar for case?
 It'll just inline to the same code.
 
 For example:
 
 maybe 10 (\n - n + 1) bigexpr
 
  = {inline maybe}
 
 (\n f x - case x of
 Nothing - n
 Just x  - f x) 10 (\n - n + 1) bigexpr
 
  = {reduce}
 
 case bigexpr of
 Nothing - 10
 Just x  - x+1
 
 So use 'maybe' if its clearer -- it doesn't cost anything.
 
 -- Don
 
 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Henning Thielemann

On Tue, 10 Jul 2007, Tony Morris wrote:

 Is your explanation specific to maybe? Or does that apply to all functions?

 Suppose the following function for lists:

 f :: [a] - b - (a - [a] - b) - b

 ...instead of pattern matching [] and (x:xs)

A foldr without recursion. I use such functions frequently in order to
hide constructors of a data type. Does this kind of functions has a common
name?

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


Re: [Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Donald Bruce Stewart
tmorris:
 Thanks Don,
 Is your explanation specific to maybe? Or does that apply to all functions?
 
 Suppose the following function for lists:
 
 f :: [a] - b - (a - [a] - b) - b
 
 ...instead of pattern matching [] and (x:xs)

It really depends on the body of 'f'. If they're simple wrappers over
case analysis they should be inlined perfectly.

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


Re: [Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Donald Bruce Stewart
lemming:
 
 On Tue, 10 Jul 2007, Tony Morris wrote:
 
  Is your explanation specific to maybe? Or does that apply to all functions?
 
  Suppose the following function for lists:
 
  f :: [a] - b - (a - [a] - b) - b
 
  ...instead of pattern matching [] and (x:xs)
 
 A foldr without recursion. I use such functions frequently in order to
 hide constructors of a data type. Does this kind of functions has a common
 name?

They're catamorphisms:

Bool  - cond/if-then-else
Maybe - maybe
(,)   - uncurry
[]- foldr

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


[Haskell-cafe] Re: GHC threads and SMP

2007-07-10 Thread Simon Marlow

Donald Bruce Stewart wrote:

ninegua:

replying to my own message... the behavior is only when -O is used
during compilation, otherwise they both run on 2 cores but at a much
lower (1/100) speed.


Hmm, any change with -O2? Is the optimiser changing the code such that
the scheduler doesn't get to switch threads as often? If you change
the thread scheduler switching rate does that change anything?

See the GHC user's guide for more details:

7.12.1.3.�Scheduling policy for concurrent threads

Runnable threads are scheduled in round-robin fashion. Context switches are
signalled by the generation of new sparks or by the expiry of a virtual 
timer
(the timer interval is configurable with the -C[num] RTS option). 
However, a
context switch doesn't really happen until the current heap block is full. 
You
can't get any faster context switching than this.

When a context switch occurs, pending sparks which have not already been
reduced to weak head normal form are turned into new threads. However, 
there is
a limit to the number of active threads (runnable or blocked) which are 
allowed
at any given time. This limit can be adjusted with the -t num RTS option 
(the
default is 32). Once the thread limit is reached, any remaining sparks are
deferred until some of the currently active threads are completed.


I think you got that from an old version of the users's guide - it certainly 
isn't in the 6.6.1 or HEAD versions of the docs.


I don't have any specific advice about the program in this thread, but in my 
(limited) experience with debugging parallelism problems in GHC, these are common:


 (a) the child threads aren't doing any work, just accumulating a large
 thunk which gets evaluated by the main thread sequentially.

 (b) you have a sequential dependency somewhere

 (c) tight loops that don't allocate don't give the scheduler a chance
 to run and load-balance.

 (d) GHC's scheduler is too stupid


I doubt that (c) is a problem for you: it normally occurs when you try to use 
par/seq and strategies, and are playing with parallel fibonacci.  Here you are 
using forkIO which definitely allocates, so that shouldn't be a problem.


(d) is quite possible.  I once tried to parallelise the simple concurrency 
example from the language shootout, which essentially consists of a long chain 
of threads with data items being passed along the chain.  I could only get any 
kind of speedup when I fixed half the chain on to each CPU, rather than using 
the automatic migration logic in the scheduler.  You can use GHC.Conc.forkOn for 
this:


  forkOnIO :: Int - IO () - IO ThreadId

pass it an integer T, and the thread will be stuck to CPU T `mod` N (where N is 
the number of CPUs).  The RTS doesn't really phyisically fix its execution units 
to CPUs, but usually the OS manages to do a reasonable job of this.


In GHC 6.8, hopefully we'll have some better tools for debugging parallelism 
performance problems.  Michael Adams (who just finished an internship here at 
MSR) ported some of the GranSim visualisation tools to the current GHC, I have 
the patches sitting in my inbox ready to review.


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


Re: [Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Henning Thielemann

On Tue, 10 Jul 2007, Donald Bruce Stewart wrote:

 lemming:
 
  On Tue, 10 Jul 2007, Tony Morris wrote:
 
   Is your explanation specific to maybe? Or does that apply to all 
   functions?
  
   Suppose the following function for lists:
  
   f :: [a] - b - (a - [a] - b) - b
  
   ...instead of pattern matching [] and (x:xs)
 
  A foldr without recursion. I use such functions frequently in order to
  hide constructors of a data type. Does this kind of functions has a common
  name?

 They're catamorphisms:

 Bool  - cond/if-then-else
 Maybe - maybe
 (,)   - uncurry
 []- foldr

The emphasis was on without recursion. There is clearly only a
difference for lists. So is there a name for fold without recursion?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] no-coding functional data structures via lazyness

2007-07-10 Thread Janis Voigtlaender

Jonathan Cast wrote:

On Tuesday 10 July 2007, Dave Bayer wrote:


On Jul 9, 2007, at 6:52 PM, Donald Bruce Stewart wrote:


bayer:


Learning Haskell, the Prelude.ShowS type stood out as odd, exploiting
the implementation of lazy evaluation to avoid explicitly writing an
efficient concatenable list data structure.


See also
   http://hackage.haskell.org/cgi-bin/hackage-scripts/package/
dlist-0.3


Thanks; I added a link to the dlist package from my discussion of
this idiom on the Wiki page
http://www.haskell.org/haskellwiki/Prime_numbers

On Jul 9, 2007, at 3:19 PM, Jonathan Cast wrote:


I think we usually call it `exploiting laziness'. . .


My motivation in asking for a name was to be able to find other
Haskell one-liners adequately replacing chapters of data structure
books for problems of modest scale, e.g. finding the 5,000,000th
prime. So far, I know concatenable lists, and heaps.  Is there a Wiki
page where someone teaches this principle for a dozen other classic
data structures? Your one-liner made me laugh, but it didn't help
me in googling, I would have preferred a one-liner teaching me
another classic data structure, or an explanation of why burrowing
into the GHC implementation gives such a speed advantage over a
carefully written explicit data structure.

People in other camps don't really get lazy evaluation, even many
of our ML neighbors. It would pay to communicate this better to the
outside world.



Unfortunately, I'm afraid all I can do at this point is wish you luck in your 
search.


Maybe it is worth pointing out that the concatenable lists trick can
be extended to various other operations on lists. For example, if one
just changes a few definitions in the DList-package as follows:

newtype DList a = DL { unDL :: forall b. (a - b) - [b] - [b] }
fromList = \xs - DL ((++) . (flip List.map xs))
toList   = ($[]) . ($ id) . unDL
empty= DL (const id)
singleton= \x - DL ((++) . (:[]) . ($ x))
cons x xs= DL (\f - (f x:) . unDL xs f)
snoc xs x= DL (\f - unDL xs f . (f x:))
append xs ys = DL (\f - unDL xs f . unDL ys f)
map f xs = DL (unDL xs . (.f))

one gets concatenable, mappable lists in the sense that for those
lists now also map can be done in O(1).

(Of course, the actual cost of computing the mapped function on each
eventually demanded list element is not saved, but there is no O(spine)
cost anymore for distributing the function to each position in the list.
Rather, this becomes O(1), just as the cost of append goes down from
O(spine of the first list) to O(1). If there are repeated maps, such as
in a naive definition of inits, the improvement can be considerable.)

Similar tricks can be played with reverse, filter, (...?).

Just how, can be seen from:

http://wwwtcs.inf.tu-dresden.de/~voigt/p114-voigtlaender.pdf
http://wwwtcs.inf.tu-dresden.de/~voigt/icfp2002-slides.pdf
http://wwwtcs.inf.tu-dresden.de/~voigt/Vanish.lhs

Ciao, Janis.

--
Dr. Janis Voigtlaender
http://wwwtcs.inf.tu-dresden.de/~voigt/
mailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] ANNOUNCE: HCL v1.0 -High-level library for building command line interfaces

2007-07-10 Thread Malte Milatz
Justin Bailey:
 I'm please to announce HCL 1.0 - a library for building command line
 interfaces. [...]
 Included with the library is a hangman game, so if nothing else you
 can enjoy that.

When building on Linux something gets confused because of filenames in
Windows style. Namely, hangman becomes hangman^M, and the word list is
not found because it is hangman/2of12.txt, not hangman\2of12.txt.  You
might want to fix that.

Malte

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


[Haskell-cafe] Re: no-coding functional data structures via lazyness

2007-07-10 Thread apfelmus
Dave Bayer wrote:
 Learning Haskell, the Prelude.ShowS type stood out as odd, exploiting
 the implementation of lazy evaluation to avoid explicitly writing an
 efficient concatenable list data structure.

ShowS has nothing to do with lazy evaluation, the same trick can be done
in a call-by-value language. The idea is to represent a string xs as a
context (xs ++ •).

 merge xs@(x:xt) ys@(y:yt) = case compare x y of
 LT - x : (merge xt ys)
 EQ - x : (merge xt yt)
 GT - y : (merge xs yt)

 diff xs@(x:xt) ys@(y:yt) = case compare x y of
 LT - x : (diff xt ys)
 EQ - diff xt yt
 GT - diff xs yt

 merge' (x:xt) ys = x : (merge xt ys)

 primes = ps ++ (diff ns $ foldr1 merge' $ map f $ tail primes)
 where ps  = [2,3,5]
   ns  = [7,9..]
   f p = [ m*p | m - [p,p+2..]]
 
 The code is very fast for its size; I haven't seen Haskell code posted
 on the web that comes close, and it is faster than any of my other tries
 (I posted this code to http://www.haskell.org/haskellwiki/Prime_numbers).
 Effectively, it steals a heap data structure out of thin air by
exploiting the
 implementation of lazy evaluation. It would seem that GHC's core data
 structures are coded closer to the machine that anything I can write
 _in_ Haskell. So much for studying how to explicitly write a good heap!

While your observation that merge may create an implicit heap is true,
it doesn't happen in your code :) When unfolding the foldr1, we get
something like

  2:.. `merge'` (3:.. `merge'` (5:.. `merge1` (...)))

i.e. just a linear chain of merges. Retrieving the least element is
linear time in the worst case. This shape will not change with
subsequent reductions of  merge. In other words, it's the responsibility
of  fold  to build a heap. Mergesort shows how a fold can build a heap:

  http://thread.gmane.org/gmane.comp.lang.haskell.general/15007

For  primes , the heap shape has to be chosen carefully in order to
ensure termination. It's the same problem that forces you to use  foldr1
merge'  instead of  foldr1 merge .


There's also a long thread about prime sieves

  http://thread.gmane.org/gmane.comp.lang.haskell.cafe/19699


Regards,
apfelmus

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


Re: [Haskell-cafe] ANNOUNCE: HCL v1.0 -High-level library for building command line interfaces

2007-07-10 Thread Neil Mitchell

Hi


When building on Linux something gets confused because of filenames in
Windows style. Namely, hangman becomes hangman^M


Your Cabal file should be in Unix format, i.e. without \r\n's in it,
just \n's. Arguably this is either a Cabal bug, or something that
Cabal-upload should be checking.

Thanks

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


[Haskell-cafe] Looking for final year project - using Haskell, or another functional language

2007-07-10 Thread wp

Hi all,

I will soon be doing my last year in computer science.
One part of our last year encompasses quite a big project which will
go over 3 terms and will account for 3 modules (45 credits).
I was thinking in doing something using functional languages
(preferably Haskell, as it's the one I know most).
Does anybody know anyone who would have a task suitable for such a
project which would encompass the whole development life cycle (maybe a
sub-project?). I
would do this obviously for free; the client can be anyone
(industrial, academic, open source, etc. ... ), as long as the project
is something serious and for practical usage.
I would be happy for any suggestions ...
Thanks
walter.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] A really bad way to say all isSpace

2007-07-10 Thread Neil Mitchell

Hi,

Reading through the code to read:

read s  =  case [x | (x,t) - reads s, (,) - lex t] of
   [x] - x
   []  - error Prelude.read: no parse
   _   - error Prelude.read: ambiguous parse

Reading through the code to lex, it appear that it will return
[(,)] if and only if all isSpace t.

If this is really the case, does it make sense to state all isSpace t?
It has a much clearer meaning to me.

Thanks

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


Re: [Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Jonathan Cast
On Tuesday 10 July 2007, Tony Morris wrote:
 Thanks Don,
 Is your explanation specific to maybe? Or does that apply to all functions?

 Suppose the following function for lists:

 f :: [a] - b - (a - [a] - b) - b

 ...instead of pattern matching [] and (x:xs)

Of course.  GHC doesn't know anything about maybe; all it sees is:

1. One-liner:

maybe f x mb = case mb of { Just x' - f x'; Nothing - x }

2. Non-recursive

And it inlines like crazy.  If you had quite a large data type, the number of 
case alternatives /might/ put you over GHC's inlining threshold, but that 
(ridiculous) scenario is the only thing that'll keep the argument from 
generalizing to your use case.

snip

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Nicolas Frisby

This might be a feasible appropriation of the term destructor.

On 7/10/07, Bruno Oliveira [EMAIL PROTECTED] wrote:

On Tue, 10 Jul 2007 10:53:35 +0200 (MEST), Henning Thielemann wrote:
On Tue, 10 Jul 2007, Tony Morris wrote:
A foldr without recursion. I use such functions frequently in order to
hide constructors of a data type. Does this kind of functions has a common
name?

I think they just called case analysis; at least that's the terminology used 
here:

http://www.dcs.st-andrews.ac.uk/~james/RESEARCH/concon.pdf

(See the treeCase example in Section 3).

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


[Haskell-cafe] Sequence Classes

2007-07-10 Thread Jonathan Cast
I was just meditating on array fusion using streams, and list fusion using 
streams, and it struck me: the definition of the list functions over arrays 
is the same as that of the list functions over lists.  From the ByteString 
paper, we get:

map f = transformerBi (mapS f)
foldr f z = consumerDn (foldrS f z)
foldl f z = consumerUp (foldlS f z)
replicate n = producerBi (replicateS n)

etc.

So why not say

class Sequence t alpha where
  consumerUp, consumerDn, consumerBi
:: (Stream alpha - beta) - t alpha - beta
  producerUp, producerDn, producerBi :: Stream alpha - t alpha
  transformerUp, transformerDn, transformerBi
:: Sequence t beta = (Stream alpha - Stream beta) - t alpha - t beta

map :: Sequence t alpha = (alpha - beta) - t alpha - t beta
map f = transformerBi (mapS f)

etc.?

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Constraints on data-types, mis-feature?

2007-07-10 Thread Jim Apple

On 7/9/07, Jonathan Cast [EMAIL PROTECTED] wrote:

GADTs don't change anything (at least, not the last time I checked).


GHC (in HEAD, at least) eliminates this wart for any datatype declared
with GADT syntax.

http://www.haskell.org/ghc/dist/current/docs/users_guide/data-type-extensions.html#gadt-style

Any data type that can be declared in standard Haskell-98 syntax can
also be declared using GADT-style syntax. The choice is largely
stylistic, but GADT-style declarations differ in one important
respect: they treat class constraints on the data constructors
differently. Specifically, if the constructor is given a type-class
context, that context is made available by pattern matching.

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


Re: [Haskell-cafe] ANNOUNCE: HCL v1.0 -High-level library for building command line interfaces

2007-07-10 Thread Neil Mitchell

Hi


 Your Cabal file should be in Unix format, i.e. without \r\n's in it,
 just \n's.

I'm surprised that our resident Windows hacker would advocate this,
instead of a more tolerant approach to line ending conventions :-)


Line endings should be one character long, they always should have
been. Windows internally opens all files with \r\n and then maps them
to \n when you read them! How silly! I've been bitten with binary vs
text time and time again, CVS, writeFile, readFile, everything just
breaks based on weird assumptions. I write all my code with \n, and
using TextPad, I can open any text file with any line ending and have
it appear correctly.

I have also emailed the Cabal people and requested that they don't
choke on \r's, but in general, \r\n should be killed.

Thanks

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


Re: [Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Tony Morris
Thanks for the explanations - fully understood.

Tony Morris
http://tmorris.net/



Jonathan Cast wrote:
 On Tuesday 10 July 2007, Tony Morris wrote:
 Thanks Don,
 Is your explanation specific to maybe? Or does that apply to all functions?

 Suppose the following function for lists:

 f :: [a] - b - (a - [a] - b) - b

 ...instead of pattern matching [] and (x:xs)
 
 Of course.  GHC doesn't know anything about maybe; all it sees is:
 
 1. One-liner:
 
 maybe f x mb = case mb of { Just x' - f x'; Nothing - x }
 
 2. Non-recursive
 
 And it inlines like crazy.  If you had quite a large data type, the number of 
 case alternatives /might/ put you over GHC's inlining threshold, but that 
 (ridiculous) scenario is the only thing that'll keep the argument from 
 generalizing to your use case.
 
 snip
 
 Jonathan Cast
 http://sourceforge.net/projects/fid-core
 http://sourceforge.net/projects/fid-emacs
 ___
 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] reading existential types

2007-07-10 Thread Jim Apple

reading existentials (or gadts, for that matter)
is an interesting problem. sometimes too interesting..


http://www.padsproj.org/

is a project that allows automated reading codde for even some
dependently-typed data. Perhaps it has something to offer for
automatic deriving of Read instances for GADTs?

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


Re: [Haskell-cafe] ANNOUNCE: HCL v1.0 -High-level library for building command line interfaces

2007-07-10 Thread Justin Bailey

On 7/10/07, Neil Mitchell [EMAIL PROTECTED] wrote:

Your Cabal file should be in Unix format, i.e. without \r\n's in it,
just \n's. Arguably this is either a Cabal bug, or something that
Cabal-upload should be checking.


I've uploaded a new version with LF only in the cabal file. Please let
me know if it works for you, and my thanks to Neil for the tip.

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/HCL-1.1

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


Re: [Haskell-cafe] xkcd #287 NP-Complete

2007-07-10 Thread Hugh Perkins

This is a compact solution, but it produces multiple permutations of the
same solution, which increases runtime.  I let it run for 10 seconds, then
ctrl-c'd.

Here's a solution that produces all 2 (or three, if you include Barbecue
Sandwich) solutions instantly:

Output:
=

*Xkcd287 go
Menu 1
**
Mixed Fruit ($2.15) x 7
Total: 15.05

Menu 2
**
Hot Wings ($3.55) x 2
Mixed Fruit ($2.15) x 1
Sample Plate ($5.8) x 1
Total: 15.05

Menu 3
**
Barbecue Sandwich ($6.55) x 1
Mixed Fruit ($2.15) x 2
Mozzarella Sticks ($4.2) x 1
Total: 15.05

*Xkcd287

Sourcecode:
=

module Xkcd287
  where

import Char
import IO
import GHC.Float
import List
import qualified Data.Map as Map
import Control.Monad
import Control.Monad.State
import Control.Monad.Reader
import Control.Monad.Writer

menu :: [(String,Int)]
menu = [(Mixed Fruit, 215),
   (French Fries, 275),
   (Side Salad, 335),
   (Hot Wings, 355),
   (Mozzarella Sticks, 420),
   (Sample Plate, 580),
   (Barbecue Sandwich, 655) ]

cost:: Int
cost = 1505

solutions :: [(String,Int)] - Int - [[(String,Int)]]
solutions menu targetcost = [ solution | solution - solutions' menu []
targetcost ]

solutions' :: [(String,Int)] - [(String,Int)] - Int - [[(String,Int)]]
solutions' menu itemssofar targetcost | targetcost == 0 = [itemssofar]
 | otherwise = [ solution | item -
menu,
(null
itemssofar) || ((snd item) = snd(head itemssofar)),
(snd item)
= targetcost,
solution -
solutions' menu (item:itemssofar) (targetcost - (snd item) ) ]

synthesize :: [[(String,Int)]] - [[(String,Int,Int)]]
synthesize solutions = [ synthesize' solution | solution - solutions ]

synthesize' :: [(String,Int)] - [(String,Int,Int)]
synthesize' solution = [ (name,value,count) | (name,(value,count)) -
synthesize'' ]
  where synthesize'' :: [(String,(Int,Int))]
synthesize'' = Map.toList $ foldr (\(name,value) thismap -
(process name value (Map.lookup name thismap) thismap) ) Map.empty solution
process :: String - Int - Maybe (Int,Int) - Map.Map String
(Int,Int) - Map.Map String (Int,Int)
process name value Nothing thismap = Map.insert name (value,1 )
thismap
process name value (Just(value',count)) thismap =
Map.adjust(\(oldvalue,oldcount) - (oldvalue,oldcount + 1)) name
thismap

createbilling :: [[(String,Int,Int)]] - [String]
createbilling solutions = [ line | (solution,i) - (zip solutions [1..]),
  line - [Menu  ++ show(i), **] ++
  createbilling' solution ++
  [Total:  ++ show( (int2Double $
foldr (\(name,value,count) total - (total + (value * count)) ) 0 solution )
/ 100) ] ++
  []
  ]

createbilling' :: [(String,Int,Int)] - [String]
createbilling' solution = [ name ++  ($ ++ show((int2Double value) / 100.0)
++ ) x  ++ show(count) | (name,value,count) - solution ]

go' :: [[(String,Int,Int)]]
go' = synthesize $ solutions menu cost

go :: IO ()
go = mapM_ putStrLn (createbilling $ go' )


On 7/10/07, Henning Thielemann [EMAIL PROTECTED] wrote:



On Tue, 10 Jul 2007, Donald Bruce Stewart wrote:

 These smaller NP problems really love the list monad. here's roconnor's
 solution from #haskell:

 import Control.Monad

 menu = [(Mixed Fruit,215),(French Fries,275)
,(Side Salad,335),(Hot Wings,355)
,(Mozzarella Sticks,420),(Sampler Plate,580)]

 main = mapM_ print
 [ map fst y
 | i - [0..]
 , y - replicateM i menu
 , sum (map snd y) == 1505 ]

Shouldn't we stay away from integer indices on lists?

[ map fst y |
y - concat (iterate (liftM2 (:) menu) [[]]),
sum (map snd y) == 1505]
___
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] Type system madness

2007-07-10 Thread Andrew Coppin

Stefan O'Rear wrote:

On Mon, Jul 09, 2007 at 09:57:14PM +0100, Andrew Coppin wrote:
  

(BTW... How in the hell do you get symbols like that in plain ASCII??)



You can't, but the most commonly used replacement for ASCII
(Unicode-UTF8) supports them just fine.


Wait... I thought Unicode was still an experimental prototype? Since 
when does it work in the real world??



Consider the ST monad, which lets you use update-in-place, but is
escapable (unlike IO).  ST actions have the form:

ST s α

Meaning that they return a value of type α, and execute in thread s.
All reference types are tagged with the thread, so that actions can only
affect references in their own thread.
  


...so *that* is what that thing does...! (I thought it did something 
quite different.)



Now, the type of the function used to escape ST is:

runST :: ∀ α. (∀ s. ST s α) → α

The action you pass must be universal in s, so inside your action you
don't know what thread, thus you cannot access any other threads, thus
runST is pure.  This is very useful, since it allows you to implement
externally pure things like in-place quicksort, and present them as pure
functions ∀ e. Ord e ⇒ Array e → Array e; without using any unsafe
functions.
  


...so the 's' doesn't really exist, it's just random hackery of the 
type system to implement uniqueness?



But that type of runST is illegal in Haskell-98, because it needs a
universal quantifier *inside* the function-arrow!  In the jargon, that
type has rank 2; haskell 98 types may have rank at most 1.
  


...kinda wishing I hadn't asked... o_O

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


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Neil Mitchell

Hi


 The worst problem that comes of this is a slow loss of disk space, but
 I don't think I'll ever be able to fill this 80G disk :)


...OK...and when you tell GHC to compile something, exactly which
compiler does it run? o_O


It picks whichever one you have first on your $(PATH).

On linux you can do:


which ghc

c:\path\to\ghc

Thanks

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


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Stefan O'Rear
On Tue, Jul 10, 2007 at 08:10:32PM +0100, Andrew Coppin wrote:
 Neil Mitchell wrote:
 ...OK...and when you tell GHC to compile something, exactly which
 compiler does it run? o_O

 It picks whichever one you have first on your $(PATH).

 ...right. Presumably this is isomorphic to whichever one was installed the 
 most recently?

Yes.

Stefan


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


Re: [Haskell-cafe] Type system madness

2007-07-10 Thread Jonathan Cast
On Tuesday 10 July 2007, Andrew Coppin wrote:
 Stefan O'Rear wrote:
  On Mon, Jul 09, 2007 at 09:57:14PM +0100, Andrew Coppin wrote:
  (BTW... How in the hell do you get symbols like that in plain ASCII??)
 
  You can't, but the most commonly used replacement for ASCII
  (Unicode-UTF8) supports them just fine.

 Wait... I thought Unicode was still an experimental prototype? Since
 when does it work in the real world??

Are you serious?  Unicode has been a (more-or-less) working reality on Linux 
for several years now. . .

  Consider the ST monad, which lets you use update-in-place, but is
  escapable (unlike IO).  ST actions have the form:
 
  ST s α
 
  Meaning that they return a value of type α, and execute in thread s.
  All reference types are tagged with the thread, so that actions can only
  affect references in their own thread.

 ...so *that* is what that thing does...! (I thought it did something
 quite different.)

  Now, the type of the function used to escape ST is:
 
  runST :: ∀ α. (∀ s. ST s α) → α
 
  The action you pass must be universal in s, so inside your action you
  don't know what thread, thus you cannot access any other threads, thus
  runST is pure.  This is very useful, since it allows you to implement
  externally pure things like in-place quicksort, and present them as pure
  functions ∀ e. Ord e ⇒ Array e → Array e; without using any unsafe
  functions.

 ...so the 's' doesn't really exist, it's just random hackery of the
 type system to implement uniqueness?

Exactly.

  But that type of runST is illegal in Haskell-98, because it needs a
  universal quantifier *inside* the function-arrow!  In the jargon, that
  type has rank 2; haskell 98 types may have rank at most 1.

 ...kinda wishing I hadn't asked... o_O

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Very freaky

2007-07-10 Thread Andrew Coppin

OK, so technically it's got nothing to do with Haskell itself, but...

I was reading some utterly incomprehensible article in Wikipedia. It was 
saying something about categories of recursive sets or some nonesense 
like that, and then it said something utterly astonishing.


By playing with the lambda calculus, you can come up with functions 
having all sorts of types. For example,


 identity :: x - x

 add :: x - x - x

 apply :: (x - y) - (y - z) - (x - z)

However - and I noticed this myself a while ago - it is quite impossible 
to write a (working) function such as


 foo :: x - y

Now, Wikipedia seems to be suggesting something really remarkable. The 
text is very poorly worded and hard to comprehend, but they seem to be 
asserting that a type can be interpreted as a logic theorum, and that 
you can only write a function with a specific type is the corresponding 
theorum is true. (Conversly, if you have a function with a given type, 
the corresponding theorum *must* be true.)


For example, the type for identity presumably reads as given that x 
is true, we know that x is true. Well, duh!


Moving on, add tells as that if x is true and x is true, then x is 
true. Again, duh.


Now apply seems to say that if we know that x implies y, and we know 
that y implies z, then it follows that x implies z. Which is 
nontrivial, but certainly looks correct to me.


On the other hand, the type for foo says given that some random 
statement x happens to be true, we know that some utterly unrelated 
statement y is also true. Which is obviously nucking futs.


Taking this further, we have ($) :: (x - y) - x - y, which seems to 
read given that x implies y, and that x is true, it follows that y is 
true. Which, again, seems to compute.


So is this all a huge coincidence? Or have I actually suceeded in 
comprehending Wikipedia?


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


Re: [Haskell-cafe] Clearly, Haskell is ill-founded

2007-07-10 Thread Stefan O'Rear
On Tue, Jul 10, 2007 at 08:08:52PM +0100, Andrew Coppin wrote:
 Erm... Wait a sec... coroutines, comonads, coprograms, codata... what in 
 the name of goodness does co actually *mean* anyway??

Nothing.

When mathematicians find a new thing completely unlike an OldThing, but
related by some symmetry, they often call the new thing a CoOldThing.

Data can only be constructed using constructors, but can be
deconstructed using recursive folds;
Codata can only be deconstructed using case analysis, but can be
constructed using recursive unfolds.

Monads keep things inside.
Comonads keep things outside.

Homology theory studies the boundaries of shapes.
Cohomology theory studies the insides of curves.

...

Stefan


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


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Hugh Perkins

On 7/8/07, Andrew Coppin [EMAIL PROTECTED] wrote:


I was wittering on about stream fusion and how great it is, and I got a
message from Mr C++.

(Mr C++ develops commercial games, and is obsessed with performance. For
him, the only way to achieve the best performance is to have total
control over every minute detail of the implementation. He sees Haskell
is a stupid language that can never be fast. It seems he's not alone...)



Just a random observation: the competition for Haskell is not really C or
C++.  C is basically dead; C++ is only really useful when you dont want
people to be able to read your source code.  Java comes close to being
competition, but it's slow and eats memory (except in benchmarks where it
somehow does quite well).

The competition for Haskell is C#, which runs at 80% C++ speed, has a really
decent interface into legacy C libraries, has a garbage collector, bounds
checking, decent debug messages.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Clearly, Haskell is ill-founded

2007-07-10 Thread Creighton Hogg

On 7/9/07, Dan Piponi [EMAIL PROTECTED] wrote:


On 7/8/07, Thomas Conway [EMAIL PROTECTED] wrote:
 The basic claim appears to be that discrete mathematics is a bad
 foundation for computer science. I suspect the subscribers to this
 list would beg to disagree.

Wearing my tin foil hat for the moment, I think that there is a
conspiracy by some computer scientists to drive a wedge between
mathematicians and computer scientists. You can see hints of it in
many places where both mathematicians and computer scientists hang out
and there have been quite a few recent articles setting up mathematics
and computer science as somehow in competition with each other.

Many of the structures studied by mathematicians are algebraic. Many
of the structures studied by computer scientists are coalgebraic (eg.
the web itself can be seen as a vast coalgebraic structure).



Okay Mr. Piponi, as a math geek I can't let that comment about the web slide
without further explanation.  Is it just the idea that coalgebras can
capture the idea of side affects (a - F a) or is there something more
specific that you're thinking of?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] xkcd #287 NP-Complete

2007-07-10 Thread Hugh Perkins

By the way, if you enjoy these problems, there are tons of these at
topcoder.com  I cant help thinking it'd be neat to have topcoder-like
competitions for Haskell, either by pursuading topcoder to integrate support
for Haskell, or hosting our own.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very freaky

2007-07-10 Thread Jonathan Cast
On Tuesday 10 July 2007, Andrew Coppin wrote:
 OK, so technically it's got nothing to do with Haskell itself, but...

Actually, it does: the basic technologies underlying Haskell (combinatory 
logic and the Hindley-Milner type system) were originally invented in the 
course of this stream of research.

 I was reading some utterly incomprehensible article in Wikipedia. It was
 saying something about categories of recursive sets or some nonesense
 like that, and then it said something utterly astonishing.

 By playing with the lambda calculus, you can come up with functions
 having all sorts of types. For example,

   identity :: x - x

   add :: x - x - x

   apply :: (x - y) - (y - z) - (x - z)

 However - and I noticed this myself a while ago - it is quite impossible
 to write a (working) function such as

   foo :: x - y

 Now, Wikipedia seems to be suggesting something really remarkable. The
 text is very poorly worded and hard to comprehend,

Nothing is ever absolutely so --- except the incomprehensibility of 
Wikipedia's math articles.  They're still better than MathWorld, though.

 but they seem to be  
 asserting that a type can be interpreted as a logic theorum, and that
 you can only write a function with a specific type is the corresponding
 theorum is true. (Conversly, if you have a function with a given type,
 the corresponding theorum *must* be true.)

 For example, the type for identity presumably reads as given that x
 is true, we know that x is true. Well, duh!

 Moving on, add tells as that if x is true and x is true, then x is
 true. Again, duh.

 Now apply seems to say that if we know that x implies y, and we know
 that y implies z, then it follows that x implies z. Which is
 nontrivial, but certainly looks correct to me.

 On the other hand, the type for foo says given that some random
 statement x happens to be true, we know that some utterly unrelated
 statement y is also true. Which is obviously nucking futs.

 Taking this further, we have ($) :: (x - y) - x - y, which seems to
 read given that x implies y, and that x is true, it follows that y is
 true. Which, again, seems to compute.

 So is this all a huge coincidence? Or have I actually suceeded in
 comprehending Wikipedia?

Yes, you have.  In the (pure, non-recursive) typed lambda calculus, there is 
an isomorphism between (intuitionistic) propositions and types, and between 
(constructive) proofs and terms, such that a term exists with a given type 
iff a (corresponding) (constructive) proof exists of the corresponding 
(intuitionistic) theorem.  This is called the Curry-Howard isomorphism, after 
Haskell Curry (he whom our language is named for), and whatever computer 
scientist independently re-discovered it due to not having figured out to 
read the type theory literature before doing type theoretic research.

Once functional programming language designers realized that the 
generalization of this to the fragments of intuitionistic logic with logical 
connectives `and' (corresponds to products/record types) and `or' 
(corresponds to sums/union types) holds, as well, the prejudice that 
innovations in type systems should be driven by finding an isomorphism with 
some fragment of intuitionistic logic set in, which gave us existential types 
and rank-N types, btw.  So this is really good research to be doing.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Clearly, Haskell is ill-founded

2007-07-10 Thread Creighton Hogg

On 7/9/07, Conor McBride [EMAIL PROTECTED] wrote:


Hi all

On 9 Jul 2007, at 06:42, Thomas Conway wrote:

 I don't know if you saw the following linked off /.

 http://www.itwire.com.au/content/view/13339/53/

[..]

 The basic claim appears to be that discrete mathematics is a bad
 foundation for computer science. I suspect the subscribers to this
 list would beg to disagree.

It's true that some systems are better characterised as corecursive
coprograms, rather than as recursive programs. This is not a
popular or well-understood distinction. In my career as an advocate
for total programming (in some carefully delineated fragment of a
language) I have many times been gotcha'ed thus: but an operating
system is a program which isn't supposed to terminate. No, an
operating system is supposed to remain responsive. And that's what
total coprograms do.



I'm sorry, but can you expand a little further on this?  I guess I don't
understand how a corecursion = responsive to input but not terminating.
Where does the idea of waiting for input fit into corecursion?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] xkcd #287 NP-Complete

2007-07-10 Thread Andrew Coppin

Albert Y. C. Lai wrote:
You are right, I saw many solutions but they were all equivalent to 
just those two. I did not avoid permutation-induced redundancy.


I was unsure how to eliminate that redundancy. After reading your 
algorithm, I see it. Here is my algorithm modified.


In general, I find this kind of stuff really hard to avoid... :-S

(Or rather, avoid efficiently.)

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


Re: [Haskell-cafe] Very freaky

2007-07-10 Thread Stefan O'Rear
On Tue, Jul 10, 2007 at 08:19:53PM +0100, Andrew Coppin wrote:
 OK, so technically it's got nothing to do with Haskell itself, but...

 I was reading some utterly incomprehensible article in Wikipedia. It was 
 saying something about categories of recursive sets or some nonesense like 
 that, and then it said something utterly astonishing.

 By playing with the lambda calculus, you can come up with functions having 
 all sorts of types. For example,

  identity :: x - x

  add :: x - x - x

  apply :: (x - y) - (y - z) - (x - z)

 However - and I noticed this myself a while ago - it is quite impossible to 
 write a (working) function such as

  foo :: x - y

 Now, Wikipedia seems to be suggesting something really remarkable. The text 
 is very poorly worded and hard to comprehend, but they seem to be asserting 
 that a type can be interpreted as a logic theorum, and that you can only 
 write a function with a specific type is the corresponding theorum is true. 
 (Conversly, if you have a function with a given type, the corresponding 
 theorum *must* be true.)

 For example, the type for identity presumably reads as given that x is 
 true, we know that x is true. Well, duh!

 Moving on, add tells as that if x is true and x is true, then x is 
 true. Again, duh.

 Now apply seems to say that if we know that x implies y, and we know 
 that y implies z, then it follows that x implies z. Which is nontrivial, 
 but certainly looks correct to me.

 On the other hand, the type for foo says given that some random 
 statement x happens to be true, we know that some utterly unrelated 
 statement y is also true. Which is obviously nucking futs.

 Taking this further, we have ($) :: (x - y) - x - y, which seems to 
 read given that x implies y, and that x is true, it follows that y is 
 true. Which, again, seems to compute.

 So is this all a huge coincidence? Or have I actually suceeded in 
 comprehending Wikipedia?

Yup, you understood it perfectly.

This is precisely the Curry-Howard isomorphism I alluded to earlier.

Another good example:

foo :: ∀ pred : Nat → Prop . (∀ n:Nat . pred n → pred (n + 1))
 → pred 0 → ∀ n : Nat . pred n

Which you can read as For all statements about natural numbers, if the
statement applies to 0, and if it applies to a number it applies to the
next number, then it applies to all numbers..  IE, mathematical
induction.

Haskell's type system isn't *quite* powerful enough to express the
notion of a type depending on a number (you can hack around it with a
type-level Peano construction, but let's not go there just yet), but if
you ignore that part of the type:

foo :: (pred - pred) - pred - Int - pred {- the int should be nat, ie 
positive -}
foo nx z 0 = z
foo nx z (n+1) = nx (foo nx z n)

Which is just an iteration function!

http://haskell.org/haskellwiki/Curry-Howard-Lambek_correspondence might
be interesting - same idea, but written for a Haskell audience.

Stefan


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


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Neil Mitchell

Hi


 It picks whichever one you have first on your $(PATH).

...right. Presumably this is isomorphic to whichever one was installed
the most recently?

(Oh, wait... IIRC, on Windoze the GHC installer doesn't actually add GHC
to the PATH variable. You have to do it by hand...)


It does.

Thanks

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


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Hugh Perkins

You're talking to someone who spent his teenage years doing assembler
because that's what l33t games developers did, and I wanted to be like
them.  Sure, you can still find assembler around the place, but even l33t
games developers dont use it any more.

On 7/10/07, Alex Queiroz [EMAIL PROTECTED] wrote:


 Just a random observation: the competition for Haskell is not really C
or
 C++.  C is basically dead;

 20 years from now people will still be saying this...


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


Re: [Haskell-cafe] Type system madness

2007-07-10 Thread Alex Queiroz

Hallo,

On 7/10/07, Andrew Coppin [EMAIL PROTECTED] wrote:


Last time I looked, everything treats text as being 8 bits per
character. (Or, more commonly, 7, and if the MSB isn't 0, weird things
happen...) That's why (for example) HTML has lots of weird constructs
such as hellip; in it, instead of just typing in the actual character
you want. (And let's be clear here: SGML and all those decendents are
all using  and  - the mathematical greater and less operations -
when what they *really* mean are angle brackets, a quite distinct
glyph.) Last time I checked, nobody was keen on using 64 bits per
character...



You must look out more. I use áéíóúç in web pages all the time.

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


Re: [Haskell-cafe] Clearly, Haskell is ill-founded

2007-07-10 Thread Dan Piponi

On 7/10/07, Creighton Hogg [EMAIL PROTECTED] wrote:

Okay Mr. Piponi, as a math geek I can't let that comment about the web slide
without further explanation.  Is it just the idea that coalgebras can
capture the idea of side affects (a - F a) or is there something more
specific that you're thinking of?


First a quick bit of background on algebras.

If F is a functor, an F-algebra is an arrow FX-X. For example if we
choose FX = 1+X+X^2 (using + to mean disjoint union) then an F-algebra
is a function 1+X+X^2-X. The 1-X part just picks out a constant, the
image of 1. The X^2-X defines a binary operator and the X-X part is
an endomorphism. A group has a constant element (the identity) an
endomorphism (the inverse) and a binary operator (multiplication). So
a group is an example of an F-algebra (with some extra equations added
in so a group isn't *just* an F-coalgebra).

A F-coalgebra is an arrow X-FX. As an example, let's pick
FX=(String,[X]). So an F-coalgebra is a function X-(String,[X]). We
can view this as two functions, 'appearance' of type X-String and
'links' of type X-[X]. If X is the type of web pages, then interpret
'appearance' as the rendering (as plain text) of the web page and
links as the function that gives a list of links in the page. So the
web forms a coalgebra. (Though you'll need some extra work to deal
with persistent state like cookies.)

The theme is that mathematicians often like to study objects with some
kind of 'combination' operation like (generalised) addition or
multiplication. These form algebras with maps FX-X. Computer
scientists often like to study things that generate more stuff (eg.
when you press a button or input something). So you end up with
something of the form X-FX. This includes many familiar things like
web pages, state machines and formal languages. This isn't a sharp
divide (of course) but I think it reflects a real difference in
emphasis.

A great source for this stuff is the book 'Vicious Circles' by Barwise
and Moss. It's full of computer sciencey stuff but it seems to be
written for an audience that includes mathematicians and computer
scientists. (It has quite a few typos and more serious errors
however.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very freaky

2007-07-10 Thread Andrew Coppin

Stefan O'Rear wrote:

On Tue, Jul 10, 2007 at 08:19:53PM +0100, Andrew Coppin wrote:
  
So is this all a huge coincidence? Or have I actually suceeded in 
comprehending Wikipedia?



Yup, you understood it perfectly.
  


This is a rare event... I must note it on my calendar! o_O


This is precisely the Curry-Howard isomorphism I alluded to earlier.
  


Yeah, the article I was reading was called Curry-Howard isomorphism. 
But it rambled on for, like, 3 pagefulls of completely opaque 
set-theoretic gibberish before I arrived at the (cryptically phrased) 
statements I presented above. Why it didn't just *say* that in the first 
place I have no idea...



Another good example:

foo :: ∀ pred : Nat → Prop . (∀ n:Nat . pred n → pred (n + 1))
 → pred 0 → ∀ n : Nat . pred n
  


x_x


Which you can read as For all statements about natural numbers, if the
statement applies to 0, and if it applies to a number it applies to the
next number, then it applies to all numbers..  IE, mathematical
induction.
  


...and to think the idea of mathematical symbols is to make things 
*clearer*...



Haskell's type system isn't *quite* powerful enough to express the
notion of a type depending on a number (you can hack around it with a
type-level Peano construction, but let's not go there just yet), but if
you ignore that part of the type:
  


Peano integers are like Church numerals, but less scary. ;-)

(I have a sudden feeling that that would make a good quote for... 
somewhere...)



foo :: (pred - pred) - pred - Int - pred {- the int should be nat, ie 
positive -}
foo nx z 0 = z
foo nx z (n+1) = nx (foo nx z n)

Which is just an iteration function!
  


Error: Insufficient congative power.


http://haskell.org/haskellwiki/Curry-Howard-Lambek_correspondence might
be interesting - same idea, but written for a Haskell audience.
  


An interesting read - although again a little over my head.

I find myself wondering... A polymorphic type signature such as (a - b) 
- a - b says given that a implies b and a is true, b is true. But 
what does, say, Maybe x - x say?


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


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Sebastian Sylvan

On 10/07/07, Alex Queiroz [EMAIL PROTECTED] wrote:

Hallo,

On 7/10/07, Hugh Perkins [EMAIL PROTECTED] wrote:
 On 7/8/07, Andrew Coppin [EMAIL PROTECTED] wrote:
  I was wittering on about stream fusion and how great it is, and I got a
  message from Mr C++.
 
  (Mr C++ develops commercial games, and is obsessed with performance. For
  him, the only way to achieve the best performance is to have total
  control over every minute detail of the implementation. He sees Haskell
  is a stupid language that can never be fast. It seems he's not alone...)
 
 

 Just a random observation: the competition for Haskell is not really C or
 C++.  C is basically dead;

 20 years from now people will still be saying this...


I highly doubt that. For two reasons:
1. People can only cling to unproductive and clumsy tools for so long
(we don't write much assembly any more...). Capitalism works to ensure
this; people who are willing to switch to  more efficient tools will
put the rest out of business (if they really are more efficient).
2. The many-core revolution that's on the horizon.

While I personally think that the productivity argument should be
enough to make the switch, the killer-app (the app that will kill C,
that is :-)) is concurrency. C is just not a tractable tool to program
highly concurrent programs, unless the problem happens to be highly
amenable to concurrency (web servers etc.). We need *something* else.
It may not be Haskell, but it will be something (and it will probably
be closer to Haskell than C!).

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Clearly, Haskell is ill-founded

2007-07-10 Thread Andrew Coppin

Dan Piponi wrote:

First a quick bit of background on algebras.

If F is a functor, an F-algebra is an arrow FX-X. For example if we
choose FX = 1+X+X^2 (using + to mean disjoint union) then an F-algebra
is a function 1+X+X^2-X. The 1-X part just picks out a constant, the
image of 1. The X^2-X defines a binary operator and the X-X part is
an endomorphism. A group has a constant element (the identity) an
endomorphism (the inverse) and a binary operator (multiplication). So
a group is an example of an F-algebra (with some extra equations added
in so a group isn't *just* an F-coalgebra).

A F-coalgebra is an arrow X-FX. As an example, let's pick
FX=(String,[X]). So an F-coalgebra is a function X-(String,[X]). We
can view this as two functions, 'appearance' of type X-String and
'links' of type X-[X]. If X is the type of web pages, then interpret
'appearance' as the rendering (as plain text) of the web page and
links as the function that gives a list of links in the page. So the
web forms a coalgebra. (Though you'll need some extra work to deal
with persistent state like cookies.)


...wosh...

...and now I know what normal people must feel like when *I* open my 
mouth. o_O


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


Re: [Haskell-cafe] Very freaky

2007-07-10 Thread Dan Piponi

On 7/10/07, Andrew Coppin [EMAIL PROTECTED] wrote:

But what does, say, Maybe x - x say?


Maybe X is the same as True or X, where True is the statement that
is always true. Remember that the definition is

data Maybe X = Nothing | Just X

You can read | as 'or', 'Just' as nothing but a wrapper around an X
and Nothing as an axiom.

So Maybe X - X says that True or X implies X. That's a valid proposition.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type system madness

2007-07-10 Thread Albert Y. C. Lai

Andrew Coppin wrote:
Wait... I thought Unicode was still an experimental prototype? Since 
when does it work in the real world??


That myth is as old as Haskell is an experimental prototype. Old as 
in that's an old one.


Windows has been well supporting Unicode since 2000. That is pretty much 
of the real world.


The only reason you see α as the Greek letter alpha and not scrambled 
code is that I send it as Unicode and your Windows and Thunderbird also 
support Unicode and therefore they display it to you properly.


The whole scheme works so well and so transparently that you didn't even 
notice it.


No one notices when things are right.

Alex Queiroz wrote:

You must look out more. I use áéíóúç in web pages all the time.


I even use Chinese. (And no, not those big5 or gb2312 funny business.)

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


Re: [Haskell-cafe] Very freaky

2007-07-10 Thread Stefan O'Rear
On Tue, Jul 10, 2007 at 08:59:16PM +0100, Andrew Coppin wrote:
 http://haskell.org/haskellwiki/Curry-Howard-Lambek_correspondence might
 be interesting - same idea, but written for a Haskell audience.
   

 An interesting read - although again a little over my head.

 I find myself wondering... A polymorphic type signature such as (a - b) - 
 a - b says given that a implies b and a is true, b is true. But what 
 does, say, Maybe x - x say?

Given that x may or may not be true, x is definitely true.

Which, of course, is absurd.

Stefan


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


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Alex Queiroz

Hallo,

On 7/10/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:


I highly doubt that. For two reasons:
1. People can only cling to unproductive and clumsy tools for so long
(we don't write much assembly any more...). Capitalism works to ensure
this; people who are willing to switch to  more efficient tools will
put the rest out of business (if they really are more efficient).


As I replied to Hugh, the Universe of computers is not restricted
to PCs. We, embedded developers, will be using C for a lot of time
still.

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


Re: [Haskell-cafe] Clearly, Haskell is ill-founded

2007-07-10 Thread Andrew Coppin

Stefan O'Rear wrote:

On Tue, Jul 10, 2007 at 08:08:52PM +0100, Andrew Coppin wrote:
  
Erm... Wait a sec... coroutines, comonads, coprograms, codata... what in 
the name of goodness does co actually *mean* anyway??



Nothing.

When mathematicians find a new thing completely unlike an OldThing, but
related by some symmetry, they often call the new thing a CoOldThing.

Data can only be constructed using constructors, but can be
deconstructed using recursive folds;
Codata can only be deconstructed using case analysis, but can be
constructed using recursive unfolds.

Monads keep things inside.
Comonads keep things outside.

Homology theory studies the boundaries of shapes.
Cohomology theory studies the insides of curves.

...
  


...so it's similar to the term normal?

As in

Normal vector - a vector having unit length.
Normal distribution - a common monomodal distribution following a 
characterstic Gaussian bell curve.
Normal subgroup - a subset of a group such that all elements of it 
commute with the all elements of the whole group.

...

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


Re: [Haskell-cafe] Very freaky

2007-07-10 Thread Andrew Coppin

Stefan O'Rear wrote:

On Tue, Jul 10, 2007 at 08:59:16PM +0100, Andrew Coppin wrote:
  
I find myself wondering... A polymorphic type signature such as (a - b) - 
a - b says given that a implies b and a is true, b is true. But what 
does, say, Maybe x - x say?



Given that x may or may not be true, x is definitely true.

Which, of course, is absurd.
  


...which, presumably, is because a (pure) function with that type might 
be able to fail?


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


Re: [Haskell-cafe] Type system madness

2007-07-10 Thread Andrew Coppin

Albert Y. C. Lai wrote:

Andrew Coppin wrote:
Wait... I thought Unicode was still an experimental prototype? Since 
when does it work in the real world??


That myth is as old as Haskell is an experimental prototype. Old 
as in that's an old one.


Windows has been well supporting Unicode since 2000. That is pretty 
much of the real world.


The only reason you see α as the Greek letter alpha and not scrambled 
code is that I send it as Unicode and your Windows and Thunderbird 
also support Unicode and therefore they display it to you properly.


The whole scheme works so well and so transparently that you didn't 
even notice it.


No one notices when things are right.


That is, indeed, impressive.


Alex Queiroz wrote:

You must look out more. I use áéíóúç in web pages all the time.


I even use Chinese. (And no, not those big5 or gb2312 funny business.)


Interesting... I tried to put a pound sign on my web page, and it came 
out garbled, so I had to replace it with pound;...


(BTW, I always wondered how the Asian and Chinese people do any work 
with computers, given that the ASCII character set doesn't even include 
any characters in their alphabet...)


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


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Sebastian Sylvan

On 10/07/07, Alex Queiroz [EMAIL PROTECTED] wrote:

Hallo,

On 7/10/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:

 I highly doubt that. For two reasons:
 1. People can only cling to unproductive and clumsy tools for so long
 (we don't write much assembly any more...). Capitalism works to ensure
 this; people who are willing to switch to  more efficient tools will
 put the rest out of business (if they really are more efficient).

 As I replied to Hugh, the Universe of computers is not restricted
to PCs. We, embedded developers, will be using C for a lot of time
still.



That might eliminate the concurrency imperative (for a while!), but it
doesn't adress the productivity point. My hypothesis is this: People
don't like using unproductive tools, and if they don't have to, they
won't.

When the next mainstream language comes along to solve the
concurrency problem (to some extent), it would seem highly likely that
there will relatively soon be compilers for it for most embedded
devices too, so why would you make your life miserable with C in that
case (and cost your company X dollars due to inefficiency in the
process)?


--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Hugh Perkins

On 7/10/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:


While I personally think that the productivity argument should be
enough to make the switch, the killer-app (the app that will kill C,
that is :-)) is concurrency. C is just not a tractable tool to program
highly concurrent programs, unless the problem happens to be highly
amenable to concurrency (web servers etc.). We need *something* else.
It may not be Haskell, but it will be something (and it will probably
be closer to Haskell than C!).



Yeah I agree with this.  C# totally rocks, but threading is an unsolved
problem.

If you can get to the stage where you can get a non-optimized,
readable/maintainable Haskell program to run at more than say 30% of the
speed of a non-optimized, readable/maintainable C# program, but
automatically runs across 16 or 256 cores, then you're on to a winner.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Clearly, Haskell is ill-founded

2007-07-10 Thread Dan Piponi

On 7/10/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Stefan O'Rear wrote:
 On Tue, Jul 10, 2007 at 08:08:52PM +0100, Andrew Coppin wrote:

 Erm... Wait a sec... coroutines, comonads, coprograms, codata... what in
 the name of goodness does co actually *mean* anyway??
 Nothing.
 When mathematicians find a new thing completely unlike an OldThing, but
 related by some symmetry, they often call the new thing a CoOldThing.


(I got lost somewhere with the levels of quotation there...)

It's more specific than this. Coalgebra, cohomology, codata, comonads
and so on derive their name from the fact that they can be described
using category theory. In category theory you draw lots of diagrams
with arrows in them. When you flip all the arrows round you get a
description of something else. Pairs of concepts connected in this way
often differ by the prefix co-. Often theorems you prove about
objects have analogous theorems about the respective co-objects. In
fact, often the proof is the same, just written with all the arrows
pointing the other way.

This carries over to Haskell too. You can sometimes write functional
(as in useful) code simply by taking an already existing piece of code
and figuring out what flipping the arrows means. It often means
something very different, but it still makes sense. A really cool
example is the relationship between fold and unfold. But I'll leave
that for someone else.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Andrew Coppin

Hugh Perkins wrote:
Yeah I agree with this.  C# totally rocks, but threading is an 
unsolved problem.


I have repeatedly attempted to discover what C# actually is, all to no 
avail. Still, that probably means I don't need it...


If you can get to the stage where you can get a non-optimized, 
readable/maintainable Haskell program to run at more than say 30% of 
the speed of a non-optimized, readable/maintainable C# program, but 
automatically runs across 16 or 256 cores, then you're on to a winner.


Hint: If you can get readable/maintainable Haskell to run on more than 
one core automatically, you're onto something pretty special. ;-)


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


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Sebastian Sylvan

On 10/07/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Hugh Perkins wrote:
 Yeah I agree with this.  C# totally rocks, but threading is an
 unsolved problem.

I have repeatedly attempted to discover what C# actually is, all to no
avail. Still, that probably means I don't need it...

 If you can get to the stage where you can get a non-optimized,
 readable/maintainable Haskell program to run at more than say 30% of
 the speed of a non-optimized, readable/maintainable C# program, but
 automatically runs across 16 or 256 cores, then you're on to a winner.

Hint: If you can get readable/maintainable Haskell to run on more than
one core automatically, you're onto something pretty special. ;-)


Soon, have a little patience :-)

See for example:
http://research.microsoft.com/~simonpj/papers/ndp/NdpSlides.pdf
http://research.microsoft.com/~tharris/papers/2007-fdip.pdf


--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Clearly, Haskell is ill-founded

2007-07-10 Thread Andrew Coppin

Dan Piponi wrote:

(I got lost somewhere with the levels of quotation there...)

It's more specific than this. Coalgebra, cohomology, codata, comonads
and so on derive their name from the fact that they can be described
using category theory. In category theory you draw lots of diagrams
with arrows in them. When you flip all the arrows round you get a
description of something else. Pairs of concepts connected in this way
often differ by the prefix co-. Often theorems you prove about
objects have analogous theorems about the respective co-objects. In
fact, often the proof is the same, just written with all the arrows
pointing the other way.

This carries over to Haskell too. You can sometimes write functional
(as in useful) code simply by taking an already existing piece of code
and figuring out what flipping the arrows means. It often means
something very different, but it still makes sense. A really cool
example is the relationship between fold and unfold. But I'll leave
that for someone else.


Sounds a lot like the Boolean duality principle. (If a statement works 
one way, if you flip all the true/false and/or stuff, you get a brand 
new statement, which also works.)


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


[Haskell-cafe] CGI test

2007-07-10 Thread Andrew Coppin

Greetings.

Can somebody write a trivial (as in: small) program so I can test my CGI 
stuff without having to actually install and configure Apache?


(Basically, I'd like something I can compile into a small binary, so 
when I double-click it, it will listen on port 80, and when it gets a 
HTTP request, it tries to find a program with that name, and run it as a 
CGI script. And that's all. Nothing fancy; if I want fancy Apache can do 
a propper job...)


Actually, might be a useful thing to have in a library somewhere.

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


Re: [Haskell-cafe] Type system madness

2007-07-10 Thread Hugh Perkins

We can consider three families of character sets:
- ASCII: 127 characters, some of which are escape codes like bell etc
- regional encodings: china uses GB2312, Europe uses ISO-8859-1, America
uses ... something
- unicode: UTF-8, UTF-16

The regional encodings are optimized for their region, and they only support
characters from their own region, so the chinese character set (GB2312)
contains all the chinese characters, and the english letters, but it doesnt
contain for example French characters like é or ç.

Similarly ISO-8859-1 contains the characters for all the european langauges
(I think), but it doesnt contain the Chinese characters.

Unicode contains the characters from *all* the worlds languages combined.
UTF-16 encodes this uses 2 or more bytes.  UTF-8 encodes this using 1 or
more bytes.

Basically the characters 0-127 are identical between ASCII and UTF-8, then
numbers from 128 onwards are a flag to say that you need to read another
byte or so to get the full information to know the character (something like
that).

UTF-16 kindof sucks because its not compatible with ASCII, and it uses twice
as many bytes for English characters.  On the other hand its what Windows NT
uses.  UTF-8 is compatible with ASCII, but it can use more bytes to encode
the data for certain non-English characters than UTF-16.

On 7/10/07, Andrew Coppin [EMAIL PROTECTED] wrote:


(BTW, I always wondered how the Asian and Chinese people do any work
with computers, given that the ASCII character set doesn't even include
any characters in their alphabet...)

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


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Alex Queiroz

Hallo,

On 7/10/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:


That might eliminate the concurrency imperative (for a while!), but it
doesn't adress the productivity point. My hypothesis is this: People
don't like using unproductive tools, and if they don't have to, they
won't.



So you think we use C because we like it? :-) When this
revolutionary tool of yours arrive that compiles Haskell to PIC
devices, I'm gonna be the first to use it.

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


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Jon Harrop
On Tuesday 10 July 2007 21:02:45 Sebastian Sylvan wrote:
 While I personally think that the productivity argument should be
 enough to make the switch, the killer-app (the app that will kill C,
 that is :-)) is concurrency. C is just not a tractable tool to program
 highly concurrent programs, unless the problem happens to be highly
 amenable to concurrency (web servers etc.). We need *something* else.
 It may not be Haskell, but it will be something (and it will probably
 be closer to Haskell than C!).

As long as your C-killer language has a run-time that is written in C, it 
won't be killing C. :-)

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
The OCaml Journal
http://www.ffconsultancy.com/products/ocaml_journal/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Clearly, Haskell is ill-founded

2007-07-10 Thread Dan Piponi

On 7/10/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Sounds a lot like the Boolean duality principle.


That is, in fact, very closely related.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very freaky

2007-07-10 Thread Dan Piponi

On 7/10/07, Dan Piponi [EMAIL PROTECTED] wrote:

On 7/10/07, Andrew Coppin [EMAIL PROTECTED] wrote:
 But what does, say, Maybe x - x say?


Silly me. You reversed the arrows and I copied you. (Could it be
something to do with the other conversation we were having?)

I meant to say:

So x - Maybe x says that X implies True or X. That's a valid
proposition and so there is a function x - Maybe x.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] function unique

2007-07-10 Thread Alexteslin

Hi, i am a beginner to Haskell and i have a beginner's question to ask.

An exercise asks to define function unique :: [Int] - [Int], which outputs
a list with only elements that are unique to the input list (that appears no
more than once).  I defined a function with list comprehension which works
but trying to implement with pattern matching and primitive recursion with
lists and doesn't work.

unique :: [Int] - [Int]
unique xs = [x | x - xs, elemNum2 x xs == 1]


elemNum2 :: Int - [Int] - Int
elemNum2 el xs = length [x| x - xs, x == el]

//This doesn't work, I know because the list shrinks and produces wrong
result but can not get a right //thinking

unique2 :: [Int] - [Int]
unique2 [] = []
unique2 (x:xs)
|elemNum2 x xs == 1 = x:unique2 xs
|otherwise = unique2 xs


Any help to a right direction would be very appreciated, thanks.
-- 
View this message in context: 
http://www.nabble.com/function-unique-tf4058328.html#a11528933
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Looking for final year project - using Haskell, or another functional language

2007-07-10 Thread Hugh Perkins

rpc layer, like .Net Remoting or ICE (but preferably without needing
configuration/interface files)

Course, if you know what you're doing, that's more like 1 week than one
year, but you could do that and then see where it takes you.

If you want something really challenging, rewrite OSMP (
http://metaverse.sf.net) in Haskell, and get it better than
http://secondlife.com

If you want a commercial idea, try convincing http://lindenlab.com to let
you implement Haskell as a scripting language within SecondLife.

If you're interested in designing human-computer interfaces, make a version
of Haskell that is easy to use: eg do something so that the nasty bits are
hidden.  Why can you write a function both in lambda notation and in the
non-lambda notation?  Make it so that there is only one way to write a
function.  That means less stuff to learn!  Get rid of all the nastiness
with using Transformer monads etc: make it so we can just provide a couple
of monads as our environment, and not have to think about the underlying
maths.

Implement the entire opengl 1.3 interface specifications in Haskell.

Make Glade work in Haskell as easily as it works in mono.

Create a topcoder-like algorithm competition.  Convince at least 100 people
to participate each week.  Find a sponsor to provide a 16-core server. Let
people write their algorithms in both threaded C# and threaded Haskell.
Create algorithm problems that consistently bring out the best in Haskell,
so that the  Haskell competitors win.

Work with Simon Peyton Jones to implement automatic threading in ghc.

On 7/10/07, wp [EMAIL PROTECTED] wrote:


Hi all,

I will soon be doing my last year in computer science.
One part of our last year encompasses quite a big project which will
go over 3 terms and will account for 3 modules (45 credits).
I was thinking in doing something using functional languages
(preferably Haskell, as it's the one I know most).
Does anybody know anyone who would have a task suitable for such a
project which would encompass the whole development life cycle (maybe a
sub-project?). I
would do this obviously for free; the client can be anyone
(industrial, academic, open source, etc. ... ), as long as the project
is something serious and for practical usage.
I would be happy for any suggestions ...
Thanks
walter.
___
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] In-place modification

2007-07-10 Thread Sebastian Sylvan

On 10/07/07, Alex Queiroz [EMAIL PROTECTED] wrote:

Hallo,

On 7/10/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:

 That might eliminate the concurrency imperative (for a while!), but it
 doesn't adress the productivity point. My hypothesis is this: People
 don't like using unproductive tools, and if they don't have to, they
 won't.


 So you think we use C because we like it? :-) When this
revolutionary tool of yours arrive that compiles Haskell to PIC
devices, I'm gonna be the first to use it.



No, you use it because you have to, there is very little choice. Which
is exactly my point.

I don't think it's unreasonable to expect that when nobody uses C for
desktop applications, games etc. anymore because there's a better
language available and widely supported, that some version of this
next mainstream language will make it onto embedded devices too.

The revolution (tm) won't come at the same time for all domains. C is
probably used/supported in embedded devices mostly because it's
popular for non-embedded devices (not because C is somehow uniquely
suited for embedded devices). So what happens when something else is
popular, when most industries have stopped using C and almost nobody
coming from university knows it very well or at all? Isn't it likely
that a lot of vendors will write compilers targeting embedded devices
for this new popular language?


--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function unique

2007-07-10 Thread Brent Yorgey

The problem with your second implementation is that elements which occur
more than once will eventually be included, when the part of the list
remaining only has one copy. For example:

unique2 [1,1,2,4,1]
= unique2 [1,2,4,1]
= unique2 [2,4,1]
= 2 : unique2 [4,1]
= 2 : 4 : unique2 [1]
= 2 : 4 : 1 : unique2 []   -- only a single 1 left, so it gets mistakenly
included
= [2,4,1]

When you determine that a certain number should not be included in the
output, you need to delete all remaining occurrences of it from the list, so
it won't get included later.

unique2 (x:xs)
   |elemNum2 x xs == 1 = x:unique2 xs
   |otherwise = unique2 (deleteElt x xs)

I'll let you figure out how to implement the deleteElt function.

hope this is helpful!
-Brent

On 7/10/07, Alexteslin [EMAIL PROTECTED] wrote:



Hi, i am a beginner to Haskell and i have a beginner's question to ask.

An exercise asks to define function unique :: [Int] - [Int], which
outputs
a list with only elements that are unique to the input list (that appears
no
more than once).  I defined a function with list comprehension which works
but trying to implement with pattern matching and primitive recursion with
lists and doesn't work.

unique :: [Int] - [Int]
unique xs = [x | x - xs, elemNum2 x xs == 1]


elemNum2 :: Int - [Int] - Int
elemNum2 el xs = length [x| x - xs, x == el]

//This doesn't work, I know because the list shrinks and produces wrong
result but can not get a right //thinking

unique2 :: [Int] - [Int]
unique2 [] = []
unique2 (x:xs)
|elemNum2 x xs == 1 = x:unique2 xs
|otherwise = unique2 xs


Any help to a right direction would be very appreciated, thanks.
--
View this message in context:
http://www.nabble.com/function-unique-tf4058328.html#a11528933
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
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] xkcd #287 NP-Complete

2007-07-10 Thread Andrew Coppin

Hugh Perkins wrote:

There's a good tutorial on pruning at:

http://www.cs.nott.ac.uk/~gmh/book.html 
http://www.cs.nott.ac.uk/%7Egmh/book.html  (Section Slides, number 11)


In general, I find this kind of stuff really hard to avoid... :-S



...and indeed, countdown was what I was attempting to solve... o_O

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


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Andrew Coppin

Sebastian Sylvan wrote:

That might eliminate the concurrency imperative (for a while!), but it
doesn't adress the productivity point. My hypothesis is this: People
don't like using unproductive tools, and if they don't have to, they
won't.

When the next mainstream language comes along to solve the
concurrency problem (to some extent), it would seem highly likely that
there will relatively soon be compilers for it for most embedded
devices too, so why would you make your life miserable with C in that
case (and cost your company X dollars due to inefficiency in the
process)?


...because only C works on bizzare and unusual hardware?

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


Re: [Haskell-cafe] function unique

2007-07-10 Thread Alexteslin

I'v got it - it produces the right output.
Thank you.


Brent Yorgey wrote:
 
 The problem with your second implementation is that elements which occur
 more than once will eventually be included, when the part of the list
 remaining only has one copy. For example:
 
 unique2 [1,1,2,4,1]
 = unique2 [1,2,4,1]
 = unique2 [2,4,1]
 = 2 : unique2 [4,1]
 = 2 : 4 : unique2 [1]
 = 2 : 4 : 1 : unique2 []   -- only a single 1 left, so it gets mistakenly
 included
 = [2,4,1]
 
 When you determine that a certain number should not be included in the
 output, you need to delete all remaining occurrences of it from the list,
 so
 it won't get included later.
 
 unique2 (x:xs)
 |elemNum2 x xs == 1 = x:unique2 xs
 |otherwise = unique2 (deleteElt x xs)
 
 I'll let you figure out how to implement the deleteElt function.
 
 hope this is helpful!
 -Brent
 
 On 7/10/07, Alexteslin [EMAIL PROTECTED] wrote:


 Hi, i am a beginner to Haskell and i have a beginner's question to ask.

 An exercise asks to define function unique :: [Int] - [Int], which
 outputs
 a list with only elements that are unique to the input list (that appears
 no
 more than once).  I defined a function with list comprehension which
 works
 but trying to implement with pattern matching and primitive recursion
 with
 lists and doesn't work.

 unique :: [Int] - [Int]
 unique xs = [x | x - xs, elemNum2 x xs == 1]


 elemNum2 :: Int - [Int] - Int
 elemNum2 el xs = length [x| x - xs, x == el]

 //This doesn't work, I know because the list shrinks and produces wrong
 result but can not get a right //thinking

 unique2 :: [Int] - [Int]
 unique2 [] = []
 unique2 (x:xs)
 |elemNum2 x xs == 1 = x:unique2 xs
 |otherwise = unique2 xs


 Any help to a right direction would be very appreciated, thanks.
 --
 View this message in context:
 http://www.nabble.com/function-unique-tf4058328.html#a11528933
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

 ___
 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
 
 

-- 
View this message in context: 
http://www.nabble.com/function-unique-tf4058328.html#a11529400
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Andrew Coppin

Sebastian Sylvan wrote:

On 10/07/07, Alex Queiroz [EMAIL PROTECTED] wrote:

 So you think we use C because we like it? :-) When this
revolutionary tool of yours arrive that compiles Haskell to PIC
devices, I'm gonna be the first to use it.



No, you use it because you have to, there is very little choice. Which
is exactly my point.

I don't think it's unreasonable to expect that when nobody uses C for
desktop applications, games etc. anymore because there's a better
language available and widely supported, that some version of this
next mainstream language will make it onto embedded devices too.

The revolution (tm) won't come at the same time for all domains. C is
probably used/supported in embedded devices mostly because it's
popular for non-embedded devices (not because C is somehow uniquely
suited for embedded devices). So what happens when something else is
popular, when most industries have stopped using C and almost nobody
coming from university knows it very well or at all? Isn't it likely
that a lot of vendors will write compilers targeting embedded devices
for this new popular language?


Mmm... a garbage-collected language on a PIC with single-digit RAM 
capacity? That's going to be fun! :-D


OTOH, isn't somebody out there using Haskell to design logic? (As in, 
computer ICs.) I doubt you'll even run Haskell on a PIC, but you might 
well use it to *construct* a program that works on a PIC...


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


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Sebastian Sylvan

On 10/07/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Sebastian Sylvan wrote:
 That might eliminate the concurrency imperative (for a while!), but it
 doesn't adress the productivity point. My hypothesis is this: People
 don't like using unproductive tools, and if they don't have to, they
 won't.

 When the next mainstream language comes along to solve the
 concurrency problem (to some extent), it would seem highly likely that
 there will relatively soon be compilers for it for most embedded
 devices too, so why would you make your life miserable with C in that
 case (and cost your company X dollars due to inefficiency in the
 process)?

...because only C works on bizzare and unusual hardware?


By what magic is this the case? Hardware automatically supports C
without the efforts of compiler-writers?

We're talking 20 years down the line here, when someone can choose to
write a C compiler, or an X compiler (where X is the most popular
systems programming language of the time).

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Floating phi, round and even Fibonnaci numbers

2007-07-10 Thread Brian L. Troutwine
I'm rather new to Haskell and need, in typical newbie style,
a bit of help understanding the type system.

The Nth even Fibonacci number, EF(n) can be defined by the recursive
relation EF(0) = 2, EF(n) = [EF(n-1) * (phi**3)], where phi is the
golden ratio and [] is the nearest integer function. An infinite lazy
list of this sequence would be nice to have for my Project Euler, er,
project. Defining phi thusly,

 phi :: (Floating t) = t
 phi = (1+sqrt(5))/2

With phi in place, if I understood types properly (and if I understand
iterate correctly as I think), the lazy list should be a relatively
quick matter.

 even_fibs :: (Num t) = [t]
 even_fibs = iterate (\x - round(x * (phi**3))) 2

Dynamically typed even_fibs :: (Floating t, Integral t, RealFrac t) =
[t], assuming I pass -fno-monomorphism-restriction to ghci. That's not
at all the type I assumed even_fibs would take, as can be seen from
above. So, I went on a bit of sojourn. Having seen the sights of the
Haskell Report section 6.4, the marvels of the references cited in the
wiki's article on the monomorphism restriction and the Gentle
Introduction's chapter 10 I must say I'm rather more terribly confused
than when I started out, possibly.

Can someone explain where my type statements have gone wrong?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Sebastian Sylvan

On 10/07/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Sebastian Sylvan wrote:
 On 10/07/07, Alex Queiroz [EMAIL PROTECTED] wrote:
  So you think we use C because we like it? :-) When this
 revolutionary tool of yours arrive that compiles Haskell to PIC
 devices, I'm gonna be the first to use it.


 No, you use it because you have to, there is very little choice. Which
 is exactly my point.

 I don't think it's unreasonable to expect that when nobody uses C for
 desktop applications, games etc. anymore because there's a better
 language available and widely supported, that some version of this
 next mainstream language will make it onto embedded devices too.

 The revolution (tm) won't come at the same time for all domains. C is
 probably used/supported in embedded devices mostly because it's
 popular for non-embedded devices (not because C is somehow uniquely
 suited for embedded devices). So what happens when something else is
 popular, when most industries have stopped using C and almost nobody
 coming from university knows it very well or at all? Isn't it likely
 that a lot of vendors will write compilers targeting embedded devices
 for this new popular language?

Mmm... a garbage-collected language on a PIC with single-digit RAM
capacity? That's going to be fun! :-D

OTOH, isn't somebody out there using Haskell to design logic? (As in,
computer ICs.) I doubt you'll even run Haskell on a PIC, but you might
well use it to *construct* a program that works on a PIC...



Yeah, and 640K should be enough for everybody... Again, the original
statement was about 20 years down the line. Go back 20 years and
people would say similar things about C (comparing it to assembly).

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Jon Harrop
On Tuesday 10 July 2007 21:19:42 Andrew Coppin wrote:
 Hugh Perkins wrote:
  Yeah I agree with this.  C# totally rocks, but threading is an
  unsolved problem.

 I have repeatedly attempted to discover what C# actually is...

Take Java. Make it Windows only. Fix some mistakes. Tweak performance. Add a 
little functionality (e.g. operator overloading). That is C#.

Both are designed for GUI and web programming, so they don't fare well for 
massive concurrency, high-performance numerics or allocation-intensive 
algorithms (e.g. idiomatic functional programming).

 Hint: If you can get readable/maintainable Haskell to run on more than
 one core automatically, you're onto something pretty special. ;-)

If you're using a Unix, just fork the process and pass messages via a pipe.

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
The OCaml Journal
http://www.ffconsultancy.com/products/ocaml_journal/?h
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] In-place modification

2007-07-10 Thread Sebastian Sylvan

On 10/07/07, Jon Harrop [EMAIL PROTECTED] wrote:

On Tuesday 10 July 2007 21:19:42 Andrew Coppin wrote:
 Hugh Perkins wrote:
  Yeah I agree with this.  C# totally rocks, but threading is an
  unsolved problem.

 I have repeatedly attempted to discover what C# actually is...

Take Java. Make it Windows only. Fix some mistakes. Tweak performance. Add a
little functionality (e.g. operator overloading). That is C#.

Both are designed for GUI and web programming, so they don't fare well for
massive concurrency, high-performance numerics or allocation-intensive
algorithms (e.g. idiomatic functional programming).


C# 3.0 gets it a bit closer, though. I wonder what C# 4.0 will look
like, though I worry about the complexity of the language when they
keep tacking stuff on like that.


--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very freaky

2007-07-10 Thread Andrew Coppin

Jonathan Cast wrote:

On Tuesday 10 July 2007, Andrew Coppin wrote:
  

OK, so technically it's got nothing to do with Haskell itself, but...



Actually, it does
  


I rephrase: This isn't *specifically* unique to Haskell, as such.


Now, Wikipedia seems to be suggesting something really remarkable. The
text is very poorly worded and hard to comprehend,



Nothing is ever absolutely so --- except the incomprehensibility of 
Wikipedia's math articles.  They're still better than MathWorld, though.
  


Ah, MathWorld... If you want to look up a formula or identity, it's 
practically guaranteed to be there. If you want to *learn* stuff... 
forget it!



So is this all a huge coincidence? Or have I actually suceeded in
comprehending Wikipedia?



Yes, you have.  In the (pure, non-recursive) typed lambda calculus, there is 
an isomorphism between (intuitionistic) propositions and types, and between 
(constructive) proofs and terms, such that a term exists with a given type 
iff a (corresponding) (constructive) proof exists of the corresponding 
(intuitionistic) theorem.  This is called the Curry-Howard isomorphism, after 
Haskell Curry (he whom our language is named for), and whatever computer 
scientist independently re-discovered it due to not having figured out to 
read the type theory literature before doing type theoretic research.
  


...let us not even go into what constitutes intuitionistic 
propositions (hell, I can't even *pronounce* that!) or what a 
constructive proof is...


Once functional programming language designers realized that the 
generalization of this to the fragments of intuitionistic logic with logical 
connectives `and' (corresponds to products/record types) and `or' 
(corresponds to sums/union types) holds, as well, the prejudice that 
innovations in type systems should be driven by finding an isomorphism with 
some fragment of intuitionistic logic set in, which gave us existential types 
and rank-N types, btw.  So this is really good research to be doing.
  


On the one hand, it feels exciting to be around a programming language 
where there are deep theoretical discoveries and new design territories 
to be explored. (Compared to Haskell, the whole C / C++ / Java / 
JavaScript / Delphi / VisualBasic / Perl / Python thing seems so boring.)


On the other hand... WHAT THE HECK DOES ALL THAT TEXT *MEAN*?! _

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


Re: [Haskell-cafe] Floating phi, round and even Fibonnaci numbers

2007-07-10 Thread Tim Chevalier

On 7/10/07, Brian L. Troutwine [EMAIL PROTECTED] wrote:

I'm rather new to Haskell and need, in typical newbie style,
a bit of help understanding the type system.

The Nth even Fibonacci number, EF(n) can be defined by the recursive
relation EF(0) = 2, EF(n) = [EF(n-1) * (phi**3)], where phi is the
golden ratio and [] is the nearest integer function. An infinite lazy
list of this sequence would be nice to have for my Project Euler, er,
project. Defining phi thusly,

 phi :: (Floating t) = t
 phi = (1+sqrt(5))/2

With phi in place, if I understood types properly (and if I understand
iterate correctly as I think), the lazy list should be a relatively
quick matter.

 even_fibs :: (Num t) = [t]
 even_fibs = iterate (\x - round(x * (phi**3))) 2

Dynamically typed even_fibs :: (Floating t, Integral t, RealFrac t) =
[t], assuming I pass -fno-monomorphism-restriction to ghci. That's not
at all the type I assumed even_fibs would take, as can be seen from
above. So, I went on a bit of sojourn. Having seen the sights of the
Haskell Report section 6.4, the marvels of the references cited in the
wiki's article on the monomorphism restriction and the Gentle
Introduction's chapter 10 I must say I'm rather more terribly confused
than when I started out, possibly.


That was your first mistake :-) (As a beginner, anyway.)

Look at the type of round:
Prelude :t round
round :: forall a b. (RealFrac a, Integral b) = a - b

So the argument x in the lambda-expression being passed to iterate
must have a type that's an instance of RealFrac. It must also have a
type that's an instance of Integral, since the result of multiplying
it with phi gets passed into the next iteration. Finally, it has to
have a type that's an instance of Floating, since phi is declared as a
Floating. You can probably see the problem.

Cheers,
Tim

--
Tim Chevalier* catamorphism.org *Often in error, never in doubt
There's no money in poetry, but there's no poetry in money, either.
--Robert Graves
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] CGI test

2007-07-10 Thread Jim Burton



Andrew Coppin wrote:
 
 Greetings.
 
 Can somebody write a trivial (as in: small) program so I can test my CGI 
 stuff without having to actually install and configure Apache?
 
 [...]
 
You could adapt the TCP server from this tutorial -
http://sequence.complete.org/node/258 

Regards,
-- 
View this message in context: 
http://www.nabble.com/CGI-test-tf4058260.html#a11529701
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Floating phi, round and even Fibonnaci numbers

2007-07-10 Thread haskell

Brian L. Troutwine wrote:

phi :: (Floating t) = t
phi = (1+sqrt(5))/2




even_fibs :: (Num t) = [t]
even_fibs = iterate (\x - round(x * (phi**3))) 2


*Main :t iterate
iterate :: forall a. (a - a) - a - [a]
*Main :t round
round :: forall a b. (RealFrac a, Integral b) = a - b

So the 'x' in your anonymous lambda must be (a-a) and the type 'a' must be an 
integral.


You need to convert this Integral 'x' into something that can be used in the 
math (x * (phi**3)) which is where you need to insert fromIntegral:



even_fibs :: (Integral t) = [t]
even_fibs = iterate (\x - round(fromIntegral x * (phi**3))) 2



Which of course can be tested against


even_fibs_2 = filter even fibs
  where fibs = 1 : 1 : zipWith (+) (fibs) (tail fibs)


And the phi version fails at


head $ dropWhile (uncurry (==)) $ zip even_fibs even_fibs_2


Which is
(37889062373143904,37889062373143906)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Floating phi, round and even Fibonnaci numbers

2007-07-10 Thread haskell

But that also depended on phi defaulting to Double in even_fibs.

To be clearer:


even_fibs :: (Integral t) = [t]
even_fibs = iterate (\x - round(fromIntegral x * (dp**3))) 2
  where dp :: Double
dp = phi


The above is equivalent to the previous.

The below uses less precision:



even_fibs' :: (Integral t) = [t]
even_fibs' = iterate (\x - round(fromIntegral x * (dp**3))) 2
  where dp :: Float
dp = phi



So it fails earlier:


head $ dropWhile (uncurry (==)) $ zip even_fibs' even_fibs_2
(14930353,14930352)


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


Re: [Haskell-cafe] Very freaky

2007-07-10 Thread Neil Davies

I means that you can view programming as constructing witnesses to
proofs - programs becoming the (finite) steps that, when followed,
construct a proof.

Intuitionism only allows you to make statements that can be proved
directly - no Reductio ad absurdum only good, honest to goodness
constructive computational steps - sounds like programming (and
general engineering) to me.

Powerful when you grasp it - which is why I've spent the last 15 or 20
years considering myself as an intuitionistic semantic philosopher -
reasoning about the meaning of things by constructing their proofs -
great way of taking ideas, refining them into an axiomatic system then
going and making them work.

Take it from me - it is a good approach it generates exploitable ideas
that people fund that make people money!

Neil

On 10/07/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Jonathan Cast wrote:
 On Tuesday 10 July 2007, Andrew Coppin wrote:

 OK, so technically it's got nothing to do with Haskell itself, but...


 Actually, it does


I rephrase: This isn't *specifically* unique to Haskell, as such.

 Now, Wikipedia seems to be suggesting something really remarkable. The
 text is very poorly worded and hard to comprehend,


 Nothing is ever absolutely so --- except the incomprehensibility of
 Wikipedia's math articles.  They're still better than MathWorld, though.


Ah, MathWorld... If you want to look up a formula or identity, it's
practically guaranteed to be there. If you want to *learn* stuff...
forget it!

 So is this all a huge coincidence? Or have I actually suceeded in
 comprehending Wikipedia?


 Yes, you have.  In the (pure, non-recursive) typed lambda calculus, there is
 an isomorphism between (intuitionistic) propositions and types, and between
 (constructive) proofs and terms, such that a term exists with a given type
 iff a (corresponding) (constructive) proof exists of the corresponding
 (intuitionistic) theorem.  This is called the Curry-Howard isomorphism, after
 Haskell Curry (he whom our language is named for), and whatever computer
 scientist independently re-discovered it due to not having figured out to
 read the type theory literature before doing type theoretic research.


...let us not even go into what constitutes intuitionistic
propositions (hell, I can't even *pronounce* that!) or what a
constructive proof is...

 Once functional programming language designers realized that the
 generalization of this to the fragments of intuitionistic logic with logical
 connectives `and' (corresponds to products/record types) and `or'
 (corresponds to sums/union types) holds, as well, the prejudice that
 innovations in type systems should be driven by finding an isomorphism with
 some fragment of intuitionistic logic set in, which gave us existential types
 and rank-N types, btw.  So this is really good research to be doing.


On the one hand, it feels exciting to be around a programming language
where there are deep theoretical discoveries and new design territories
to be explored. (Compared to Haskell, the whole C / C++ / Java /
JavaScript / Delphi / VisualBasic / Perl / Python thing seems so boring.)

On the other hand... WHAT THE HECK DOES ALL THAT TEXT *MEAN*?! _

___
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] CGI test

2007-07-10 Thread Alec Berryman
Andrew Coppin on 2007-07-10 21:23:23 +0100:

 Can somebody write a trivial (as in: small) program so I can test my CGI 
 stuff without having to actually install and configure Apache?

The Haskell wiki (http://www.haskell.org/) lists several web servers; one
appears to fit your needs of being small and able to run CGI.  Look under
Applications and libraries to get started.

 Actually, might be a useful thing to have in a library somewhere.

The Haskell wiki also lists several HTTP libraries.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Floating phi, round and even Fibonnaci numbers

2007-07-10 Thread haskell

And using dynamic precision :

http://haskell.org/haskellwiki/Applications_and_libraries/Mathematics#Dynamic_precision

The ERA package (darcs get http://darcs.augustsson.net/Darcs/CReal/) one can do 
better...



import CReal

even_fibs'' :: (Integral t) = [t]
even_fibs'' = iterate (\x - round(fromIntegral x * (dp**3))) 2
  where dp :: CReal
dp = phi


even_fibs_2 = filter even fibs
  where fibs = 1 : 1 : zipWith (+) (fibs) (tail fibs)

z n = take n $ zipWith (\a b - (a==b,a)) even_fibs'' even_fibs_2

t z = not $ null $ filter fst $ z

main = let y = z 1000
   in putStr . unlines . map show $ y


This works quite well

(True,2)
(True,8)
(True,34)
(True,144)
(True,610)
(True,2584)
(True,10946)
(True,46368)

...snip...

(True,3987795824799770715342824788687062628452272409956636682999616408)
(True,16892574194241670428824570378554538679120491007541580961500624834)
(True,71558092601766452430641106302905217344934236440122960529002115744)

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


[Haskell-cafe] Re: In-place modification

2007-07-10 Thread Aaron Denney
On 2007-07-10, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 On 10/07/07, Andrew Coppin [EMAIL PROTECTED] wrote:
 Sebastian Sylvan wrote:
  On 10/07/07, Alex Queiroz [EMAIL PROTECTED] wrote:
   So you think we use C because we like it? :-) When this
  revolutionary tool of yours arrive that compiles Haskell to PIC
  devices, I'm gonna be the first to use it.
 
 
  No, you use it because you have to, there is very little choice. Which
  is exactly my point.
 
  I don't think it's unreasonable to expect that when nobody uses C for
  desktop applications, games etc. anymore because there's a better
  language available and widely supported, that some version of this
  next mainstream language will make it onto embedded devices too.
 
  The revolution (tm) won't come at the same time for all domains. C is
  probably used/supported in embedded devices mostly because it's
  popular for non-embedded devices (not because C is somehow uniquely
  suited for embedded devices). So what happens when something else is
  popular, when most industries have stopped using C and almost nobody
  coming from university knows it very well or at all? Isn't it likely
  that a lot of vendors will write compilers targeting embedded devices
  for this new popular language?

 Mmm... a garbage-collected language on a PIC with single-digit RAM
 capacity? That's going to be fun! :-D

 OTOH, isn't somebody out there using Haskell to design logic? (As in,
 computer ICs.) I doubt you'll even run Haskell on a PIC, but you might
 well use it to *construct* a program that works on a PIC...


 Yeah, and 640K should be enough for everybody... Again, the original
 statement was about 20 years down the line. Go back 20 years and
 people would say similar things about C (comparing it to assembly).

And assembly is still widely used.  Moore's law as applied to the
embedded domain has a lot of the transistors going to more, cheaper
devices, not bigger ones.

-- 
Aaron Denney
--

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


Re: [Haskell-cafe] Very freaky

2007-07-10 Thread Jim Burton


Andrew Coppin wrote:
 
 
 On the one hand, it feels exciting to be around a programming language 
 where there are deep theoretical discoveries and new design territories 
 to be explored. (Compared to Haskell, the whole C / C++ / Java / 
 JavaScript / Delphi / VisualBasic / Perl / Python thing seems so boring.)
 
 On the other hand... WHAT THE HECK DOES ALL THAT TEXT *MEAN*?! _
 
 
I agree, it's exciting to use Haskell because of its theoretical
underpinning and the sense of it as a lab for PL ideas. The cost of taking
part in that (even as an observer) is the background knowledge and common
vocabulary you need in order to make sense of a lot of the papers that you
may get referred to, presuming you start asking the kind of questions that
elicit answers like that. I don't think the amount of background knowledge
required is actually that big but if it's missing you will feel like you're
going one step forwards and two steps back. 

The Getting Started thread on Lambda the Ultimate is good  - maybe we need
a wikipage like that but of links to sources of the type theoretical
background to Haskell (is there one already? I see Research Papers, which
obviously has a different purpose). 

I don't know where the best place to start would be but, as I said in
another thread Andrew, TAPL is great. Re. Curry-Howard, have a look Simon
Thompson's book (online for free)
http://www.cs.kent.ac.uk/people/staff/sjt/TTFP/  . Not quick reads (by any
means!), but depending on your learning style, better value than asking ad
hoc questions and joining the dots via blog posts/wiki pages etc.

-- 
View this message in context: 
http://www.nabble.com/Very-freaky-tf4057907.html#a11530874
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Looking for final year project - using Haskell, or another functional language

2007-07-10 Thread Paul Johnson




On 7/10/07, *wp* [EMAIL PROTECTED] mailto:[EMAIL PROTECTED] 
wrote:


Hi all,


Does anybody know anyone who would have a task suitable for such a
project which would encompass the whole development life cycle
(maybe a sub-project?).




How about implementing AQMP (Advanced Queuing Message Protocol)?  A 
chunk of it can be generated directly from the XML specification, and 
the rest should be a reasonably sized project.  Also you can split the 
project into phases (e.g. client architecture, minimal server, extra 
bits of server), so even if you only get part way through you would have 
made a distinct contribution with some finished code to show for it.


http://www.amqp.org/

Paul.

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


Re: [Haskell-cafe] Re: In-place modification

2007-07-10 Thread Sebastian Sylvan

On 10/07/07, Aaron Denney [EMAIL PROTECTED] wrote:

On 2007-07-10, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 On 10/07/07, Andrew Coppin [EMAIL PROTECTED] wrote:
 Sebastian Sylvan wrote:
  On 10/07/07, Alex Queiroz [EMAIL PROTECTED] wrote:
   So you think we use C because we like it? :-) When this
  revolutionary tool of yours arrive that compiles Haskell to PIC
  devices, I'm gonna be the first to use it.
 
 
  No, you use it because you have to, there is very little choice. Which
  is exactly my point.
 
  I don't think it's unreasonable to expect that when nobody uses C for
  desktop applications, games etc. anymore because there's a better
  language available and widely supported, that some version of this
  next mainstream language will make it onto embedded devices too.
 
  The revolution (tm) won't come at the same time for all domains. C is
  probably used/supported in embedded devices mostly because it's
  popular for non-embedded devices (not because C is somehow uniquely
  suited for embedded devices). So what happens when something else is
  popular, when most industries have stopped using C and almost nobody
  coming from university knows it very well or at all? Isn't it likely
  that a lot of vendors will write compilers targeting embedded devices
  for this new popular language?

 Mmm... a garbage-collected language on a PIC with single-digit RAM
 capacity? That's going to be fun! :-D

 OTOH, isn't somebody out there using Haskell to design logic? (As in,
 computer ICs.) I doubt you'll even run Haskell on a PIC, but you might
 well use it to *construct* a program that works on a PIC...


 Yeah, and 640K should be enough for everybody... Again, the original
 statement was about 20 years down the line. Go back 20 years and
 people would say similar things about C (comparing it to assembly).

And assembly is still widely used.  Moore's law as applied to the
embedded domain has a lot of the transistors going to more, cheaper
devices, not bigger ones.


Depends on your definition of widely used. You'll always need some
low-level stuff at the bottom (e.g. for the page manager in an OS),
and if your device is nothing but the bottom, well then that's what
you get.
Doesn't mean that assembly isn't dead in the most reasonable sense
of the word for the purposes of a discussion like this (i.e. nobody
chooses to use assembly when they don't need to). And that's what I
predict will happen (and already has in very many domains) with C.

--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: In-place modification

2007-07-10 Thread Aaron Denney
On 2007-07-10, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 On 10/07/07, Andrew Coppin [EMAIL PROTECTED] wrote:
 Sebastian Sylvan wrote:
  That might eliminate the concurrency imperative (for a while!), but it
  doesn't adress the productivity point. My hypothesis is this: People
  don't like using unproductive tools, and if they don't have to, they
  won't.
 
  When the next mainstream language comes along to solve the
  concurrency problem (to some extent), it would seem highly likely that
  there will relatively soon be compilers for it for most embedded
  devices too, so why would you make your life miserable with C in that
  case (and cost your company X dollars due to inefficiency in the
  process)?

 ...because only C works on bizzare and unusual hardware?

 By what magic is this the case? Hardware automatically supports C
 without the efforts of compiler-writers?

No, of course not.  But the most popular architectures support C with
/much smaller/ efforts of compiler writers.

-- 
Aaron Denney
--

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


Re: [Haskell-cafe] Re: In-place modification

2007-07-10 Thread Sebastian Sylvan

On 10/07/07, Aaron Denney [EMAIL PROTECTED] wrote:

On 2007-07-10, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 On 10/07/07, Andrew Coppin [EMAIL PROTECTED] wrote:
 Sebastian Sylvan wrote:
  That might eliminate the concurrency imperative (for a while!), but it
  doesn't adress the productivity point. My hypothesis is this: People
  don't like using unproductive tools, and if they don't have to, they
  won't.
 
  When the next mainstream language comes along to solve the
  concurrency problem (to some extent), it would seem highly likely that
  there will relatively soon be compilers for it for most embedded
  devices too, so why would you make your life miserable with C in that
  case (and cost your company X dollars due to inefficiency in the
  process)?

 ...because only C works on bizzare and unusual hardware?

 By what magic is this the case? Hardware automatically supports C
 without the efforts of compiler-writers?

No, of course not.  But the most popular architectures support C with
/much smaller/ efforts of compiler writers.



Competition sorts that one out. If there's a clear alternative that's
let's say 10x more productive, then the cost of developing a compiler
(or a backend for an existing one) is offset by the benefits of being
able to offer a more productive programming environment for your
customers.

My point is that C isn't a magical language that is immune to
progress, and I would say it's likely that the main future competitor
to C in the embedded domain will eventually be [a version of] whatever
langauge wins out in the other domains (e.g. due to the many-core
stuff).


--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: In-place modification

2007-07-10 Thread Creighton Hogg

On 7/10/07, Aaron Denney [EMAIL PROTECTED] wrote:


On 2007-07-10, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 On 10/07/07, Andrew Coppin [EMAIL PROTECTED] wrote:
 Sebastian Sylvan wrote:
  That might eliminate the concurrency imperative (for a while!), but
it
  doesn't adress the productivity point. My hypothesis is this: People
  don't like using unproductive tools, and if they don't have to, they
  won't.
 
  When the next mainstream language comes along to solve the
  concurrency problem (to some extent), it would seem highly likely
that
  there will relatively soon be compilers for it for most embedded
  devices too, so why would you make your life miserable with C in that
  case (and cost your company X dollars due to inefficiency in the
  process)?

 ...because only C works on bizzare and unusual hardware?

 By what magic is this the case? Hardware automatically supports C
 without the efforts of compiler-writers?

No, of course not.  But the most popular architectures support C with
/much smaller/ efforts of compiler writers.



Now is this just because of the relative simplicity of C, because of a
larger amount of collective experience in writing C compilers, or something
else entirely
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function unique

2007-07-10 Thread Dan Weston

Alexteslin wrote:
 I'v got it - it produces the right output.
 Thank you.

Now that you've done the exercise, the fun starts! What assumptions did 
you build in to your solution?


1) You just need uniqueness, so counting the number of copies is not 
only overkill, but requires you to go through the entire list to count them.


2) The list might be infinite, and your function should work if you make 
only want to use the first part of it, so the following should return 
[1,2,3,4,5] in a finite amount of time:


take 5 (unique [1..])

Your algorithm fails both of these. Consider a *lazy* approach:

1) Keep the head of the list
2) Then filter the tail, keeping only elements different from the head
3) Then put the two together

Don't worry in step #2 about having an infinite number of list elements 
to be filtered out of the list. Think of it like asking a lazy child to 
clean the house. They're only going to do it just before mom gets home 
(who knows, with any luck she'll be in a car crash and forget about 
having asked you to clean!)


This works for infinite lists, and puts off the work until you actually 
need the elements.


I won't cheat you out of the fun, but here's the solution to a *very* 
similar problem using the Sieve of Eratosthenes to find prime numbers:


isNotDivisor divisor dividend = dividend `rem` divisor /= 0

keepOnlyLowestMultiple (x:xs) =
  x : keepOnlyLowestMultiple (filter (isNotDivisor x) xs)

primes = keepOnlyLowestMultiple [2..]

Dan


Brent Yorgey wrote:

The problem with your second implementation is that elements which occur
more than once will eventually be included, when the part of the list
remaining only has one copy. For example:

unique2 [1,1,2,4,1]
= unique2 [1,2,4,1]
= unique2 [2,4,1]
= 2 : unique2 [4,1]
= 2 : 4 : unique2 [1]
= 2 : 4 : 1 : unique2 []   -- only a single 1 left, so it gets mistakenly
included
= [2,4,1]

When you determine that a certain number should not be included in the
output, you need to delete all remaining occurrences of it from the list,
so
it won't get included later.

unique2 (x:xs)
|elemNum2 x xs == 1 = x:unique2 xs
|otherwise = unique2 (deleteElt x xs)

I'll let you figure out how to implement the deleteElt function.

hope this is helpful!
-Brent

On 7/10/07, Alexteslin [EMAIL PROTECTED] wrote:


Hi, i am a beginner to Haskell and i have a beginner's question to ask.

An exercise asks to define function unique :: [Int] - [Int], which
outputs
a list with only elements that are unique to the input list (that appears
no
more than once).  I defined a function with list comprehension which
works
but trying to implement with pattern matching and primitive recursion
with
lists and doesn't work.

unique :: [Int] - [Int]
unique xs = [x | x - xs, elemNum2 x xs == 1]


elemNum2 :: Int - [Int] - Int
elemNum2 el xs = length [x| x - xs, x == el]

//This doesn't work, I know because the list shrinks and produces wrong
result but can not get a right //thinking

unique2 :: [Int] - [Int]
unique2 [] = []
unique2 (x:xs)
|elemNum2 x xs == 1 = x:unique2 xs
|otherwise = unique2 xs


Any help to a right direction would be very appreciated, thanks.
--
View this message in context:
http://www.nabble.com/function-unique-tf4058328.html#a11528933
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
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







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


  1   2   >