Re: [Haskell-cafe] using an external application

2007-11-02 Thread Stuart Cook
On 11/2/07, Petr Hoffmann [EMAIL PROTECTED] wrote:
 import System.Cmd
 main = do
   System.Cmd.system echo hello output.txt -- use the external
 application to create an output file
   o1 - readFile output.txt
   System.Cmd.system echo bye output.txt -- the second call to
 the external application
   o2 - readFile output.txt
   putStr o1 -- hello expected, but bye printed
   return 0

 Can you please give me some hint to solve this problem?
 I'm a beginning haskell developer and I'm still a bit confused
 by the IO monad.

This looks like yet another case of the lazy-I/O goblins.

The readFile function uses evil magic to avoid actually performing
any I/O until the contents are actually used.  In your case, I suspect
that by the time o1 is used -- i.e. in the putStr call -- the file
contents have already changed, so the lazy I/O reads the new contents
without complaining.

The solution would be to use a version of readFile that works in a
stricter way, by reading the file when it's told to, but I don't have
an implementation handy.


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


Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Ketil Malde
Sebastian Sylvan [EMAIL PROTECTED] writes:

[LOC vs gz as a program complexity metric]

 Obviously no simple measure is going to satisfy everyone, but I think the
 gzip measure is more even handed across a range of languages.  
 It probably more closely aproximates the amount of mental effort [..]

I'm not sure I follow that reasoning?

At any rate, I think the ICFP contest is much better as a measure of
productivity. But, just like for performance, LOC for the shootout can
be used as a micro-benchmark. 

 Personally I think syntactic noise is highly distracting, and semantic
 noise is even worse!

This is important - productivity doesn't depend so much on the actual
typing, but the ease of refactoring, identifying and fixing bugs, i.e
*reading* code.

Verbosity means noise, and also lower information content in a
screenful of code.

I think there were some (Erlang?) papers where they showed a
correlation between program size (in LOC), time of development, and
possibly number of bugs?) - regardless of language.

 Token count would be good, but then we'd need a parser for
 each language, which is quite a bit of work to do...

Whatever you do, it'll be an approximation, so why not 'wc -w'?

With 'wc -c' for J etc where programs can be written as spaceless
sequences of symbols.  Or just average chars, words and lines?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] using an external application

2007-11-02 Thread Bas van Dijk
On 11/2/07, Petr Hoffmann [EMAIL PROTECTED] wrote:
 I'm solving the following problem - I need to use an external
 application - give it the input data and receive its output.

Check out: The HSH library:

HSH is designed to let you mix and match shell expressions with
Haskell programs. With HSH, it is possible to easily run shell
commands, capture their output or provide their input, and pipe them
to and from other shell commands and arbitrary Haskell functions at
will.

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/HSH-1.2.4

regards,

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


Re: [Haskell-cafe] using an external application

2007-11-02 Thread Henning Thielemann

On Fri, 2 Nov 2007, Petr Hoffmann wrote:

 Hi,

 I'm solving the following problem - I need to use an external
 application - give it the input data and receive its output.
 However, when multiple calls are made, the results are not
 as expected. The simplified version of the problem is given
 below:

 import System.Cmd
 main = do
   System.Cmd.system echo hello output.txt -- use the external
 application to create an output file
   o1 - readFile output.txt
   System.Cmd.system echo bye output.txt -- the second call to
 the external application
   o2 - readFile output.txt
   putStr o1 -- hello expected, but bye printed
   return 0

You fell into the trap, that 'readFile' works lazily, that is, data is
only read when needed. If o1 is not completely evalutated until the second
write to output.txt, it will not be read correctly from the disk.
 I think it was not a good choice to make the lazy version of 'readFile'
the default. I think it would have been better to provide a strict
'readFile' and another 'readFileLazy' with warnings in the documentation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Sebastian Sylvan
On 02/11/2007, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 Hello Sebastian,

 Thursday, November 1, 2007, 9:58:45 PM, you wrote:

  the ideal. Token count would be good, but then we'd need a parser for
  each language, which is quite a bit of work to do...

 i think that wc (word count) would be good enough approximation


Yes, as long as you police abuse ( eg
if(somevar)somfunccall(foo,bar,baz)shouldn't be treated as a single
word)).

-- 
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: Semantics of uniqueness types for IO (Was: Why can't Haskell be faster?)

2007-11-02 Thread Brandon S. Allbery KF8NH


On Nov 2, 2007, at 6:35 , apfelmus wrote:

during function evaluation. Then, we'd need a purity lemma that  
states that any function not involving the type *World as in- and  
output is indeed pure, which may be a bit tricky to prove in the  
presence of higher-order functions and polymorphism. I mean, the  
function arrows are tagged for side effects in a strange way,  
namely by looking like *World - ... - (*World, ...).


I don't quite see that; the Clean way looks rather suspiciously like  
my unwrapped I/O in GHC example from a couple weeks ago, so I have  
trouble seeing where any difficulty involving functions not using  
*World / RealWorld# creeps in.


I will grant that hiding *World / RealWorld# inside IO is cleaner  
from a practical standpoint, though.  Just not from a semantic one.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] using an external application

2007-11-02 Thread Andrew Butterfield



On 11/2/07, Petr Hoffmann [EMAIL PROTECTED] wrote:
 

import System.Cmd
main = do
  System.Cmd.system echo hello output.txt -- use the external
application to create an output file
  o1 - readFile output.txt
  System.Cmd.system echo bye output.txt -- the second call to
the external application
  o2 - readFile output.txt
  putStr o1 -- hello expected, but bye printed
  return 0

Can you please give me some hint to solve this problem?
I'm a beginning haskell developer and I'm still a bit confused
by the IO monad.



  
I'm puzzled - when I run this on GHCi (v6.4, Windows XP) I get the 
following outcome


*Mainmain
The process cannot access the file because it is being used by another 
process.

hello
*Main

This is certainly the behaviour I would expect - seeing bye being 
printed seems to me to be an error

and may even constitute a violation of referential transparency.

What implementation  of GHC are you using ?

This looks like yet another case of the lazy-I/O goblins.
  

Yes, but not quite what everyone has being addressing


--

Andrew Butterfield Tel: +353-1-896-2517 Fax: +353-1-677-2204
Foundations and Methods Research Group Director.
Course Director, B.A. (Mod.) in CS and ICT degrees, Year 4.
Department of Computer Science, Room F.13, O'Reilly Institute,
Trinity College, University of Dublin, Ireland.
   http://www.cs.tcd.ie/Andrew.Butterfield/


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


Re: [Haskell-cafe] Re: Semantics of uniqueness types for IO (Was: Why can't Haskell be faster?)

2007-11-02 Thread Jonathan Cast

On Fri, 2007-11-02 at 08:35 -0400, Brandon S. Allbery KF8NH wrote:
 On Nov 2, 2007, at 6:35 , apfelmus wrote:
 
  during function evaluation. Then, we'd need a purity lemma that  
  states that any function not involving the type *World as in- and  
  output is indeed pure, which may be a bit tricky to prove in the  
  presence of higher-order functions and polymorphism. I mean, the  
  function arrows are tagged for side effects in a strange way,  
  namely by looking like *World - ... - (*World, ...).
 
 I don't quite see that; the Clean way looks rather suspiciously like  
 my unwrapped I/O in GHC example from a couple weeks ago, so I have  
 trouble seeing where any difficulty involving functions not using  
 *World / RealWorld# creeps in.
 
 I will grant that hiding *World / RealWorld# inside IO is cleaner  
 from a practical standpoint, though.  Just not from a semantic one.

On the contrary.  GHC's IO newtype isn't an implementation of IO in
Haskell at all.  It's an implementation in a language that has a
Haskell-compatible subset, but that also has semantically bad constructs
like unsafePerformIO and unsafeInterleaveIO that give side effects to
operations of pure, non-RealWorld#-involving types.  Clean's type system
is specified in a way that eliminates both functions from the language,
which recovers purity.  But proving that is harder than I'd like to
attempt.

jcc


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


[Haskell-cafe] Re: Semantics of uniqueness types for IO (Was: Why can't Haskell be faster?)

2007-11-02 Thread apfelmus

Brandon S. Allbery KF8NH wrote:

apfelmus wrote:
during function evaluation. Then, we'd need a purity lemma that 
states that any function not involving the type *World as in- and 
output is indeed pure, which may be a bit tricky to prove in the 
presence of higher-order functions and polymorphism. I mean, the 
function arrows are tagged for side effects in a strange way, namely 
by looking like *World - ... - (*World, ...).


I don't quite see that; the Clean way looks rather suspiciously like my 
unwrapped I/O in GHC example from a couple weeks ago, so I have 
trouble seeing where any difficulty involving functions not using *World 
/ RealWorld# creeps in.


I will grant that hiding *World / RealWorld# inside IO is cleaner from a 
practical standpoint, though.  Just not from a semantic one.


What do you mean?

I mean, in Clean, we may ask the following question: are all functions 
of type say


  forall a . Either (a - *World - a) String - [*World]

or

  Either (forall a . a - *World - a) String - Maybe *World

pure? In Haskell, the answer to any such question is unconditionally 
yes (unless you're hacking with unsafePerformIO and GHC internals like 
RealWorld# of course) even with plenty of appearances of the  IO  type 
constructor. But in Clean, functions may perform side effects, that's 
the only way to explain why the examples  loop  and  loop'  aren't the same.



Regards,
apfelmus

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


Re: [Haskell-cafe] using an external application

2007-11-02 Thread Jules Bean

Can you please give me some hint to solve this problem?
I'm a beginning haskell developer and I'm still a bit confused
by the IO monad.


Other people have explained to the OP why unsafe lazy IO is breaking his 
code.


Yet another piece of evidence, in my opinion, that 
unsafe-lazy-by-default is the wrong basic API. Provide that API as an 
option, sure. But as a default? Not IMO.


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


Re: [Haskell-cafe] Re: Semantics of uniqueness types for IO (Was: Why can't Haskell be faster?)

2007-11-02 Thread Brandon S. Allbery KF8NH


On Nov 2, 2007, at 11:51 , Jonathan Cast wrote:


I will grant that hiding *World / RealWorld# inside IO is cleaner
from a practical standpoint, though.  Just not from a semantic one.


On the contrary.  GHC's IO newtype isn't an implementation of IO in
Haskell at all.  It's an implementation in a language that has a
Haskell-compatible subset, but that also has semantically bad  
constructs


Differing viewpoints, I guess; from my angle, Clean's uniqueness  
constraint looks like a hack hidden in the compiler.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] using an external application

2007-11-02 Thread Ketil Malde
Andrew Butterfield [EMAIL PROTECTED] writes:

 I'm puzzled - when I run this on GHCi (v6.4, Windows XP) I get the
 following outcome^^

 The process cannot access the file because it is being used by another
 process.

Isnt' this a difference between Windows and Unix?  Windows typically
locks files, Unix typically does not.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] using an external application

2007-11-02 Thread Bulat Ziganshin
Hello Petr,

Friday, November 2, 2007, 11:17:23 AM, you wrote:

   o1 - readFile output.txt

add return $! length o1 here to evaluate whole list

   System.Cmd.system echo bye output.txt -- the second call to



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] using an external application

2007-11-02 Thread jerzy . karczmarczuk
Petr Hoffmann writes: 


I'm solving the following problem - I need to use an external
application - give it the input data and receive its output.
However, when multiple calls are made, the results are not
as expected. The simplified version of the problem is given
below:


 System.Cmd.system echo hello output.txt -- use the external  

...
 System.Cmd.system echo bye output.txt -- the second call to  
the external application

 o2 - readFile output.txt
 putStr o1 -- hello expected, but bye printed




Can you please give me some hint to solve this problem?
I'm a beginning haskell developer and I'm still a bit confused
by the IO monad.


I have the impression that your problem has nothing to do do
with Haskell, you just rewrite your file, instead of appending to it.
But perhaps I didn't look correctly... 

Jerzy Karczmarczuk 



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


Re[2]: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Bulat Ziganshin
Hello Sebastian,

Thursday, November 1, 2007, 9:58:45 PM, you wrote:

 the ideal. Token count would be good, but then we'd need a parser for
 each language, which is quite a bit of work to do...

i think that wc (word count) would be good enough approximation

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] using an external application

2007-11-02 Thread Petr Hoffmann

Hi,

I'm solving the following problem - I need to use an external
application - give it the input data and receive its output.
However, when multiple calls are made, the results are not
as expected. The simplified version of the problem is given
below:

import System.Cmd
main = do
 System.Cmd.system echo hello output.txt -- use the external  
application to create an output file

 o1 - readFile output.txt
 System.Cmd.system echo bye output.txt -- the second call to  
the external application

 o2 - readFile output.txt
 putStr o1 -- hello expected, but bye printed
 return 0

Can you please give me some hint to solve this problem?
I'm a beginning haskell developer and I'm still a bit confused
by the IO monad.

Thank you in advance.

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


Re: [Haskell-cafe] Slightly off-topic

2007-11-02 Thread Bas van Dijk
On 11/1/07, PR Stanley [EMAIL PROTECTED] wrote:
 If anyone knows anything about the rules of proof by deduction and
 quantifiers I'd be grateful for some assistance.

I'm currently doing a course on Type Theory which includes proving by
natural deduction. See, among other things, the course notes on:
http://www.cs.ru.nl/~freek/courses/tt-2007

regards,

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


Re: [Haskell-cafe] space leak?

2007-11-02 Thread Justin Bailey
Massimiliano,

I had to update your code for it to compile (removed sequence from
testpdf'. However, I don't see any significant difference in the
memory profile of either testpdf or testpdf'.

Not sure how you are watching the memory usage, but if you didn't know
the option +RTS -sstderr will print out useful memory statistics
when you run your program. E.g.:

   pdf_test.exe +RTS -sstderr

gives:

  2,157,524,764 bytes allocated in the heap
  246,516,688 bytes copied during GC (scavenged)
  6,086,688 bytes copied during GC (not scavenged)
  45,107,704 bytes maximum residency (8 sample(s))
   4086 collections in generation 0 (  0.61s)
  8 collections in generation 1 (  0.67s)
129 Mb total memory in use
  INIT  time0.02s  (  0.00s elapsed)
  MUT   time5.83s  (  7.48s elapsed)
  GCtime1.28s  (  1.45s elapsed)
  RPtime0.00s  (  0.00s elapsed)
  PROF  time0.00s  (  0.00s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time7.13s  (  8.94s elapsed)
  %GC time  18.0%  (16.3% elapsed)
  Alloc rate369,202,098 bytes per MUT second
  Productivity  81.8% of total user, 65.2% of total elapsed

Above you can see 45 MB was the max amount of memory ever in use - and
according to the heap profiling I did it's about constant. I saw the
same results when using testpdf'.

A few tricks I've learned to reduce space usage:

  * Use strict returns ( return $! ...)
  * foldl' over foldr unless you have to use foldr.
  * Profile, profile, profile - understand who is hanging on to the
memory (+RTS -hc) and how it's being used (+RTS -hb).
  * Use +RTS -p to understand who's doing all the allocations and
where your time is being spent.
  * Approach profiling like a science experiment - make one change,
observe if anything is different, rollback and make another change -
observer the change. Keep notes!

Good luck!

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


Re: [Haskell-cafe] Re: Semantics of uniqueness types for IO (Was: Why can't Haskell be faster?)

2007-11-02 Thread Jeff Polakow
Hello,

Just a bit of minor academic nitpicking...
 
 Yeah.  After all, the uniqueness constraint has a theory with an
 excellent pedigree (IIUC linear logic, whose proof theory Clean uses
 here, goes back at least to the 60s, and Wadler proposed linear types
 for IO before anybody had heard of monads). 

Linear logic/typing does not quite capture uniqueness types since a term 
with a unique type can always be copied to become non-unique, but a linear 
type cannot become unrestricted. 

As a historical note, the first paper on linear logic was published by 
Girard in 1987; but the purely linear core of linear logic has 
(non-commutative) antecedents in a system introduced by Lambek in a 1958 
paper titled The Mathematics of Sentence Structure.

-Jeff


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Compile-time evaluation

2007-11-02 Thread Nicholas Messenger
{-# OPTIONS_GHC -fglasgow-exts -fno-monomorphism-restriction #-}

-- Many people ask if GHC will evaluate toplevel constants at compile
-- time, you know, since Haskell is pure it'd be great if those
-- computations could be done once and not use up cycles during
-- runtime.  Not an entirely bad idea, I think.
-- 
-- So I set about allowing just that: for arbitrary expressions to be
-- evaluated, and the expanded expression spliced into client code.
-- 
-- If you had some data in a file just out of convenience, you could say:
--  yourData = $(compileTimeIO $ parseFile $ readFile data.txt)
-- 
-- Or if you had an expensive computation that you want done at compile:
--  result = $(compileTimeEval $ expensiveComputation)
-- 
-- I would appreciate comments.  I wrote this completely blind with just
-- the TH and Generics haddocks, so if I'm doing something tremendously
-- stupid that can be improved, let me know. :)  Especially if you can
-- think of a less awkward way to go from Generics' data to TH
-- expressions than using 'showConstr'...
-- 
-- I wrote this with 6.6.1, in case there's any incompatibilities.  Copy/
-- paste this post into CompileTime.hs, load into ghci, :set -fth, and
-- futz around with the splices.
-- 
-- -- Nicholas Messenger (nmessenger at gmail.com, omnId on #haskell)

module CompileTime(compileTimeEval, compileTimeIO) where

import Data.Generics
import Language.Haskell.TH
import Control.Monad
import Data.Tree
import Data.Ratio

-- Expands a datum into an expression tree to be spliced into
-- client code.
compileTimeEval :: Data a = a - ExpQ
compileTimeEval = return . toExp

-- Runs the IO action and splices in the evaluated result datum.
compileTimeIO :: Data a = IO a - ExpQ
compileTimeIO = liftM toExp . runIO

-- Does the work. :)  toTree gets us a tree of constructors, so
-- we mostly just have to fold the tree with AppE, except for
-- TH's bizarre TupE.
toExp :: Data d = d - Exp
toExp = applyAll . toTree
 where
  applyAll (Node k args)
| isTuple k = TupE (map applyAll args)
| otherwise = foldl AppE k (map applyAll args)

  isTuple (ConE n) = all (==',') (nameBase n)
  isTuple _= False

-- Synonym to shorten the definition of exp below
type Ex a = a - Exp

-- Turns some datum into a tree of TH expressions representing
-- that datum.  The Exp at each node represents the constructor,
-- the subtrees are its arguments.
toTree :: Data d = d - Tree Exp
toTree x = Node (exp x) (gmapQ toTree x)
 where
  -- The various ways to turn a (Data d = d) into an
  -- Exp representing its constructor.
  any  = ConE . mkName . deparen . showConstr . toConstr
  char = LitE . CharL
  int  = sigged $ LitE . IntegerL . toInteger
  rat  = sigged $ LitE . RationalL . toRational
  sigged f x = SigE (f x) (ConT . mkName . show $ typeOf x)

  -- The above functions combined together for different types.
  -- This is what gives the constructor Exp at each Node.  There
  -- are definitely more types to cover that 'any' gets wrong...
  exp = any `extQ` (int::Ex Int)`extQ` (int::Ex Integer)
`extQ` char `extQ` (rat::Ex Float)
`extQ` (rat::Ex Double) `extQ` (rat::Ex Rational)

  -- Generics' showConstr puts parens around infix
  -- constructors.  TH's ConE doesn't like 'em.
  deparen s = (if last s == ')' then init else id) .
  (if head s == '(' then tail else id) $ s
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] using an external application

2007-11-02 Thread Felipe Lessa
On 11/2/07, Stuart Cook [EMAIL PROTECTED] wrote:
 The solution would be to use a version of readFile that works in a
 stricter way, by reading the file when it's told to, but I don't have
 an implementation handy.

I guess this does the job:

 readFile' fp = do
   contents - readFile fp
   let ret (x:xs) = x `seq` ret xs
   ret [] = return contents
   ret contents

Maybe the x `seq` part isn't necessary at all.

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


Re: [Haskell-cafe] using an external application

2007-11-02 Thread Henning Thielemann

On Fri, 2 Nov 2007, Felipe Lessa wrote:

 On 11/2/07, Stuart Cook [EMAIL PROTECTED] wrote:
  The solution would be to use a version of readFile that works in a
  stricter way, by reading the file when it's told to, but I don't have
  an implementation handy.

 I guess this does the job:

  readFile' fp = do
contents - readFile fp
let ret (x:xs) = x `seq` ret xs
ret [] = return contents
ret contents

 Maybe the x `seq` part isn't necessary at all.

Awful. It reminds me on MatLab where the developers have implemented many
automatisms which do arbitrary clever things in every corner case, but
nothing consistent, because they thought programmers want it that way.
Then the programmers must write wrappers in order to get functions with
consistent behaviour around the fully automated functions.

The unlazying procedure looks much like the lazying one, and I wonder
whether it would be a good idea to eventually add readFileStrict,
getContentStrict and hGetContentStrict to the standard library.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] space leak?

2007-11-02 Thread Massimiliano Gubinelli
 ( these two lines are just to fool the gmane post algorithm which 
   complains for top-posting)


Hi,
 i'm learning Haskell and trying to use the HPDF 1.2 library I've come
 across some large memory  consumption for which I do not understand
 the origin. I've tried heap profiling but without much  success.
This is my code 


 module Main where

 import Control.Monad.State
 import Graphics.PDF 

 data Opcodes = Rect | Ship  deriving (Show)

 doPage (Rect:ops) = do
  stroke $! Rectangle 10.0 10.0  10.0 10.0
  doPage ops   

 doPage l = return l

 doOps [] = return ()

 doOps (Ship:ops) = {-# SCC OPSHIP #-}  do  
 p - addPage Nothing
 ops' - drawWithPage p $! do 
   strokeColor red
   applyMatrix $ (translate 72.0 72.0)
   doPage ops  
 doOps ops'

 doOps (op:_) = error (unexpected  ++ show op)

 testpdf =  do
let ops = concat $ replicate 100 (Ship : (replicate 1000 Rect )) 
pageRect = PDFRect 0 0 
   (floor $ 21.0/2.54*72.0) (floor $ 29.7/2.54*72.0)
runPdf test1.pdf (standardDocInfo { author=toPDFString mgubi, 
  compressed = False}) 
pageRect $ doOps ops


 testpdf' = do  
let pageRect = PDFRect 0 0 
   (floor $ 21.0/2.54*72.0) (floor $ 29.7/2.54*72.0)
runPdf full.pdf (standardDocInfo { author=toPDFString mgubi, 
 compressed = False}) 
 pageRect $ sequence_ $ foldM f [] $ replicate 100 $ 
 (\p - sequence_ $ replicate 1000 $ 
   drawWithPage p $ stroke $ 
Rectangle 0.0 0.0 10.0 10.0)
 where f ps acts = do
 p - addPage Nothing
 acts p
 return $ p:ps

 main = testpdf


now, if I run testpdf' then memory profile is very low and everything
is as expected while if I run testpdf  then the profile grows up to
80MB and more. This is the stripped down version of the original
program  (which is a DVI interpreter) so there I will have also some
StateT and more complicated opcodes. I would  like to know what is
wrong with the above code. Could someone help me? 

thanks,

Massimiliano Gubinelli


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


[Haskell-cafe] Re: Semantics of uniqueness types for IO (Was: Why can't Haskell be faster?)

2007-11-02 Thread apfelmus

Paul Hudak wrote:

  loop, loop' :: *World - ((),*World)

  loop  w = loop w
  loop' w = let (_,w') = print x w in loop' w'

both have denotation _|_ but are clearly different in terms of side effects.


   One can certainly use an operational semantics such as bisimulation, 
but you don't have to abandon denotational semantics.  The trick is to 
make output part of the final answer.  For a conventional imperative 
language one could define, for example, a (lifted, recursive) domain:


Answer = Terminate + (String x Answer)

and then define a semantic function meaning, say, such that:

meaning loop = _|_
meaning loop' = x, x, ... 

In other words, loop denotes bottom, whereas loop' denotes the infinite 
sequence of xs.  There would typically also be a symbol to denote 
proper termination, perhaps .


A good read on this stuff is Reynolds book Theories of Programming 
Languages, where domain constructions such as the above are called 
resumptions, and can be made to include input as well.


In the case of Clean, programs take as input a World and generate a 
World as output.  One of the components of that World would presumably 
be standard output, and that component's value would be _|_ in the 
case of loop, and x, x, ...  in the case of loop'.  Another part 
of the World might be a file system, a printer, a missile firing, and so 
on.  Presumably loop and loop' would not affect those parts of the World.


Ah, so the denotational semantics would be a bit like good old 
stream-based IO.


However, we have to change the semantics of  - , there's no way to put 
the side effects in *World only. I mean, the problem of both loop and 
loop' is that they never return any world at all, the side effects occur 
during function evaluation. Then, we'd need a purity lemma that states 
that any function not involving the type *World as in- and output is 
indeed pure, which may be a bit tricky to prove in the presence of 
higher-order functions and polymorphism. I mean, the function arrows are 
tagged for side effects in a strange way, namely by looking like 
*World - ... - (*World, ...).


In contrast, we can see  IO a  as an abstract (co-)data type subject to 
some straightforward operational semantics, no need to mess with the 
pure  - . So, in a sense, the Haskell way is cleaner than the Clean way ;)



Regards,
apfelmus

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


Re: [Haskell-cafe] Compile-time evaluation

2007-11-02 Thread Robin Green
On Fri, 2 Nov 2007 05:11:53 -0500
Nicholas Messenger [EMAIL PROTECTED] wrote:

 -- Many people ask if GHC will evaluate toplevel constants at compile
 -- time, you know, since Haskell is pure it'd be great if those
 -- computations could be done once and not use up cycles during
 -- runtime.  Not an entirely bad idea, I think.

I implemented the same idea. First a note about nomenclature: since
there is a Template Haskell class for the concept of translating actual
values into TH representations of those values called Lift, I call that
lifting; I also call evaluating and storing top-level constants at
compile time baking them into the executable.

From glancing at your code, my approach has two main differences
(apart from the fact that I didn't implement support for all of the
types that you did):

1. A generic lifter using Data.Generics does not work for certain
types, like IntSet. So I implemented the Template Haskell class Lift
for each of my own data types that I wanted to use in lifting, and
where it would work, called my generic lifter function, otherwise
lifted it more manually (as shown below).

2. I used synthesise instead of gmapQ, and did not use an intermediate
Tree data structure.

Here is the module which does most of the work. (You will not be able to
compile this as-is, obviously, because I have not published the rest of
my code yet.)

{-# OPTIONS_GHC -fglasgow-exts -fallow-overlapping-instances
-fallow-undecidable-instances -XTemplateHaskell #-}

module Language.Coq.Syntax.AbstractionBaking where

import Data.Generics.Basics (ConstrRep(..), constrRep, Data, toConstr,
Typeable)
import Data.Generics.Schemes (synthesize)
import Data.List (foldl')
import Data.IntSet (IntSet)
import qualified Data.IntSet as IntSet (fromList, toList)
import Data.Set (Set)
import qualified Data.Set as Set (fromList, toList)
import Language.Haskell.TH.Lib (appE, charL, conE, ExpQ, infixE,
integerL, litE)
import Language.Haskell.TH.Syntax (Lift(..), mkName)
import System.FilePath ((/))

import Data.DList (DList)
import Data.ListLike (fromList, ListLike, toList)

import Language.Coq.Parser (CoqParserState(..))
import Language.Coq.Syntax.Abstract (CoqState(..), Sentence, Term)
import Language.Coq.Syntax.Concrete (NotationRec(..))
import Language.Coq.Syntax.ParseSpec

lifter :: Data d = d - ExpQ
lifter = head . synthesize [] (++) combiner
where
  combiner x args = [case rep of
   IntConstr i - litE $ integerL i
   AlgConstr _ - algebraic (show constr) args
   StringConstr (h:_) - litE $ charL h
   _ - fail $ Unimplemented constrRep:  ++
show rep]
  where constr = toConstr x
rep = constrRep constr
algebraic (:) = cons
algebraic name = foldl' appE $ conE $ mkName name
cons [] = [e| (:) |]
cons [left] = infixE (Just left) (cons []) Nothing
cons [left, right] = infixE (Just left) (cons []) $
Just right

instance Lift NotationRec where
lift (NotationRec w x y z)
= appE (appE (appE (appE [| NotationRec |] $ lift w) $ lift x)
$ lift y) $ lift z

instance Lift ParseSpecTok where
lift = lifter

instance Lift Associativity where
lift = lifter

instance Lift Sentence where
lift = lifter

instance Lift Term where
lift = lifter

instance Lift CoqState where
lift (CoqState x y) = appE (appE [| CoqState |] $ lift x) $ lift y

instance Lift CoqParserState where
lift (CoqParserState x y z) = appE (appE (appE [| CoqParserState |]
$ lift x) $ lift y) $ lift z

instance (Lift a, ListLike full a) = Lift full where
lift = appE [| fromList |] . lift . toList

instance Lift IntSet where
lift = appE [| IntSet.fromList |] . lift . IntSet.toList

instance Lift a = Lift (Set a) where
lift = appE [| Set.fromList |] . lift . Set.toList

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


Re: [Haskell-cafe] using an external application

2007-11-02 Thread Stuart Cook
On 11/2/07, Andrew Butterfield [EMAIL PROTECTED] wrote:
 I'm puzzled - when I run this on GHCi (v6.4, Windows XP) I get the
 following outcome

 *Mainmain
 The process cannot access the file because it is being used by another
 process.
 hello
 *Main

Under GHCi 6.6 I get this:

  *Main main
  bye
  0

My guess is that 6.4's readFile always opens the file as soon as it is
called, whereas 6.6's readFile delays opening until the list is
actually forced.  Either way, goblins all round!


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


Re: [Haskell-cafe] Re: Semantics of uniqueness types for IO (Was: Why can't Haskell be faster?)

2007-11-02 Thread Jonathan Cast
On Fri, 2007-11-02 at 11:56 -0400, Brandon S. Allbery KF8NH wrote:
 On Nov 2, 2007, at 11:51 , Jonathan Cast wrote:
 
  I will grant that hiding *World / RealWorld# inside IO is cleaner
  from a practical standpoint, though.  Just not from a semantic one.
 
  On the contrary.  GHC's IO newtype isn't an implementation of IO in
  Haskell at all.  It's an implementation in a language that has a
  Haskell-compatible subset, but that also has semantically bad  
  constructs
 
 Differing viewpoints, I guess; from my angle, Clean's uniqueness  
 constraint looks like a hack hidden in the compiler.

Yeah.  After all, the uniqueness constraint has a theory with an
excellent pedigree (IIUC linear logic, whose proof theory Clean uses
here, goes back at least to the 60s, and Wadler proposed linear types
for IO before anybody had heard of monads).  It's not some random hack
somebody happened to notice would work, any more than existential types
are.

jcc


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


Re: [Haskell-cafe] using an external application

2007-11-02 Thread Don Stewart
lemming:
 
 On Fri, 2 Nov 2007, Felipe Lessa wrote:
 
  On 11/2/07, Stuart Cook [EMAIL PROTECTED] wrote:
   The solution would be to use a version of readFile that works in a
   stricter way, by reading the file when it's told to, but I don't have
   an implementation handy.
 
  I guess this does the job:
 
   readFile' fp = do
 contents - readFile fp
 let ret (x:xs) = x `seq` ret xs
 ret [] = return contents
 ret contents
 
  Maybe the x `seq` part isn't necessary at all.
 
 Awful. It reminds me on MatLab where the developers have implemented many
 automatisms which do arbitrary clever things in every corner case, but
 nothing consistent, because they thought programmers want it that way.
 Then the programmers must write wrappers in order to get functions with
 consistent behaviour around the fully automated functions.
 
 The unlazying procedure looks much like the lazying one, and I wonder
 whether it would be a good idea to eventually add readFileStrict,
 getContentStrict and hGetContentStrict to the standard library.

Yes, I have often thought System.IO.Strict should be added to the strict
package on hackage, maybe in terms of bytestring.readFile = return .
unpack, since we're being strict anyway.

The above is also a rather odd implementation of readFile', which is
usually implemented by forcing the last element of the list instead.

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


[Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Isaac Gouy
Ketil Malde wrote:

 [LOC vs gz as a program complexity metric]

Do either of those make sense as a program /complexity/ metric?

Seems to me that's reading a lot more into those measurements than we
should.


It's slightly interesting that, while we're happily opining about LOCs
and gz, no one has even tried to show that switching from LOCs to gz
made a big difference in those program bulk rankings, or even
provided a specific example that they feel shows how gz is
misrepresentative - all opinion, no data.


(Incidentally LOC measures source code shape as much as anything else
- programs in statement heavy languages tend to be longer and thinner,
and expression heavy languages tend to be shorter and wider.)

__
Do You Yahoo!?
Tired of spam?  Yahoo! Mail has the best spam protection around 
http://mail.yahoo.com 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Hiding side effects in a data structure

2007-11-02 Thread Jon Fairbairn
Cale Gibbard [EMAIL PROTECTED] writes:

 On 21/10/2007, Jon Fairbairn [EMAIL PROTECTED] wrote:
 No, they (or at least links to them) typically are that bad!
 Mind you, as far as fragment identification is concerned, so
 are a lot of html pages.  But even if the links do have
 fragment ids, pdfs still impose a significant overhead: I
 don't want stuff swapped out just so that I can run a pdf
 viewer; a web browser uses up enough resources as it is. And
 will Hoogle link into pdfs?

 Swapped out!? What PDF viewer are you running on what machine?
 Currently, with a 552 page book open (Hatcher's algebraic topology),
 my PDF viewer (Evince) uses about 36MiB,

If loading another 36MiB doesn't cause swapping, you're
obviously not running enough haskell programmes.

-- 
Jón Fairbairn [EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: Semantics of uniqueness types for IO (Was: Why can't Haskell be faster?)

2007-11-02 Thread Jonathan Cast

On Fri, 2007-11-02 at 15:43 -0400, Jeff Polakow wrote:
 
 Hello, 
 
   Just a bit of minor academic nitpicking... 

Yeah.  After all, the uniqueness constraint has a theory with
 an
excellent pedigree (IIUC linear logic, whose proof theory Clean
 uses
here, goes back at least to the 60s, and Wadler proposed linear
   types
for IO before anybody had heard of monads).   

   Linear logic/typing does not quite capture uniqueness types since
 a
   term with a unique type can always be copied to become non-unique,
 but
   a linear type cannot become unrestricted. 
  
  Can I write a Clean program with a function that duplicates World?
  
 Clean won't let you duplicate the World. My comment on the mismatch
 with linear logic is aimed more at general uniqueness type systems
 (e.g. recent work by de Vries, Plasmeijer, and Abrahamson such as
 https://www.cs.tcd.ie/~devriese/pub/ifl06-paper.pdf). Sorry for the
 confusion. 

Ah.  I see.

jcc


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


Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Luke Palmer
On 11/2/07, Isaac Gouy [EMAIL PROTECTED] wrote:
 Ketil Malde wrote:

  [LOC vs gz as a program complexity metric]

 Do either of those make sense as a program /complexity/ metric?

You're right!  We should be using Kolmogorov complexity instead!

I'll go write a program to calculate it for the shootout.  Oh wait...

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


Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Jon Harrop
On Friday 02 November 2007 19:03, Isaac Gouy wrote:
 It's slightly interesting that, while we're happily opining about LOCs
 and gz, no one has even tried to show that switching from LOCs to gz
 made a big difference in those program bulk rankings, or even
 provided a specific example that they feel shows how gz is
 misrepresentative - all opinion, no data.

Why gzip and not run-length encoding, Huffman coding, arithmetic coding, block 
sorting, PPM etc.?

Choosing gzip is completely subjective and there is no logical reason to think 
that gzipped byte count reflects anything of interest. Why waste any time 
studying results in such an insanely stupid metric? Best case you'll end up 
concluding that the added complexity had no adverse effect on the results.

In contrast, LOC has obvious objective merits: it reflects the amount of code 
the developer wrote and the amount of code the developer can see whilst 
reading code.

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


[Haskell-cafe] The question of ByteString

2007-11-02 Thread Andrew Coppin

Somewhat related to the discussions about Haskell's performance...

String. ByteString. Do we really need both? Can one replace the other? 
Why is one faster? Can't we make *all* lists this fast? [insert further 
variations here]


Thoughts?

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


Re: [Haskell-cafe] Re: Semantics of uniqueness types for IO

2007-11-02 Thread Jeff Polakow
Hello,

 Just to continue the academic nitpicking.. :-)
 
  Linear logic/typing does not quite capture uniqueness types since a 
term 
  with a unique type can always be copied to become non-unique, but a 
linear 
  type cannot become unrestricted. 
 
 Actually, that isn't quite accurate. In linear logic, a term with a
 non-linear type can always be regarded as having a linear type, i.e.
 
   U -o !U
 
 is a theorem (my favourite reading of this theorem is if you have an
 unlimited supply of bank notes, then you also have a single one). The
 implication in the opposite direction is a falsity (from the fact that
 we have a single bank note, we cannot decude that we have an unlimited
 supply).

I think you mean

!U -o U

is a theorem. The converse is not provable.

In any case, I think we are saying the same thing.
 
-Jeff


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Semantics of uniqueness types for IO

2007-11-02 Thread Jeff Polakow
Hello,

 I think you mean 
 
 !U -o U 
 
 is a theorem. The converse is not provable. 

Oops... I should read more carefully before hitting send. 

This is of course completely wrong.

Sorry for the noise,
  Jeff


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Semantics of uniqueness types for IO

2007-11-02 Thread Jeff Polakow
Hello,

  I think you mean 
  
  !U -o U 
  
  is a theorem. The converse is not provable. 
  
 Oops... I should read more carefully before hitting send. 
 
 This is of course completely wrong. 
 
This is embarrassing... I was right the first time.

!U -o U 

is a theorem in linear logic. It can be read as given infinitely many U, I 
can get one U.


U -o !U 

is not a theorem in linear logic. It can be read as given one U, I can get 
infintely many U.


Sorry about the continued noise.

-Jeff



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Isaac Gouy

--- Jon Harrop [EMAIL PROTECTED] wrote:

 On Friday 02 November 2007 19:03, Isaac Gouy wrote:
  It's slightly interesting that, while we're happily opining about
 LOCs
  and gz, no one has even tried to show that switching from LOCs to
 gz
  made a big difference in those program bulk rankings, or even
  provided a specific example that they feel shows how gz is
  misrepresentative - all opinion, no data.
 
 Why gzip and not run-length encoding, Huffman coding, arithmetic
 coding, block 
 sorting, PPM etc.?
 
 Choosing gzip is completely subjective and there is no logical reason
 to think 
 that gzipped byte count reflects anything of interest. Why waste any
 time 
 studying results in such an insanely stupid metric? Best case you'll
 end up 
 concluding that the added complexity had no adverse effect on the
 results.
 
 In contrast, LOC has obvious objective merits: it reflects the amount
 of code 
 the developer wrote and the amount of code the developer can see
 whilst 
 reading code.

How strange that you've snipped out the source code shape comment that
would undermine what you say - obviously LOC doesn't tell you anything
about how much stuff is on each line, so it doesn't tell you about the
amount of code that was written or the amount of code the developer can
see whilst reading code.

__
Do You Yahoo!?
Tired of spam?  Yahoo! Mail has the best spam protection around 
http://mail.yahoo.com 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ARM back end?

2007-11-02 Thread Greg Fitzgerald
Anybody know of an ARM back end for any of the Haskell compilers?

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


Re: [Haskell-cafe] Please help from a newby

2007-11-02 Thread Andrew Wagner
 type Pkg = (Pkgtype,Address,Payload)
 type Table = [(Address,Port)]

 update_table1::Table - Pkg - Table
 update_table1 [] (t,d,y)  = [(t,d,y)]

The problem is that your function's type signature says it's returning
a Table, which is a [(Address,Port)], but it's actually returning a
[(Pkgtype,Address,Payload)]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Please help from a newby

2007-11-02 Thread Luke Palmer
On 11/2/07, karle [EMAIL PROTECTED] wrote:
 type Address = Int
 data Port = C | D deriving(Eq,Show)
 data Payload = UP[Char] | RTDP(Address,Port) deriving(Eq,Show)
 data Pkgtype = RTD | U deriving(Eq,Show)
 type Pkg = (Pkgtype,Address,Payload)
 type Table = [(Address,Port)]
^^
  Two elements

 update_table1::Table - Pkg - Table
 update_table1 [] (t,d,y)  = [(t,d,y)]
   ^^^
Three elements

So there's the error.You probably want to return something like
[(a,p)] where a is an address and p is a port.  I'm trying to figure
out where you would get that information though.  If your payload (the
y parameter in your implementation) is RTDP then you have _two_
addresses (the d parameter and the one in the payload), so I
wouldn't know which one to use, and if your payload is a UP then I
don't know where you would get a port.

On the other hand, I haven't the slightest clue what you're trying to
implement, I was just trying to figure it out based on the types :-)

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


Re: [Haskell-cafe] ARM back end?

2007-11-02 Thread Don Stewart
garious:
Anybody know of an ARM back end for any of the Haskell compilers?
 

nhc98 compiles to ARM,

http://www.haskell.org/nhc98/

however its lightly maintained, and many hackage libraries don't work
with nhc. So there's GHC with some effort can be made to work,

http://www.haskell.org/ghc/distribution_packages.html#debian

well, its even available out of the box for debian/arm. There's 
also a wiki page,

http://hackage.haskell.org/trac/ghc/wiki/ArmLinuxGhc

-- Don


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


Re: [Haskell-cafe] Please help from a newby

2007-11-02 Thread Christopher L Conway
Karle,

The expression (t,d,y) must have type Pkg, by your type annotation for
update_table1, so [ (t,d,y) ] has type [Pkg]. Also by your type
annotation, the result of update_table1 should by of type Table. Is
the type [Pkg] compatible with type Table? In other words, is the type
[ (Pkgtype,Address,Payload) ] the same as the type [ (Address,Port) ]?

Judging from your questions yesterday and today, I suspect that you
have not worked carefully through a Haskell language tutorial. I would
not discourage you from asking questions on the mailing list, but I
would strongly encourage you to consider referring to some of the
resources at http://haskell.org/haskellwiki/Books_and_tutorials before
trying to proceed with whatever programming project you are working
on.

Regards,
Chris

On 11/2/07, karle [EMAIL PROTECTED] wrote:

 The same declaration.-


 type Address = Int
 data Port = C | D deriving(Eq,Show)
 data Payload = UP[Char] | RTDP(Address,Port) deriving(Eq,Show)
 data Pkgtype = RTD | U deriving(Eq,Show)
 type Pkg = (Pkgtype,Address,Payload)
 type Table = [(Address,Port)]

 update_table1::Table - Pkg - Table
 update_table1 [] (t,d,y)  = [(t,d,y)]

 Error is

 Type error in explicitly typed binding
 *** Term   : update_table1
 *** Type   : Table - Pkg - [(Pkgtype,Int,Payload)]
 *** Does not match : Table - Pkg - Table

 Please kindly suggest, thanks in advance.





 --
 View this message in context: 
 http://www.nabble.com/Please-help-from-a-newby-tf4740192.html#a13555338
 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] ARM back end?

2007-11-02 Thread Dan Piponi
On 11/2/07, Greg Fitzgerald [EMAIL PROTECTED] wrote:
 Anybody know of an ARM back end for any of the Haskell compilers?

This version of hugs worked on my (ARM based) NSLU2:
http://ipkgfind.nslu2-linux.org/details.php?package=hugsofficial=format=
-
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ARM back end?

2007-11-02 Thread nornagon
On 03/11/2007, Greg Fitzgerald [EMAIL PROTECTED] wrote:
 Anybody know of an ARM back end for any of the Haskell compilers?


If there's an arm-eabi port somewhere, I might be able to get Haskell
code running on the Nintendo DS...

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


Re: [Haskell-cafe] The question of ByteString

2007-11-02 Thread Andrew Coppin

Tim Chevalier wrote:

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

Somewhat related to the discussions about Haskell's performance...

String. ByteString. Do we really need both? Can one replace the other?



You can't get rid of String because a String is just a [Char].
Requiring the element type of a list to be anything except Char
would be silly. In addition, it's useful to have a String that you can
apply arbitrary list operations to when performance isn't a concern
(i.e., most of the time). Finally, removing String would break
existing code.

  

Why is one faster? Can't we make *all* lists this fast? [insert further
variations here]



ByteString takes advantage of the fact that the elements are, well,
bytes. The operations are optimized for reading large amounts of text,
but not necessarily for other applications. Lists are a parameterized
type, so the elements of a list are pointers to arbitrary data. So
that's why the same tricks as ByteString don't apply to general lists.
That isn't to say that there aren't possible optimizations which
haven't yet been dreamed of.
  


Well OK, maybe I was a little vague. Let me be a bit more specific...

If you do text processing using ByteString rather than String, you get 
dramatically better performance in time and space. For me, this raises a 
number of questions:


1. Why do I have to type ByteString in my code? Why isn't the compiler 
automatically performing this optimisation for me? (I.e., is there some 
observable property that is changed? Currently the answer is yes: the 
ByteString interface only provides trancated Unicode characters. But, 
in principle, that could be changed.)


2. ByteString makes text strings faster. But what about other kinds of 
collections? Can't we do something similar to them that makes them go 
faster?


As I understand it, ByteString is faster due to several factors. First 
of all, it's stricter. Secondly, it's an unboxed structure (so you 
eliminate layers of indirection and there's less GC load). Third, it's 
implemented as an array that looks like a linked list. Given how 
ubiquitous lists are in Haskell, array that looks like a linked list 
sounds like one seriously useful data type! Yet ByteString seems to be 
the only implementation of this concept - and only for lists on unboxed 
bytes. (Not even unboxed Word16 or anything else, *only* Word8.) If I 
understand this correctly, a ByteString is actually a linked list of 
large array chunks. (This presumably yields fastER random access than a 
plain linked list?) Also, it seems to be possible to create a new array 
which is merely a subrange of an existing one, without any copying; the 
standard array API doesn't seem to provide this, yet it sounds damn useful.


These are the things I'm thinking about. Is there some deep theoretical 
reason why things are the way they are? Or is it merely that nobody has 
yet had time to make something better? ByteString solves the problem of 
text strings (and raw binary data) very nicely, it's just a pitty we 
can't apply some of that know-how more widely...


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


Re: [Haskell-cafe] The question of ByteString

2007-11-02 Thread Tim Chevalier
On 11/2/07, Andrew Coppin [EMAIL PROTECTED] wrote:

 1. Why do I have to type ByteString in my code? Why isn't the compiler
 automatically performing this optimisation for me? (I.e., is there some
 observable property that is changed? Currently the answer is yes: the
 ByteString interface only provides trancated Unicode characters. But,
 in principle, that could be changed.)

That's an interesting question; one property the compiler would have
to prove in order to replace a String with a ByteString is that the
given String will be fully evaluated strictly (e.g., not just that it
will be evaluated to WHNF, but that each of its elements will be
demanded). Currently, GHC's demand analyzer doesn't look inside lists
(it only looks inside things that have product types), but it's not
unimaginable. It would be a matter of whether the potential payoff
justifies the complexity of the imagined analysis, as always.


 2. ByteString makes text strings faster. But what about other kinds of
 collections? Can't we do something similar to them that makes them go
 faster?

 As I understand it, ByteString is faster due to several factors. First
 of all, it's stricter. Secondly, it's an unboxed structure (so you
 eliminate layers of indirection and there's less GC load). Third, it's
 implemented as an array that looks like a linked list. Given how
 ubiquitous lists are in Haskell, array that looks like a linked list
 sounds like one seriously useful data type! Yet ByteString seems to be
 the only implementation of this concept - and only for lists on unboxed
 bytes. (Not even unboxed Word16 or anything else, *only* Word8.) If I
 understand this correctly, a ByteString is actually a linked list of
 large array chunks. (This presumably yields fastER random access than a
 plain linked list?) Also, it seems to be possible to create a new array
 which is merely a subrange of an existing one, without any copying; the
 standard array API doesn't seem to provide this, yet it sounds damn useful.

 These are the things I'm thinking about. Is there some deep theoretical
 reason why things are the way they are? Or is it merely that nobody has
 yet had time to make something better? ByteString solves the problem of
 text strings (and raw binary data) very nicely, it's just a pitty we
 can't apply some of that know-how more widely...


I don't think there's a deep theoretical reason why this doesn't
exist, but I also don't think it's necessarily *just* a matter of no
one having had time yet. As always, there are trade-offs involved, and
people try to avoid introducing *too* many special cases into the
compiler.

Cheers,
Tim

-- 
Tim Chevalier * catamorphism.org * Often in error, never in doubt
I give fellowship advice, not relationship advice.  -- Michael Sacramento
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The question of ByteString

2007-11-02 Thread Andrew Coppin

Tim Chevalier wrote:

I don't think there's a deep theoretical reason why this doesn't
exist, but I also don't think it's necessarily *just* a matter of no
one having had time yet. As always, there are trade-offs involved, and
people try to avoid introducing *too* many special cases into the
compiler.
  


Well, that sounds like a reasonable answer.

ByteString is a special case. I'm just wondering how much of it is 
really specific to the string / binary processing case, and how much of 
it will generalise to other useful places. ;-)


(Mathematicians like to ask interesting questions. Unfortunately, at 
least in mathematics, interesting tends to correlate with this may 
take several human lifetimes to solve...)


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


Re: [Haskell-cafe] The question of ByteString

2007-11-02 Thread Bryan O'Sullivan

Andrew Coppin wrote:

1. Why do I have to type ByteString in my code? Why isn't the compiler 
automatically performing this optimisation for me?


One reason is that ByteString is stricter than String.  Even lazy 
ByteString operates on 64KB chunks.  You can see how this might lead to 
problems with a String like this:


foo ++ undefined

The first three elements of this list are well-defined, but if you touch 
the fourth, you die.


2. ByteString makes text strings faster. But what about other kinds of 
collections? Can't we do something similar to them that makes them go 
faster?


Not as easily.  The big wins with ByteString are, as you observe, that 
the data are tiny, uniformly sized, and easily unboxed (though using 
ForeignPtr seems to be a significant win compared to UArray, too).  This 
also applies to other basic types like Int and Double, but leave those 
behind, and you get problems.


If your type is an instance of Storable, it's going to have a uniform 
size, but it might be expensive to flatten and unflatten it, so who 
knows whether or not it's truly beneficial.  If it's not an instance of 
Storable, you have to store an array of boxed values, and we know that 
arrays of boxes have crummy locality of reference.


Spencer Janssen hacked up the ByteString code to produce StorableVector 
as part of last year's SoC, but it never got finished off:


http://darcs.haskell.org/SoC/fps-soc/Data/StorableVector/

More recently, we've been pinning our hopes on the new list fusion stuff 
to give many of the locality of reference benefits of StorableVector 
with fewer restrictions, and all the heavy work done in a library.


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


Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Sebastian Sylvan
On 11/2/07, Isaac Gouy [EMAIL PROTECTED] wrote:

 How strange that you've snipped out the source code shape comment that
 would undermine what you say - obviously LOC doesn't tell you anything
 about how much stuff is on each line, so it doesn't tell you about the
 amount of code that was written or the amount of code the developer can
 see whilst reading code.

It still tells you how much content you can see on a given amount of
vertical space.

I think the point, however, is that while LOC is not perfect, gzip is
worse. It's completely arbitrary and favours languages wich requires
you to write tons of book keeping (semantic noise) as it will compress
down all that redundancy quite a bit (while the programmer would still
has to write it, and maintain it).
So gzip is even less useful than LOC, as it actively *hides* the very
thing you're trying to meassure! You might as well remove it
alltogether.

Or, as has been suggested, count the number of words in the program.
Again, not perfect (it's possible in some languages to write things
which has no whitespace, but is still lots of tokens).

-- 
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] The question of ByteString

2007-11-02 Thread Brandon S. Allbery KF8NH


On Nov 2, 2007, at 17:35 , Andrew Coppin wrote:

These are the things I'm thinking about. Is there some deep  
theoretical reason why things are the way they are? Or is it merely  
that nobody has yet had time to make something better? ByteString  
solves the problem of text strings (and raw binary data) very  
nicely, it's just a pitty we can't apply some of that know-how more  
widely...


I'm under the impression that several of the things that make  
ByteString faster (e.g. smarter fusion) are either implemented within  
(newer) GHC already, such that other list-like types can take  
advantage of them directly, or being worked on as part of a new  
Data.Stream module that anyone can use with their own types instead  
of simple lists.  So in the long run it *won't* just be ByteString;  
that's just what's driving the development.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Compile-time evaluation

2007-11-02 Thread Nicholas Messenger
On 11/2/07, Robin Green [EMAIL PROTECTED] wrote:
 snip ...since
 there is a Template Haskell class for the concept of translating actual
 values into TH representations of those values called Lift... snip

There's a WHAT?!

*checks docs*

You're telling me all that horrendous pain in implementing toExp and
it already exists?!?

GRRAGGHHRAWWRRRAAGGGH!

*sob*

...

Ah, well, I learned me some Data.Generics anyway.  :3

-- Nicholas Messenger (nmessenger at gmail.com, omnId on #haskell)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Could someone explain winhugs does not accept this argument?

2007-11-02 Thread karle

type Address = Int 
data Port = C | D deriving(Eq,Show) 
data Payload = UP[Char] | RTDP(Address,Port) deriving(Eq,Show) 
data Pkgtype = RTD | U deriving(Eq,Show)
type Pkg = (Pkgtype,Address,Payload) 
type Table = Signal (Address,Port) 


system inA inB = (outC,outD)
 where
 route = update_pr inA inB
 s1 = lookup_pr route inA
 s2 = lookup_pr route inB
 (s3,s4) = unzipSY s1
 (s5,s6) = unzipSY s2
 s7 = add_list_pr s3 s5
 s8 = add_list_pr s4 s6
 outC = fifoSY s7
 outD = fifoSY s8


lookup_pr::Signal Table-AbstExt Pkg-AbstExt Pkg 
lookup_pr t (Prst(x,y,z)) 
|(delive_adr_A t == y  x == U) = (Prst(x,y,z)) 
|otherwise = look_if_RTD_pkG_A t (Prst(x,y,z)) 

the error message is 

Type error in application
*** Expression : delive_adr_A t
*** Term   : t
*** Type   : Signal Table
*** Does not match : Signal (Int,Port)



-- 
View this message in context: 
http://www.nabble.com/Could-someone-explain-winhugs-does-not-accept-this-argument--tf4741195.html#a13557810
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] The question of ByteString

2007-11-02 Thread Duncan Coutts
On Fri, 2007-11-02 at 21:35 +, Andrew Coppin wrote:

 Well OK, maybe I was a little vague. Let me be a bit more specific...
 
 If you do text processing using ByteString rather than String, you get 
 dramatically better performance in time and space. For me, this raises a 
 number of questions:
 
 1. Why do I have to type ByteString in my code? Why isn't the compiler 
 automatically performing this optimisation for me? (I.e., is there some 
 observable property that is changed? 

Yes, the semantics are different. ByteString is stricter. In some
circumstances you could discover that some list is being used
sufficiently strictly (spine and element strict) that you could do a
representation change to use strict arrays. It is something I have
pondered occasionally and I think that is an interesting avenue for
research.

One approach might be to do a more sophisticated strictness analysis
earlier in the compilation process; one that gives details on strictness
of substructure, ie the tail/element strictness in lists. Then if this
strictness information were available to the rule matching then we might
be able to write rules that change certain functions to work on
optimised data representations.

However this is likely to be quite fragile. I usually think that it's
better to declare the strictness you want up front in one place, and
have that be propagated, rather than doing the reverse of inferring that
something could be stricter from all the use sites. Strictness
annotations on data constructors are a good example of this.

 Currently the answer is yes: the ByteString interface only provides
 trancated Unicode characters. But, in principle, that could be
 changed.)

Indeed it could, we could provide a proper Unicode string type.

 2. ByteString makes text strings faster. But what about other kinds of 
 collections? Can't we do something similar to them that makes them go 
 faster?

There is much less benefit for other collections since the overheads of
generic structures are smaller for other types.

Note that the NDP parallel arrays stuff uses type functions to calculate
optimised data representations for arrays of types.

 As I understand it, ByteString is faster due to several factors. First 
 of all, it's stricter.

Do that's the semantic difference.

 Secondly, it's an unboxed structure (so you eliminate layers of
 indirection and there's less GC load). 

Which is the representation optimisation allowed by the semantic change
of making it stricter.

 Third, it's implemented as an array that looks like a linked list.
 Given how ubiquitous lists are in Haskell, array that looks like a
 linked list sounds like one seriously useful data type! Yet
 ByteString seems to be the only implementation of this concept - and
 only for lists on unboxed bytes. (Not even unboxed Word16 or anything
 else, *only* Word8.) If I understand this correctly, a ByteString is
 actually a linked list of large array chunks. (This presumably yields
 fastER random access than a plain linked list?) Also, it seems to be
 possible to create a new array which is merely a subrange of an
 existing one, without any copying; the standard array API doesn't seem
 to provide this, yet it sounds damn useful.

I think the NDP project should get us most of this stuff actually.

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


[Haskell-cafe] Layout to non-layout code

2007-11-02 Thread Maurí­cio

Hi,

I understand that many people like using
layout in their code, and 99% of all
Haskell examples use some kind of layout
rule. However, sometimes, I would like
not to use layout, so I can find errors
easier (and maybe convert it to layout for
presentation after all problems are solved).

So, I wonder: would it be possible to
implement a feature in, say, ghc, that would
take code from input and output the same
code with layout replaced by delimiting
characters? For instance, it could take
(untested code warning here):

main = do
  s - readLn
  putStrLn s

and convert it to:

main = do {s-readLn; putStrLn s};

I imagine that would be easy, since the
compiler has to do that as a first step
anyway.

If it's possible, how can I sugest that
feature?

Thanks,
Maurício

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


Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Isaac Gouy

--- Sebastian Sylvan [EMAIL PROTECTED] wrote:
-snip- 
 It still tells you how much content you can see on a given amount of
 vertical space.

And why would we care about that? :-)
 

 I think the point, however, is that while LOC is not perfect, gzip is
 worse.

How do you know? 

 
  Best case you'll end up concluding that the added complexity had
  no adverse effect on the results.

Best case would be seeing that the results were corrected against bias
in favour of long-lines, and ranked programs in a way that looks-right
when we look at the program source code side-by-side.


 It's completely arbitrary and favours languages wich requires
 you to write tons of book keeping (semantic noise) as it will
 compress down all that redundancy quite a bit (while the programmer
 would still has to write it, and maintain it).
 So gzip is even less useful than LOC, as it actively *hides* the very
 thing you're trying to meassure! You might as well remove it
 alltogether.

I don't think you've looked at any of the gz rankings, or compared the
source code for any of the programs :-)
 

 Or, as has been suggested, count the number of words in the program.
 Again, not perfect (it's possible in some languages to write things
 which has no whitespace, but is still lots of tokens).

Wouldn't that be completely arbitrary?


__
Do You Yahoo!?
Tired of spam?  Yahoo! Mail has the best spam protection around 
http://mail.yahoo.com 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Don Stewart
igouy2:
 
 --- Sebastian Sylvan [EMAIL PROTECTED] wrote:
 -snip- 
  It still tells you how much content you can see on a given amount of
  vertical space.
 
 And why would we care about that? :-)
  
 
  I think the point, however, is that while LOC is not perfect, gzip is
  worse.
 
 How do you know? 
 
  
   Best case you'll end up concluding that the added complexity had
   no adverse effect on the results.
 
 Best case would be seeing that the results were corrected against bias
 in favour of long-lines, and ranked programs in a way that looks-right
 when we look at the program source code side-by-side.
 
 
  It's completely arbitrary and favours languages wich requires
  you to write tons of book keeping (semantic noise) as it will
  compress down all that redundancy quite a bit (while the programmer
  would still has to write it, and maintain it).
  So gzip is even less useful than LOC, as it actively *hides* the very
  thing you're trying to meassure! You might as well remove it
  alltogether.
 
 I don't think you've looked at any of the gz rankings, or compared the
 source code for any of the programs :-)
  
 
  Or, as has been suggested, count the number of words in the program.
  Again, not perfect (it's possible in some languages to write things
  which has no whitespace, but is still lots of tokens).
 
 Wouldn't that be completely arbitrary?
 

I follow the shootout changes fairly often, and the gzip change didn't 
significantly alter the rankings, though iirc, it did cause perl to drop
a few places.

Really, its a fine heuristic, given its power/weight ratio.

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


Re: [Haskell-cafe] Layout to non-layout code

2007-11-02 Thread Don Stewart
briqueabraque:
 Hi,
 
 I understand that many people like using
 layout in their code, and 99% of all
 Haskell examples use some kind of layout
 rule. However, sometimes, I would like
 not to use layout, so I can find errors
 easier (and maybe convert it to layout for
 presentation after all problems are solved).
 
 So, I wonder: would it be possible to
 implement a feature in, say, ghc, that would
 take code from input and output the same
 code with layout replaced by delimiting
 characters? For instance, it could take
 (untested code warning here):
 
 main = do
   s - readLn
   putStrLn s
 
 and convert it to:
 
 main = do {s-readLn; putStrLn s};
 
 I imagine that would be easy, since the
 compiler has to do that as a first step
 anyway.
 
 If it's possible, how can I sugest that
 feature?

ghc -ddump-parsed does this, iirc.

So does the Language.Haskell library. See this wiki page on indenting
for more ideas,

http://haskell.org/haskellwiki/Indent

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


Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Jon Harrop
On Friday 02 November 2007 20:29, Isaac Gouy wrote:
 ...obviously LOC doesn't tell you anything 
 about how much stuff is on each line, so it doesn't tell you about the
 amount of code that was written or the amount of code the developer can
 see whilst reading code.

Code is almost ubiquitously visualized as a long vertical strip. The width is 
limited by your screen. Code is then read by scrolling vertically. This is 
why LOC is a relevant measure: because the area of the code is given by LOC * 
screen width and is largely unrelated to the subjective amount of stuff on 
each line.

As you say, imperative languages like C are often formatted such that a lot of 
right-hand screen real estate is wasted. LOC penalizes such wastage. The same 
cannot be said for gzipped bytes, which is an entirely irrelevant metric...

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


Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Greg Fitzgerald
 while LOC is not perfect, gzip is worse.
 the gzip change didn't significantly alter the rankings

Currently the gzip ratio of C++ to Python is 2.0, which at a glance,
wouldn't sell me on a less code argument.  Although the rank stayed the
same, did the change reduce the magnitude of the victory?

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


Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Jon Harrop
On Friday 02 November 2007 23:53, Isaac Gouy wrote:
   Best case you'll end up concluding that the added complexity had
   no adverse effect on the results.

 Best case would be seeing that the results were corrected against bias
 in favour of long-lines, and ranked programs in a way that looks-right
 when we look at the program source code side-by-side.

Why would you want to subjectively correct for bias in favour of long 
lines?

  Or, as has been suggested, count the number of words in the program.
  Again, not perfect (it's possible in some languages to write things
  which has no whitespace, but is still lots of tokens).

 Wouldn't that be completely arbitrary?

That is not an argument in favour of needlessly adding extra complexity and 
adopting a practically-irrelevant metric.

Why not use the byte count of a PNG encoding of a photograph of the source 
code written out by hand in blue ballpoint pen?

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


Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Isaac Gouy

--- Greg Fitzgerald [EMAIL PROTECTED] wrote:

  while LOC is not perfect, gzip is worse.
  the gzip change didn't significantly alter the rankings
 
 Currently the gzip ratio of C++ to Python is 2.0, which at a glance,
 wouldn't sell me on a less code argument. 

a) you're looking at an average, instead try

http://shootout.alioth.debian.org/gp4/benchmark.php?test=alllang=pythonlang2=gpp

b) we're not trying to sell you on a less code argument - it's
whatever it is



 Although the rank stayed the
 same, did the change reduce the magnitude of the victory?

c) that will have varied program to program, and do you care which way
the magnitude of victory moved or do you care that where it moved to
makes more sense?

For fun, 2 meteor-contest programs, ratios to the python-2 program
 LOC  GZ  WC
ghc-3   0.981.401.51
gpp-4   3.764.144.22

Look at the python-2 and ghc-3 source and tell us if LOC gave a
reasonable indication of relative program size - is ghc-3 really the
smaller program? :-)

http://shootout.alioth.debian.org/gp4/benchmark.php?test=meteorlang=allsort=gz


__
Do You Yahoo!?
Tired of spam?  Yahoo! Mail has the best spam protection around 
http://mail.yahoo.com 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-02 Thread Ryan Dickie
On 11/2/07, Sterling Clover [EMAIL PROTECTED] wrote:

 As I understand it, the question is what you want to measure for.
 gzip is actually pretty good at, precisely because it removes
 boilerplate, reducing programs to something approximating their
 complexity. So a higher gzipped size means, at some level, a more
 complicated algorithm (in the case, maybe, of lower level languages,
 because there's complexity that's not lifted to the compiler). LOC
 per language, as I understand it, has been somewhat called into
 question as a measure of productivity, but there's still a
 correlation between programmers and LOC across languages even if it
 wasn't as strong as thought -- on the other hand, bugs per LOC seems
 to have been fairly strongly debunked as something constant across
 languages. If you want a measure of the language as a language, I
 guess LOC/gzipped is a good ratio for how much noise it introduces
 -- but if you want to measure just pure speed across similar
 algorithmic implementations, which, as I understand it, is what the
 shootout is all about, then gzipped actually tends to make some sense.

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


Lossless File compression, AKA entropy coding, attempts to maximize the
amount of information per bit (or byte) to be as close to the entropy as
possible. Basically, gzip is measuring (approximating) the amount of
information contained in the code.

I think it would be interesting to compare the ratios between raw file size
its entropy (we can come up with a precise metric later). This would show us
how concise the language and code actually is.

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


[Haskell-cafe] Re: Layout to non-layout code

2007-11-02 Thread Maurí­cio

 Hi,

 (...)

 So, I wonder: would it be possible to implement
 a feature in, say, ghc, that would take code
 from input and output the same code with layout
 replaced by delimiting characters? (...)


 ghc -ddump-parsed does this, iirc.

 So does the Language.Haskell library. See this
 wiki page on indenting for more ideas,

 http://haskell.org/haskellwiki/Indent

 -- Don

I was impressed after your tip about
'Language.Haskell'. In a few minutes, I got my
dream Haskell formatter. Here it is, parsed by
itself. Thanks for your tip.

module Main (Main.main) where
{ import System.IO;
  import Language.Haskell.Parser;
  import Language.Haskell.Pretty;
  import Text.PrettyPrint.HughesPJ;

  main :: IO ();
  main
 = do
   { program - getContents;
 ParseOk parse - return $
 parseModule program;
 estilo - return $ Style PageMode 50 1.0;
 modo - return $
PPHsMode 0 0 0 0 0 3 True
   PPSemiColon
   False
   True;
 putStrLn $
prettyPrintStyleMode estilo modo
   parse}}

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