[Haskell-cafe] Re: Can somebody give any advice for beginners?

2007-09-11 Thread Gracjan Polak
clisper clisper at 163.com writes:

 
 
 haskell is greate
 but i don't know how to start.
  

Don't!

Learning Haskell will change your world! For worse! Really! Don't do that, 
you still have time to go back! Or be damned like all of us here...

Referential transparency will suck up your soul. You'll think about monads 
as your warm and fuzzy friends. You'll wash your hands after doing IO 
because you'll feel that your purity suffered.

You'll consider unit testing a downgraded form of static typing. When your
programs finally compile, they will magically just work. You'll write 
less and less KLOC, doing more at the same time.

Your C#/C++/Java code will look like higher order code after first order
transformation done by hand. Your co-workers and friends will not understand 
what you wrote any more. You'll be like a wizard from another planet for them.

You will know the difference between foldl and foldr.

All your data structures will be infinite in size. Space leaks will bite you
hard. Your functions will be not lazy enough in some arguments and not strict
enough in some others at the same time. And even seq will not help you.

You'll know what MPTCs and GADTs are. You'll actually understand olegs posts.
You'll wonder, what was that OO thing again? You'll take out Java from your CV.

Take a friendly advice: go back and forget that you ever heard about Haskell!

-- 
Gracjan


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


[Haskell-cafe] Over-allocation

2007-11-21 Thread Gracjan Polak

Hi,

My program is eating too much memory:

copyfile source.txt dest.txt +RTS -sstderr
Reading file...
Reducing structure...
Writting file...
Done in 20.277s
1,499,778,352 bytes allocated in the heap
2,299,036,932 bytes copied during GC (scavenged)
1,522,112,856 bytes copied during GC (not scavenged)
 17,846,272 bytes maximum residency (198 sample(s))

   2860 collections in generation 0 ( 10.37s)
198 collections in generation 1 (  8.35s)

 50 Mb total memory in use

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time1.26s  (  1.54s elapsed)
  GCtime   18.72s  ( 18.74s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time   19.98s  ( 20.28s elapsed)

  %GC time  93.7%  (92.4% elapsed)

  Alloc rate1,186,898,778 bytes per MUT second

  Productivity   6.3% of total user, 6.2% of total elapsed

The source.txt is 800kb, and I expect files of size 100 times more, say 80MB, so
using -H800M will not help here much.

The profile -p says:

Wed Nov 21 14:23 2007 Time and Allocation Profiling Report  (Final)

   copyfile +RTS -p -RTS source.txt dest.txt

total time  =4.48 secs   (224 ticks @ 20 ms)
total alloc = 1,500,359,340 bytes  (excludes profiling overheads)

COST CENTREMODULE   %time %alloc

xparse PdfModel  78.1   95.0

followed by a lot of 0.0 numbers.

Then the faulty xparse:

xparse uniq borders body bin = do
parseOperatorEq xref
p - P.many (parseXRefSection uniq)
parseOperatorEq trailer
e - parseDict
let entries = IntMap.fromList (map (\(a,b,c) - (a,c)) (concat p))
return (Body e entries)

where the P is Text.ParserCombinators.ReadP made to work with [Word8]. How do I
know WHAT is making so much allocation in this function?

My files are xml-like in structure. The task currently is to read, parse, write
the file. I can provide more details for interested souls.

How do I make my program make less allocations?

-- 
Gracjan


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


[Haskell-cafe] Re: Over-allocation

2007-11-21 Thread Gracjan Polak
Stefan O'Rear stefanor at cox.net writes:
 
 Note that heap profiling is even more a black art than time profiling;
 you may need to do a lot of experimentation to find an enlightening
 profile.
 

Black art indeed... I did -hc, looked at the postscript generated from every
angle I could and it looks like this:

/|/|/|
   / |   / |   / |
  /  |  /  |  /  |
 /   | /   | /   |
/|/|/|

This is only xparse, other functions are unimportant and aren't even visible on
the graph.

My xparse allocates a lot of memory which is then almost all freed at the very
next occasion by GC. Seems I do not have space leaks.

The problem is that my prog allocates a lot just to free it immediatelly after.
But what?

-- 
Gracjan


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


[Haskell-cafe] Re: Over-allocation

2007-11-21 Thread Gracjan Polak
Ketil Malde ketil+haskell at ii.uib.no writes:

 
 Gracjan Polak gracjanpolak at gmail.com writes:
 
  let entries = IntMap.fromList (map (\(a,b,c) - (a,c)) (concat p))
 
 Gut reaction: Map is lazy in its values (but probably not the key,
 which are checked for order), so you should force the 'c' before
 inserting it in the map.  (There's probably a strict fromList or
 IntMap somewhere?) 

I tried both Map and IntMap and there was no difference in memory total usage or
usage pattern. Seems I'm already strict enough.

Values are left lazy till the point where they are forced, and that is at
write-out in my current excersise. I'd want to leave them lazy as in more
involved transformation not all of them will be needed.

-- 
Gracjan


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


[Haskell-cafe] Re: Over-allocation

2007-11-21 Thread Gracjan Polak
Ketil Malde ketil+haskell at ii.uib.no writes:
 
 Then you get the memory behavior you ask for.  Unevaluated strings are
 extremely expensive, something like 12 bytes per char on 32 bit, twice
 that on 64 bits, and then you need GC overhead, etc.  ByteStrings are
 much better, but you then probably need to implement your own XML
 parsing. 
 

My lazy chunks have type ByteString - Object. Only internally they use
ByteString.unpack to get the list of Word8s to parse them.

My parser is totally my own so I can do anything I wish. Except it is hard for
me to image a parser working on something else than [Word8]. How do I do this?

So how do I get rid of those (:) and W8# that are allocated everywhere on my 
heap?

Thanks for the suggestion for -hd, really useful option!

-- 
Gracjan




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


[Haskell-cafe] Re: Over-allocation

2007-11-22 Thread Gracjan Polak
Don Stewart dons at galois.com writes:
 
 ByteStrings have all the same operations as lists though, so you can
 index, compare and take substrings, with the benefit that he underlying
 string will be shared, not copied. And only use 1 byte per element.

Is there any parser built directly over ByteString that I could look at?

Or maybe somebody implemented something like Text.ParserCombinators.ReadP for
ByteString?

From the first sight it seems doable, so there is light at the end of the 
tunnel :)

-- 
Gracjan


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


[Haskell-cafe] Re: Over-allocation

2007-11-22 Thread Gracjan Polak
Gracjan Polak gracjanpolak at gmail.com writes:

 
 Don Stewart dons at galois.com writes:
  
  ByteStrings have all the same operations as lists though, so you can
  index, compare and take substrings, with the benefit that he underlying
  string will be shared, not copied. And only use 1 byte per element.
 
 Is there any parser built directly over ByteString that I could look at?
 
 Or maybe somebody implemented something like Text.ParserCombinators.ReadP for
 ByteString?
 
 From the first sight it seems doable, so there is light at the end of the 
 tunnel :)
 

Just a success report, after 58 min of coding I got kind of ReadP parser over
ByteString working and my memory usage went down from 1500MB to... 1.2MB! Over
1000 times better! Incredible!

Thanks for the suggestion to do it with ByteStrings!

I hope to publish it when I clean it up enough!

-- 
Gracjan



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


[Haskell-cafe] ANNOUNCE: A ReadP style parser for ByteStrings

2007-12-11 Thread Gracjan Polak

I'm happy to announce a ReadP style parser for ByteStrings,
Text.ParserCombinators.ReadP.ByteString.

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

Text.ParserCombinators.ReadP.ByteString is an adaptation of
Text.ParserCombinators.ReadP to work over Data.ByteString as input
stream representation. This gives enormous improvements in terms of
parsing speed but most significantly in memory usage.

Features:

 * ReadP style parser over ByteString input
 * Drop-in replacement for Text.ParserCombinators.ReadP
 * Fast
 * Good memory usage

The algorithm is slightly modified to exploit ByteString as random access
data input structure. Unlike original ReadP, that stressed garbage collection 
very much by creating a lot of conses (:), this parser has very good memory
allocation behaviour.

Package works out of the box with GHC 6.8.1, with slight (cabal) modifications
also with GHC 6.6.1.

Thanks to everyone for their support! Happy hacking!

--
Gracjan


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


[Haskell-cafe] Re: Happstack basic question

2010-03-15 Thread Gracjan Polak

I'd like to add a warning to this discussion.
You might be affected by this issue:

http://trac.haskell.org/network/ticket/11

TL;DR: It is kind of random if you bind to IPv4 or IPv6 or both. For example
Windows Vista likes to bind to IPv6 only.

Watch your ports and protocols!

-- 
Gracjan


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


[Haskell-cafe] How to set a breakpoint in GHCi

2010-03-21 Thread Gracjan Polak

Hi all,

Tried to use :break today, without success:

guestbook-session-bugghci -DMIN_VERSION_template_haskell(a,b,c)=1 
-isrc Main -i../happstack/happstack-ixset/src
GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
...
...
[10 of 13] Compiling Happstack.Data.IxSet (
..\happstack\happstack-ixset\src\Happstack\Data\IxSet.hs, interpreted )
...
...
*Main :m +Happstack.Data.IxSet
*Main Happstack.Data.IxSet :bre getOrd
No breakpoints found at that location.
*Main Happstack.Data.IxSet

What now?

-- 
Gracjan


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


[Haskell-cafe] Re: Are there any web server framework ?

2010-03-24 Thread Gracjan Polak


Recently I started to play with Happstack and I must say I'm amazed how good it
works for me! It has server, string templating, type safe html templating,
persistence (like a database, only more fun), email stuff.

To get a grasp at what goes under Happstack name here is a tutorial:

http://tutorial.happstack.com/

-- 
Gracjan




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


[Haskell-cafe] Re: Are there any female Haskellers?

2010-03-27 Thread Gracjan Polak
Alberto G. Corona  agocorona at gmail.com writes:
 
 Hope that this cold answer don't end this funny thread ;(
 

Those concerned with Haskellers to Haskellinas ration can always employ this
technique:

http://www.newton.dep.anl.gov/askasci/bio99/bio99128.htm

Any volunteers? :)

-- 
Gracjan



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


[Haskell-cafe] Re: src/Text/XML/HaXml/Lex.hs:(156, 0)-(160, 22): Non-exhaustive patterns in function white

2010-07-21 Thread Gracjan Polak
Antoine Latter aslatter at gmail.com writes:
 Sending off to the maintainer of haxr, although it looks like it might
 be in HaXml (from an outside guess).

Without some real example to look at it will be quite tough to proceed.

Alexander, can you send that stream of packets to me?

-- 
Gracjan


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


[Haskell-cafe] Re: src/Text/XML/HaXml/Lex.hs:(156, 0)-(160, 22): Non-exhaustive patterns in function white

2010-07-23 Thread Gracjan Polak
Alexander Kotelnikov sacha at myxomop.com writes:

 
  On Wed, 21 Jul 2010 06:46:26 + (UTC)
  GP == Gracjan Polak gracjanpolak at gmail.com wrote:
 GP 
 GP Antoine Latter aslatter at gmail.com writes:
  Sending off to the maintainer of haxr, although it looks like it might
  be in HaXml (from an outside guess).
 GP 
 GP Without some real example to look at it will be quite tough to proceed.
 GP 
 GP Alexander, can you send that stream of packets to me?
 
 I attach a stream dump.
 
 
 Attachment (poster.dump): application/octet-stream, 2916 bytes
 
 

My guess at this point:

Your XML contains PNG as binary data. Since this part is interpreted as a string
with UTF-8 encoding we have big trouble here. Some of byte combinations in PNG
do not constitute correct coding points, are probably converted/normalized and
are interpreted as invalid XML.

Solution: use text-based encoding for binary data. Base64 seems to be obvius
candidate here.

-- 
Gracjan




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


[Haskell-cafe] ReadP and MonadFix

2006-06-23 Thread Gracjan Polak

Hi all,

A question for hot summer day: Text.ParserCombinators.ReadP.ReadP is
an instance of Monad. Could it be an instance of MonadFix too?

I'm not that sharp in Haskell to write it myself, but it seems I could
make use of such a beast. :) Anybody willing to share?

This will also present the advantage of Lazy over Eager Parser
Combinators, mentioned in some other thread.

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


Re: [Haskell-cafe] ReadP and MonadFix

2006-06-24 Thread Gracjan Polak

Thanks for your response!

I searched for something more found: An Abstract Monadic Semantics for
Value Recursion, Eugenio Moggi, Amr Sabry

http://citeseer.ist.psu.edu/moggi03abstract.html

Section 4 of this paper says something about References and
Continuations. But it will be quite hard to translate this into actual
code. Could you please point me to the running examples you were
talking about?

I'm going to create MonadFix instance for the P monad and then I'll
see what can I achieve with that.

2006/6/23, Levent Erkok [EMAIL PROTECTED]:

Gracjan:

To declare ReadP an instance of MonadFix; you'll first have to make the P
monad into a MonadFix instance. That can be done using existing techniques
in the literature.

ReadP is essentially the continuation monad transformer wrapped around P.
It's well known in the value-recursion literature that continuation monad is
too strong to have a value-recursion operator. I am not aware of any
simple solutions in that space. Hence, ReadP is beyond the realm of
current theories of value recursion.

Having said that, I'd also like to point out that Amr Sabry and Eugenio
Moggi, and independently  Magnus Carlsson has done some interesting work to
extend value recursion to the world of continuations;



which might help with

your particular problem. Essentially, you end up adding some extra
infrastructure to your monad, and then forgo some of the basic axioms of
value recursion. But you can get running examples!

Maybe all you'll need is a MonadFix instance of P; which is definitely
doable with the current techniques. Anything further would actually make a
nice research paper...

-Levent. (I could provide references to above work if needed; all is
available on the net freely, anyhow.)


On 6/23/06, Gracjan Polak [EMAIL PROTECTED] wrote:

 Hi all,

A question for hot summer day:
Text.ParserCombinators.ReadP.ReadP is
an instance of Monad. Could it be an instance of MonadFix too?

I'm not that sharp in Haskell to write it myself, but it seems I could
make use of such a beast. :) Anybody willing to share?

This will also present the advantage of Lazy over Eager Parser
Combinators, mentioned in some other thread.

--
Gracjan
___
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] Network.CGI.Compat.pwrapper

2007-02-12 Thread Gracjan Polak

Hi,

I wanted to setup really simple http server, found Network.CGI.Compat.pwrapper
and decided it suits my needs. Code:

module Main where
import Network.CGI
import Text.XHtml
import Network

doit vars = do
return (body (toHtml (show vars)))

main = withSocketsDo (pwrapper (PortNumber ) doit)


Pointng any browser to http://127.0.0.1: does not render the page. It seems
the response headers are broken.

How do I report this bug (trac? something else?).

We might want to either fix it, or just get rid of it, as nobody seems to notice
the problem :)

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.6

Tested under WinXP and MacOSX 10.4.9.

Another question is: how do I do equivalent functionality without pwrapper?

-- 
Gracjan



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


[Haskell-cafe] Re: Network.CGI.Compat.pwrapper

2007-02-13 Thread Gracjan Polak
Bjorn Bringert bringert at cs.chalmers.se writes:
 
  Another question is: how do I do equivalent functionality without  
  pwrapper?
 
 You can roll you own web server if you want something very simple. If  
 you don't want to do that, there is a version of Simon Marlow's  
 Haskell Web Server with CGI support [1]. You could also get the  
 original HWS [2] and merge it with your program. You might also be  
 interested In HAppS [3].

Haskell Web Server seems to be the closest match. I don't want fully 
functional web server. I need more low level thing, as I need to set 
this up as a testing environment for some other (browser like) application. 
So I need a way to trigger (atrificial) errors, like protocol errors, garbage 
and broken connections.

Thanks for the response.

Is there a description what is a *CGI* protocol? 

-- 
Gracjan


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


[Haskell-cafe] Re: Network.CGI.Compat.pwrapper

2007-02-13 Thread Gracjan Polak
Bjorn Bringert bringert at cs.chalmers.se writes:
 
  Is there a description what is a *CGI* protocol?
 
 Here you go: http://hoohoo.ncsa.uiuc.edu/cgi/interface.html
 

I should be more clear: what kind of data does pwrapper expect? Somewhere in the
middle it needs two handles: one to write and one to read which seem to be
equivalent to stdin/stdout. But what about environment? How is it transfered, as
someone ale pointed out pwrapper runs on different machine?

-- 
Gracjan




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


[Haskell-cafe] Deleting list of elements from Data.Set

2008-01-30 Thread Gracjan Polak


My strictness analyser in my brain hurts. Which one (foldl,foldl',foldr) is the
best way?

Prelude Data.Set Data.List let s = fromList [1,2,3,4,5]
Loading package array-0.1.0.0 ... linking ... done.
Loading package containers-0.1.0.0 ... linking ... done.

Prelude Data.Set Data.List foldl (.) id 
(Data.List.map Data.Set.delete [1,3,5]) s
fromList [2,4]

Prelude Data.Set Data.List foldl' (.) id 
(Data.List.map Data.Set.delete [1,3,5]) s
fromList [2,4]

Prelude Data.Set Data.List foldr (.) id 
(Data.List.map Data.Set.delete [1,3,5]) s
fromList [2,4]

Which one is best?

-- 
Gracjan


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


[Haskell-cafe] Re: Deleting list of elements from Data.Set

2008-01-30 Thread Gracjan Polak
Duncan Coutts duncan.coutts at worc.ox.ac.uk writes:
 Data.List.foldr (Data.Set.delete) s [1,3,5]
 or
 Data.List.foldl' (flip Data.Set.delete) s [1,3,5]

There will be a day when I finally grasp foldr/foldl :)
 
 which is O (n + m * log m) rather than O(m * log n) or if the elements
 you're deleting are already sorted you can shave off the log m using
 Data.Set.fromAscList to get just O (n + m).

Thanks for advice. My data is sorted so the above applies really well.

-- 
Gracjan


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


[Haskell-cafe] ANN: acme-dont

2009-11-09 Thread Gracjan Polak
Hello fellow haskellers,

While reading reddit in the morning today:

http://www.reddit.com/r/programming/comments/a26fe/dont/

I was shocked and surprised to see that Haskell lacks a very important
feature present in Perl. It appeared that Haskell cannot not do
monadic actions!

I decided to act as fast as possible.

Luckily, monads enable us to create control flow constructs on
enterprise level. I'm proud to present the Acme.Dont module, that
implements the indispensable don't monadic action.

http://hackage.haskell.org/package/acme-dont-1.0

With special apologies to Luke Palmer that it took the Haskell
community 7.5 years to catch up with Perl.

Thanks go to Damian Conway.

Have fun!
Gracjan

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


[Haskell-cafe] Re: ANN: acme-dont

2009-11-09 Thread Gracjan Polak
Deniz Dogan deniz.a.m.dogan at gmail.com writes:
 
 Are you sure you want to license this as BSD?
 

Yes, BSD3 to be more exact.

Of course commercial options are available on case by case basis.

-- 
Gracjan




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


[Haskell-cafe] Re: Happstack with XML-RPC

2009-12-24 Thread Gracjan Polak
Michael Hartl mikehartl at web.de writes:
 
 BTW, what's the status of HaXR? Is it being actively developed?

Developed not. Maintained yes, by me. And you can argue that 'actively' part.

Please send patches against

darcs get http://code.haskell.org/haxr

-- 
Gracjan



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


[Haskell-cafe] The errorCalls and ioErrors in extensible exceptions way

2010-02-03 Thread Gracjan Polak

Hi all,

I have base==3.* code that uses errorCalls and ioErrors to intercept either
ErrorCall or IOError that may arise in deeper code.

I'd like to convert this code to base==4.* new exceptions.


-- | Evaluate the argument and catch error call exceptions
errorToErr :: Monad m = a - Err m a
errorToErr x = let e = unsafePerformIO (tryJust errorCalls (evaluate x))
   in ErrorT (return e)

-- | Catch IO errors in the error monad.
ioErrorToErr :: IO a - Err IO a
ioErrorToErr = ErrorT . liftM (either (Left . show) Right) . tryJust ioErrors


Look here for more context:

http://hackage.haskell.org/packages/archive/haxr/3000.5/doc/html/Network-XmlRpc-Internals.html#5

I know that just importing OldException will do the trick for now. But I'd like
to know how to do such a trick in extensible exceptions way.

Also that unsafePerformIO looks a bit scary. Isn't there a better way to achieve
purpose?

-- 
Gracjan


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


Re: [Haskell-cafe] List manipulation

2005-01-26 Thread Gracjan Polak

Dmitri Pissarenko wrote:
 Hello!

 I have two lists of Double with equal length and want to create a 
third one,
 in which each element is the sum of the corresponding element of the 
first
 list and the second list.

 If list1 is [1, 2, 100] and list2 is [2, 3, 500], then the result of the
 operation I desire is [3, 5, 600].

zipWith (+) [1,2,100] [2,3,500]

 I wrote this function

 function
 add2Img :: [Double] - [Double] - [Double]
 add2Img summand1 summand2 = sum
where sum = [ (x+y) | x - summand1, y - summand2 ]
 /function,

This is intepreted as two nestes loops: foreach x in summand1 (foreach 
y in summand2: x + y). You need zipWith.

There is GHC extension: parallel list composition to do what you want. 
Lookup GHC documentation for extensions.

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


Re: [Haskell-cafe] hFileSize vs length

2005-03-12 Thread Gracjan Polak

S. Alexander Jacobson wrote:
 I am using GHC 6.2 on windows and am finding that when I open a file and
 use hFileSize I get a different number than I get from reading in the
 file and calculating the length.  I assume this is not a bug, but I
 don't know why its happening.
Isn't that because of line end conversion? EOL on windows is \r\n (2 
bytes), when read converted on the fly to \n (1 char).

Try to open your file in binary mode.

 Also, why isn't there getFileSize function in System.Directory?
System.Posix.Files has getFileStatus and fileSize. No idea if they work 
on windows.


 -Alex-

 __
 S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.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] Data.Map

2005-04-02 Thread Gracjan Polak
Hi all,
As I tried to convert some of my code to newer libraries comming with 
GHC 6.4, I would like to share two things with you:

I noticed that there are two functions missing: deleteList and
insertList. The first one is easy with foldl:
deleteList list map = foldl (flip Data.Map.delete) map list
Second one is even shorter:
insertList asclist map = union map (Data.Map.fromList asclist)
Still I find both of them useful also execution speed seems to be of 
some concern here. Why generate temporary map just to join it with 
second in a moment? Isn't it slower?

Also why Data.Map.lookup and Data.Map.findWithDefault? Why not
lookupWithDefault?
Besides, I really like new library :)
--
Gracjan

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


Re: [Haskell-cafe] Data.Map

2005-04-03 Thread Gracjan Polak
Sebastian Sylvan wrote:
On Apr 3, 2005 9:38 AM, Gracjan Polak [EMAIL PROTECTED] wrote:

insertList asclist map = union map (Data.Map.fromList asclist)

How about:
insertList :: (Ord a) = Map a b - [(a, b)] - Map a b
insertList = foldr (uncurry insert) 

Is there any reason why foldr is better than foldl here?
/S
--
Gracjan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Speed comparison?

2005-05-04 Thread Gracjan Polak
Daniel Carrera wrote:
 Hi all,

 Thank you for all the information on my previous question. I learned a
 lot, and good pointers to more info.

 My next question is about speed. How fast would you consider Haskell?
 (say, for computational work). How would you compare it to C, Python and
 Ruby?
I started a small project in Ruby some time ago. It involved a bit of 
parsing and moving quite large binary data around. In Ruby speed was 
real problem so I looked for another language and ended up with... 
Haskell :)

Speed of GHC compiled programs is ok for me, but if you need handling of 
binaries FFI is your very good friend!

I cannot say anything about OCaml or Python, though.
--
Gracjan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Text search

2005-05-16 Thread Gracjan Polak
Hi,
Simple question: I need a function that matches string in another 
string. Something like:

find (isSuffixOf needle) (inits haystack)
This one is beautiful, but not very practical. Could anybody point me to 
some haskell library that does some searching, using KMP for example?

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


Re: [Haskell-cafe] Text search

2005-05-16 Thread Gracjan Polak
Ketil Malde wrote:
 Gracjan Polak [EMAIL PROTECTED] writes:


find (isSuffixOf needle) (inits haystack)


 Hmm...

 While the result isn't exactly the same, I suspect
 using isPrefixOf and tails would be more efficient.

I need the data before and including my needle. Like this:
( ... needle ) ignored
Or at least count of the first part. Or, best, pair of: 
(beforeandincluding,after).

String is rather long (potentially infinite), so using reverse and tail 
could be a problem :)


This one is beautiful, but not very practical.


 Unless you have very repetitive data and/or tiny alphabet, it is
 actually quite efficient, as the expected length of prefixes that need
 to be checked before a mismatch can be determined is small.

 At least, I was unable to beat it with my (feeble attempts at) BM or
 KMP implementations.

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


Re: [Haskell-cafe] Space questions about intern and sets

2005-06-02 Thread Gracjan Polak

Marcin 'Qrczak' Kowalczyk wrote:
 Gracjan Polak [EMAIL PROTECTED] writes:


intern :: Ord a = a - a
intern x = unsafePerformIO $ internIO x

iorefset :: Ord a = IORef(Map.Map a a)
iorefset = unsafePerformIO $ do
 newIORef $ Map.empty


 It will not work because you can't put values of different types as
 keys of the same dictionary, as you can't compare them.


I could have as many dictionaries as there are types. The problem is I 
get one dictionary for each object which defeats the idea.


Is there any other way to safe some memory when having many same objects?

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


Re: [Haskell-cafe] Space questions about intern and sets

2005-06-03 Thread Gracjan Polak

Scott Turner wrote:
 On 2005 June 02 Thursday 04:38, Gracjan Polak wrote:

 iorefset :: Ord a = IORef(Map.Map a a)
 iorefset = unsafePerformIO $ do
  newIORef $ Map.empty


I could have as many dictionaries as there are types. The problem is I
get one dictionary for each object which defeats the idea.


 To avoid unsafe operations and get control over the dictionaries that 
are
 created, I would put the desired dictionaries into a state monad. 
The type

 of 'intern' becomes
 Ord a = a - DictionaryState a
 All the code that uses 'intern' would need some modification to deal 
more
 directly with the dictionary state. It may be more complex, but it's 
also

 more solid.

As intern behaves like id and does not have any side effects, I thought 
its interface should be purely functional. But I do not see any way to 
do it :( I'll end up with a monad, probably.


In related question: does anybody here have experience/benchmarks/tests 
how/if is PackedString better (uses less memory) than String in parsing 
tasks?



--
Gracjan

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


Re: [Haskell-cafe] Space questions about intern and sets

2005-06-05 Thread Gracjan Polak

Duncan Coutts wrote:

On Fri, 2005-06-03 at 10:53 +0200, Gracjan Polak wrote:

As intern behaves like id and does not have any side effects, I thought 
its interface should be purely functional. But I do not see any way to 
do it :( I'll end up with a monad, probably.



In related question: does anybody here have experience/benchmarks/tests 
how/if is PackedString better (uses less memory) than String in parsing 
tasks?



GHC itself uses a rather low level thing it calls FastString which is
basically a pointer into a character array with a length and a unique
id. The unique ids are allocated by entering each FastString into a
global hash table which also provides sharing if the same string is seen
more than once (like your itern feature).


I thought FastString was first incarnation of PackedString, thanks for 
the hint it could be something more.


Does HaXml use any such optimization for XML element name handling?



It is all very low level and ghc-specific however and probably only
makes sence in a compiler-like application.


Exactly my setting.



Duncan


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


Re: [Haskell-cafe] [Newbie] Quest for inheritance

2005-06-05 Thread Gracjan Polak

Cédric Paternotte wrote:
 Hi. This is my first message here so Hello to everyone.

 I'm just starting to learn Haskell and I really think it's a cool 
language.


Me too :)

 I know OO and inheritance is not really the point of Haskell and that
 other mechanisms are provided to somewhat achieve reuse. But it's a
 way of programming I've been so used to that I feel lost without it.
 You might think I'm heading in the wrong direction. My mistake I have
 to agree. Let's take it as a learning exercise then.

Me too :)

 5. With this : 
http://www.cs.utexas.edu/ftp/pub/techreports/tr01-60/tr01-60.pdf



I've been thinking about slight generalization of this lately. Here are 
my semi-backed thoughts as of now.


First of all, in Haskell there will be strict separation between 
interfaces and data, so almost every method will be declared twice. This 
is not so strange to anybody programing in Java, but for C++ programmers 
can be. Inheritance relation is specified after data. There is also 
separation between two concepts: what interfaces each piece of data 
implements and which intefaces given interface inherits. So:


{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}

module Main where

-- general inheritance relation
class Inherits b x where
get_super :: x - b

-- declare interface with one method
class IA a where
get_a :: a - Int

-- define data with one field
data DA = DA { da_field :: Int }

-- say how data DA conforms to interface IA
instance IA DA where
get_a x = da_field x

-- declare some other interface IB
-- note: IB is unrelated to IA
class IB a where
get_b :: a - String

-- data that inherits fields of DA and adds one another field
data DB = DB { db_super :: DA, db_field :: String }

-- DB inherits fields and methods of DA
instance Inherits DA DB where
get_super x = db_super x

-- data DB implements interface IB
instance IB DB where
get_b x = db_field x

-- some other random data
data DC = DC { dc_super :: DA }

-- DC implements interface IB
instance IB DC where
get_b x = show (get_a x)

-- and inherits DA
instance Inherits DA DC where
get_super x = dc_super x

-- now the tricky part: state that every data x inheriting DA
-- implements all interfaces of DA (repeat for each interface)
instance (Inherits DA x) = IA x where
get_a w = da_field (get_super w)

main = do
let db = DB (DA 123) zzz
let dc = DC (DA 123)
putStrLn $ show (get_a db)
putStrLn $ show (get_a dc)
putStrLn $ show (get_b db)
putStrLn $ show (get_b dc)

As you see there is much more writting as in Java. But this gives better 
control over inheritance and subsumption because everything must be 
stated explicitly. Multiple inheritance is allowed :) Also it is 
private inheritance (as in C++) by default.


There are some problems left: how to update a field? or how to make 
inheritance transitive. I don't know it yet :)



 I guess my question now is this : Are there other ways to achieve
 inheritance in Haskell ?

Me too:)

My proposal (above) is about the level of 'OO' things done in procedural 
languages (example: C with GTK+ library). There must be a better way. 
Any comments?


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


[Haskell-cafe] Looking for lost library

2005-06-05 Thread Gracjan Polak


Hi,

Sorry for stupid question, but...

Some time ago I read a beautiful paper about variables that had their 
dependencies automatically tracked and could trigger recalculation when 
changed.  Prototype was implemented in OCaml, then reimplemented in 
Haskell (using monads). I would like to read that paper once again, 
but... I lost it :(


I do not remember neither title, nor authors. Google asked about any 
keywords that come to my mind do not show any interesting results. So I 
ask here :)


Can anybody help me, please? Thanks for any pointers...

--
Gracjan

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


[Haskell-cafe] foldl and space problems

2005-06-06 Thread Gracjan Polak


Hello,

My space problems continued...

I have foldl that produces list, some combining function and quite large 
source list:


let xyz = foldl f state myBigList

This setting should lazyli consume myBigList when next elements of xyz 
are demanded. Except that it seems that myBigList is held by state to 
the end of computation :(


Question: is there any way to see what is holding my source list? I did 
try to guess, but without results as of now:(


How do I debug and/or reason about such situation?

--
Gracjan

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


Re: [Haskell-cafe] [Newbie] Quest for inheritance

2005-06-06 Thread Gracjan Polak

Cédric Paternotte wrote:

Hi Gracjan,


This is smart. So I understand the point of this part is to forward
the function call to the parent (through get_super). All you have to
do is to define these forwards in each inheriting data.


Yes. I think this is the whole point of inheritance :)



Does it also mean that, in each inheriting data, you have to define
these forwards to all your parents (meaning not only to the one just
above, but all of them) ? In other words if I was to define a data DD
which inherits from DB (and thus also from DA), will I have to define
forwards for both get_a and get_b ? If not, how would you declare it ?



This is exactly what I described as private inheritance. If you have 
(Inherits DA DB) and (Inherits DB DC) this does not mean that you have 
automatically (Inherits DA DC). Why? This would require instance:


instance (Inherits a b,Inherits b c) = (Inherits a c) where ...

but this summons known problem: multiple inheritance. How to chose b? 
Imagine such situation:


data DA; data DB; data DC; data DD

instance Inherits DA DB where ...
instance Inherits DA DC where ...
instance Inherits DB DD where ...
instance Inherits DC DD where ...

DD inherits DA *twice*. So b in above instance declaration would not be 
determined uniquely.





As you see there is much more writting as in Java. But this gives better
control over inheritance and subsumption because everything must be
stated explicitly. Multiple inheritance is allowed :) Also it is
private inheritance (as in C++) by default.



I think I like this way of dealing with inheritance. There's a bit
more typing indeed and it's kind of limited but it has the advantage
of being relativily simple to put in action.


I agree with typing, but compared to Java this is actually not limited 
but more powerful, because it gives greater control over inheritance.


Most important aspect to me is that inheritance can be specified *after* 
data declaration. Imagine you have some strange library that has DA and 
DB, that are obviosly in generalization-specialization hierarchy, but 
some jerk forgot to inherit one from another. In Java you are toast, in 
Haskell you can specify inheritance relation in your code :)




What I really like with this is that you can come up with new data
types inheriting DA without having to change anything in the
declaration of DA.

I guess you'd just better avoid having too many levels of hierarchy as
it tends to get more and more verbose ;)


If you stick to single inheritance there is other way to simulate OO in 
Haskell. Look for phantom types. Whole wxHaskell (for example) is 
based on this concept.




Cédric


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


Re: [Haskell-cafe] [Newbie] Quest for inheritance

2005-06-07 Thread Gracjan Polak

Ralf Lammel wrote:

Cédric Paternotte wrote:
...

 5. With this :
http://www.cs.utexas.edu/ftp/pub/techreports/tr01-60/tr01-60.pdf


Gracjan Polak wrote:

I've been thinking about slight generalization of this lately. Here are
my semi-backed thoughts as of now.



I should have mentioned 
http://homepages.cwi.nl/~ralf/OOHaskell/src/PoorMens2/

(again *not* using OOHaskell)


From the quick skim of code:
.?. -- apply function to upcast object
.!. -- apply modification function to upcast object and substitute 
returned value (new object), basically update


Is there any description avaliable what is PoorMens2 all about?



A more general and preliminary observation:
the entire approach is potentially more about
object *composition* (and perhaps delegation) 
rather than inheritance. Many OO evangelists 
consider inheritance as a concept that was used

too much in early OO times, while object composition
is often more appropriate and flexible. So one *might*
say that this approach does not encode a Java-inheritance
solution but it does an inheritance-to-object-composition
migration on the fly. So what Gracjan calls Inherits
(and I call subtyping or substitution) is perhaps more a
delegates.


Yes, I agree with this statement. The OP question was: how to simulate 
inheritance in Haskell? One of the answers: using delegation :)




Ralf


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


[Haskell-cafe] class Ref...

2005-06-07 Thread Gracjan Polak


Hi,

I the paper of Magnu Carlsson I noticed small, interesting class:

class Monad m = Ref m r | m - r where
newRef :: a - m (r a)
readRef :: r a - m a
writeRef :: r a - a - m ()

He defined it locally, but it seems to be very useful generalization of 
IORef and STRef. Is there something like this in standard libraries? I 
couldn't find it... :( Is there any reason why isn't it included?


Another question: priority queue. In libraries bundled with ghc we have 
Data.Queue, but I couldn't find PriorityQueue. Is there somewhere an 
implementation that everybody uses, but is not in the library?


Thanks!

--
Gracjan

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


Re: [Haskell-cafe] foldl and space problems

2005-06-07 Thread Gracjan Polak

Bernard Pope wrote:


A more practical solution is to force the compiler to generate more
strict code. 


I tried to put strictness annotation in every place I could think of. 
Without result :(




You might also find GHood useful:

http://www.cs.kent.ac.uk/people/staff/cr3/toolbox/haskell/GHood/


Thanks for the pointer.



Cheers,
Bernie.


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


Re: [Haskell-cafe] class Ref...

2005-06-07 Thread Gracjan Polak

Bulat Ziganshin wrote:

Hello Gracjan,

Tuesday, June 07, 2005, 2:25:50 PM, you wrote:
class Monad m = Ref m r | m - r where
GP  newRef :: a - m (r a)
GP  readRef :: r a - m a
GP  writeRef :: r a - a - m ()

may be the following will be even more interesting:



I like it very much!


import Control.Monad
import Data.IORef

infixl 0 =:, +=, -=, =::, =
ref = newIORef
val = readIORef
a=:b = writeIORef a b


Pretty shame := is already reserver :(. There is something alike 
Graphics.Rendering.OpenGL.GL.StateVar. The use $= for assignment. 
Generalizing variables (in respect to some monad) seems to be often 
reinvented idea :)


As I see this could be generalized to all Ref-like constructs 
(IO,ST,others?)



a+=b = modifyIORef a (\a- a+b)
a-=b = modifyIORef a (\a- a-b)
a=::b = ((a=:).b) = val a

Is this convoluted modify? Why doesn't it use modifyIORef? Or am I wrong?


for :: [a] - (a - IO b) - IO ()
for = flip mapM_


I like:

foreach = flip mapM
foreach_ = flip mapM_



newList = ref []
list = x   =  list =:: (++[x])

Is this append?


push list x  =  list =:: (x:)
pop list =  do x:xs-val list; list=:xs; return x

main = do
  sum - ref 0
  lasti - ref undefined
  for [1..5] $ \i - do
sum += i
lasti =: i
  sum =:: (\sum- 2*sum+1)
  print = val sum
  print = val lasti

  xs - newList
  for [1..3] (push xs)
  xs = 10
  xs = 20
  print = val xs



Haskell as ultimate imperative language :)




I use this module to simplify working with references in my program.
The first inteface can be used for IORef/STRef/MVar/TVar and second
for lists and Chan



Then we should create classes for those interfaces.

--
Gracjan

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


Re: [Haskell-cafe] class Ref...

2005-06-08 Thread Gracjan Polak

Tomasz Zielonka wrote:

On Tue, Jun 07, 2005 at 12:25:50PM +0200, Gracjan Polak wrote:

Another question: priority queue. In libraries bundled with ghc we have 
Data.Queue, but I couldn't find PriorityQueue. Is there somewhere an 
implementation that everybody uses, but is not in the library?



You can use the new Data.Map module for this (old Data.FiniteMap too,
but a bit more clumsily), it has findMin, findMax, deleteFindMin,
deleteFindMax, deleteMin, deleteMax. All these operations should have
O(log N) cost.


Wow, I did not think about this.

As far as I remember in imperative world priority queues had special 
implementation, with very good O() characteristics. Is O(log N) the best 
thing that can bo done in pure functional setting?


To put it another way: is Data.Map only workaround to get something 
done, or is it The Right Way of doing PQs in Haskell?




Best regards
Tomasz


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


Re: [Haskell-cafe] Space questions about intern and sets

2005-06-08 Thread Gracjan Polak

Bjorn Bringert wrote:

memory. Here is something I wrote, but it doesn't work :(




I must have been doing something really wrong that day, because today it 
works smoothly... :)




The code below seems to work for strings, and should be generalizable to 
any type for which you have a hash function:


import Data.HashTable as H
import System.IO.Unsafe (unsafePerformIO)

{-# NOINLINE stringPool #-}
stringPool :: HashTable String String
stringPool = unsafePerformIO $ new (==) hashString

{-# NOINLINE shareString #-}
shareString :: String - String
shareString s = unsafePerformIO $ do
mv - H.lookup stringPool s
case mv of
Just s' - return s'
Nothing - do
   H.insert stringPool s s
   return s



Very interesting, thanks!

It seems very similiar to your code, except that it uses HashTable 
instead of Map.


Question is: which one is better? My tupicall file contains 16 
tokens, where 95% is taken by about 20 tokens that are used very frequently.




/Björn


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


Re: [Haskell-cafe] Space questions about intern and sets

2005-06-09 Thread Gracjan Polak

Udo Stenzel wrote:

Gracjan Polak wrote:


iorefset :: Ord a = IORef(Map.Map a a)
iorefset = unsafePerformIO $ do
   newIORef $ Map.empty


I could have as many dictionaries as there are types. The problem is I 
get one dictionary for each object which defeats the idea.



I believe the (Ord a) constraint acts like a function argument.
Therefore iorefset is no CAF, cannot be memoized itself and you get one
dictionary per invocation.  On the other hand, that is what is to be
expected when playing games with unsafePerformIO.


Seems you are right. Monomorphic type works, polymorphic doesn't. But it 
probably is not in any way guaranteed to stay like this in future.




You might get it working by giving iorefset a monomorphic type or by
specializing it for the type(s) you are using it at.  Don't forget the
NOINLINE pragma.  I wouldn't do it this way, though.  If you're parsing,
chances are that your code is monadic anyway.  Put a StateT over the
parser monad and everything works without black magic.  Even better, if
you're using parsec you can just put the Map in the user state.



This will create intern-per-parse, which isn't bad and has it's 
advantages, but I wanted to do something global. Anyway it was 
interesting experiment :)




Udo.


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


Re: [Haskell-cafe] class Ref...

2005-06-13 Thread Gracjan Polak



David Menendez wrote:
[many things deleted]...



I think the best way to look at MonadRef is as a generalization of
MonadState. 


This could be a way to transliterate (not translate, transliterate) many 
imperative programs to Haskell. And as such this could be a starting 
point for many imperative souls into functional liberation :)


I do not think that, for beginners, limitation to Hugs or GHC is serious 
problem.


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


[Haskell-cafe] Garbage collection and finalizer thread priority

2005-06-13 Thread Gracjan Polak


Hi,

My space problems continued... :)

I have some ForeignPtr's, with finalizers (finalizerFree only). And I 
have lazyly produced list of those (yes, there is some unsafePerformIO 
magic behind, but I think I got this right). The problem is I get 
out-of-memory condition because elements get produced faster than those 
consumed are garbage collected.


Example:

list = ...
mapM_ writeOut list

writeOut :: Ptr Word8
writeOut dat = do
hPutBuh handle dat 1024
-- Control.Concurrent.threadDelay 1000

Uncommenting this line allows gc thread to run finalizers, memory gets 
freed, everything runs smoothly...


As far as I know finalizers are run in separate thread. How do I 
increase priority of this thread so it runs faster?


--
Gracjan

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


Re: [Haskell-cafe] foldl and space problems

2005-06-13 Thread Gracjan Polak

Bernard Pope wrote:

Perhaps you could post the definition of the state type? Or even better,
a small example of code that runs badly.


I still don't know where old code had problems, but after rewriting 
everything it seems to run smoothly now :) Thanks for all ideas, btw.


I invented something like this:

type RestAndState = (MyState - [MyData]) - MyState - [MyData]

this is the type of funtions that take current state and continuation as 
parameters. Example:


putValues v1 v2 v3 rest state =
[v1,v2,v3] ++ rest state

there is a bit of syntactic ugliness when state chages:

putValueEx v1 rest state =
let newstate = state { ... } in
[v1] ++ rest nstate

good thing is that function can be composed quite easily with ($):

putV v1 v2 v3 v4 rest = -- state skipped here :)
putValue v1 v2 v3 $
putValueEx v4 rest


It works as I want it to. But I have strange feeling that there must be 
a better way to compose foldr and state... Does anybody have any idea 
how to put monad into this?


--
Gracjan

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


Re: [Haskell-cafe] Garbage collection and finalizer thread priority

2005-06-13 Thread Gracjan Polak

Simon Marlow wrote:


I presume you're running GHC.  There's no way to increase the priority
of a thread - GHC's scheduler doesn't have a concept of priorities.



Yes, I forgot to state it explicitly.


I would look into whether you can use mallocForeignPtr: this is much
faster than using newForeignPtr with finalizerFree, because the memory
is garbage collected directly and there's no need for a finalizer.


I use mallocBytes + reallocBytes + addForeignPtrFinalizer finalizerFree. 
 I wouldn't think this is any different, thanks for your suggestion.


May I ask where that difference comes from?

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


Re: [Haskell-cafe] Garbage collection and finalizer thread priority

2005-06-14 Thread Gracjan Polak

Sebastian Sylvan wrote:

On 6/13/05, Simon Marlow [EMAIL PROTECTED] wrote:



I presume you're running GHC.  There's no way to increase the priority
of a thread - GHC's scheduler doesn't have a concept of priorities.




Just out of curiousity, what scheme does GHC use for scheduling threads?


As I read somewhere, round robin...

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


Re: [Haskell-cafe] Garbage collection and finalizer thread priority

2005-06-14 Thread Gracjan Polak

Simon Marlow wrote:

On 13 June 2005 11:30, Gracjan Polak wrote:



My space problems continued... :)


Follow up :)



I have some ForeignPtr's, with finalizers (finalizerFree only). And I
have lazyly produced list of those (yes, there is some unsafePerformIO
magic behind, but I think I got this right). The problem is I get
out-of-memory condition because elements get produced faster than
those consumed are garbage collected.

Example:

list = ...
mapM_ writeOut list

writeOut :: Ptr Word8
writeOut dat = do
hPutBuh handle dat 1024
-- Control.Concurrent.threadDelay 1000



This sould be:

writeOut :: Ptr Word8
writeOut dat = do
 hPutBuh handle dat 1024
 System.Mem.performGC
 Control.Concurrent.threadDelay 1000


My small experimets show, that gc is not triggered?!?! What are the 
conditions to trigger gc? As I read the docs, is some % of heap. Is 
mallocForeinPtrBytes counted into that %?


Anyway I ended up triggering GC by hand and giving it time to run 
finalizers. Frankly speaking this is nonsolution:(


Related question:

Documentation says:
 -Msize
[Default: unlimited] Set the maximum heap size to size bytes. The 
heap normally grows and shrinks according to the memory requirements of 
the program...


GHC 6.4 says:
Heap exhausted;
Current maximum heap size is 268435456 bytes (256 Mb);
use `+RTS -Msize' to increase it.

What am I missing?

PS: I might be mistaken in any of above statements. I'll be thankful for 
any light... :)


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


Re: [Haskell-cafe] Garbage collection and finalizer thread priority

2005-06-14 Thread Gracjan Polak

Bulat Ziganshin wrote:

Hello Gracjan,

Tuesday, June 14, 2005, 1:29:09 PM, you wrote:
GP Documentation says:
GP   -Msize
GP  [Default: unlimited] Set the maximum heap size to size bytes. The 
GP heap normally grows and shrinks according to the memory requirements of 
GP the program...


GP GHC 6.4 says:
GP Heap exhausted;
GP Current maximum heap size is 268435456 bytes (256 Mb);
GP use `+RTS -Msize' to increase it.

it's an error in GHC 6.4/win32


:)

How do I take care of that?

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


[Haskell-cafe] Conversion between MonadPlus instances

2005-07-01 Thread Gracjan Polak



Hi all,

A simple question for advanced Haskellers, but I still have some 
problems bending my mind over it.


Example: I have some function, that can return multiple results. 
Currently I need only the first one, but in the spirit of NotJustMaybe, 
I try to be as general as possible.


If I code it like this:

reduction :: (MonadPlus m) = [Rule] - Expr - m Expr
reduction expr = do
rule - rules
reduction rule expr

Variable m gets unified with []. But I want m to stay as general as 
possible here.


This version works, but I somehow do not like the smell of it

reduction expr = do
let listmonad = do
rule - rules
reduction rule expr
msum (map return listmonad)

Is there a better way how to embed MonadPlus in other MonadPlus?

--
Gracjan

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


Re: [Haskell-cafe] FFI and callbacks

2005-08-22 Thread Gracjan Polak

Duncan Coutts wrote:


Most toolkits with a main loop system allow you to setup timers. In the
Gtk2Hs bindings we can use this trick:

-- 50ms timeout, so GHC will get a chance to scheule about 20 times a second
-- which gives reasonable latency without the polling generating too much
-- cpu load.
timeoutAddFull (yield  return True) priorityDefaultIdle 50



Just for the record, above line in wxHaskell is spelled as:

timer mainWindow [ interval := 50, on command := return () ]

By the way, thanks for this tip! This helped me to work around 
showstopper bug in my program :)


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


[Haskell-cafe] Template Haskell and Types

2005-09-12 Thread Gracjan Polak


Hi,

Probably very simple question about template haskell: How do I make a 
type for an argument to splice? Example:


data MyData = MyData1 | MyData2

mysplice mytype =
   [| litE $ stringL $ show mytype |]

main = do
   putStrLn $(mysplice MyData)


The above is not accepted, error:

Compiling Main ( thtest.hs, thtest.o )

thtest.hs:51:34: Not in scope: data constructor `MyData'

So how do I provide type as an argument?

Besides: documentation that I found for th is very dated. Could somebody 
point me to something more up to date about th? Thanks!


--
Gracjan

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


Re: [Haskell-cafe] Template Haskell and Types

2005-09-13 Thread Gracjan Polak

Tomasz Zielonka wrote:

On Mon, Sep 12, 2005 at 12:08:14PM +0200, Gracjan Polak wrote:

Probably very simple question about template haskell: How do I make a 
type for an argument to splice? Example:


data MyData = MyData1 | MyData2

mysplice mytype =
  [| litE $ stringL $ show mytype |]

main = do
  putStrLn $(mysplice MyData)



Cale explained how you can quote types in general. In the special case
when you simply want the Name of a type-constructor, you can use the ''
quoting syntax:

putStrLn $(mysplice ''MyData)



Thanks for responses. Is there any up-to-date documentation avaliable?


Best regards
Tomasz


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


Re: [Haskell-cafe] Template Haskell and Types

2005-09-13 Thread Gracjan Polak

Simon Peyton-Jones wrote:

|  putStrLn $(mysplice ''MyData)
| 
| 
| Thanks for responses. Is there any up-to-date documentation avaliable?


Template Haskell is, alas, poorly documented.  I would really welcome
someone to volunteer to help write better documentation.  Meanwhile, as
the user manual says, the stuff about quoting names is described in a
design note http://research.microsoft.com/~simonpj/tmp/notes2.ps


Thanks. With haddoc documentation it is quite easy to translate old 
names to new names and guess the meanning of others.


Next quiestion is: how do I debug my macros? When I make some error in 
my program, I get coredump (or the windows equivalent)?



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


[Haskell-cafe] TH Q Monad and fail

2005-09-20 Thread Gracjan Polak


Hi all,

The Q Monad in template haskell has fail method. As I understand it, it 
throws some kind of exception. How do I catch this exception?


Some code I'm trying to create:

infoToCode :: Info - Q Exp
infoToCode (ClassI dec) = -- ClassI Dec
fail ClassI not supported -- this will be implemented
infoToCode (ClassOpI name xtype name2 fixity) = -- ClassOpI Name Type 
Name Fixity

fail ClassOpI not supported
infoToCode (TyConI dec) = -- TyConI Dec
fail TyConI not supported
infoToCode (PrimTyConI name int bool) = -- PrimTyConI Name Int Bool
fail PrimTyConI not supported
infoToCode (DataConI name xtype name2 fixity) = -- DataConI Name Type 
Name Fixity

fail DataConI not supported
infoToCode (VarI name xtype maybedec fixity) = -- VarI Name Type (Maybe 
Dec) Fixity

fail TVarI not supported
infoToCode (TyVarI name xtype) = -- TyVarI Name Type
fail TyVarI not supported


nameToCode1 :: Name - Q Exp
nameToCode1 name = do
info - reify name
Code - infoToCode info
runIO $ putStrLn $ pprint Code
return Code

-- Here be dragons...

nameToCode name = nameToCode1 name `catch` c
where c e = do
runIO $ putStrLn $ show e
fail refailed


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


Re: [Haskell-cafe] Template Haskell and Types

2005-09-20 Thread Gracjan Polak

Simon Peyton-Jones wrote:

design note http://research.microsoft.com/~simonpj/tmp/notes2.ps



In the above paper there is something about 'giveUp'. Seems to quite 
useful, but there is no such thing in ghc 6.4.


Where did my giveUp go? And why?

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


Re: [Haskell-cafe] Template Haskell and Types

2005-09-26 Thread Gracjan Polak

Simon Peyton-Jones wrote:

Hmm.  Q is a monad, so I think
fail :: Monad m = String - m a
will do the job.

'recover' should catch the exception, and let you try something else.


So I think I have bug report :)

Haskell-cafe is probably wrong place for this, where do I go now with my 
failing test cases?


--
Gracjan



Simon

| -Original Message-
| From: Gracjan Polak [mailto:[EMAIL PROTECTED]
| Sent: 20 September 2005 10:43
| To: Simon Peyton-Jones
| Cc: haskell-cafe@haskell.org
| Subject: Re: [Haskell-cafe] Template Haskell and Types
| 
| Simon Peyton-Jones wrote:

|  design note http://research.microsoft.com/~simonpj/tmp/notes2.ps
| 
| 
| In the above paper there is something about 'giveUp'. Seems to quite

| useful, but there is no such thing in ghc 6.4.
| 
| Where did my giveUp go? And why?
| 
| --

| Gracjan


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


[Haskell-cafe] Template Haskell -- Bug?

2005-10-20 Thread Gracjan Polak


Hi,

Could somebody try to compile these two files *TWICE*? GHC dumps core at 
me. I don't know if it is something about me, or something more general 
:) I'd like to know a bit more, before I bother anybody from devel team.


Log:

$ ghc --make THTest1.hs
Chasing modules from: THTest1.hs
Compiling THTest1TH( ./THTest1TH.hs, ./THTest1TH.o )
Compiling THTest1  ( THTest1.hs, THTest1.o )

THTest1.hs:10:4: `incrSelf' is not a (visible) method of class `IncrSelf'

$ ghc --make THTest1.hs
Chasing modules from: THTest1.hs
Skipping  THTest1TH( ./THTest1TH.hs, ./THTest1TH.o )
Compiling THTest1  ( THTest1.hs, THTest1.o )
Loading package base-1.0 ... linking ... done.
Loading package haskell98-1.0 ... linking ... done.
Loading package template-haskell-1.0 ... linking ... done.
(here core dump, aka 0xc0001)



First of all, I do not understand the error in first compilation. 
Second, core dump is not nice :)


My config:

Windows XP Home,

$ ghc -v
Glasgow Haskell Compiler, Version 6.4, for Haskell 98, compiled by GHC 
version 6.2.2

Using package config file: c:\ghc\ghc-6.4\package.conf
Using package config file: C:\Documents and Settings\gracjan\Application 
Data\ghc/i386-mingw32-6.4/package.conf


Default windows package as taken from www.haskell.org.

--
Gracjan


{-# OPTIONS -fglasgow-exts -fth -fallow-undecidable-instances #-}


module THTest1TH
(
  instanceIncrSelfTuple,
  IncrSelf(..)
)
where
import Control.Monad
import Data.Maybe
import Language.Haskell.TH

class IncrSelf a where
incrSelf :: a - a

instance Num a = IncrSelf a where
incrSelf x = x + 1



sel' :: Int - Int - ExpQ
sel' i n = lamE [pat] rhs
where pat = tupP (map varP as)
  rhs = varE (as !! (i - 1))
  as = map mkName [ (a__ ++ show j) | j - [1..n] ]


instanceIncrSelfTuple :: Int - Q [Dec]
instanceIncrSelfTuple n = do
 decs - qOfDecs
 let listOfDecQ = map return decs
 conIncrSelf = conT ''IncrSelf
 name_a = mkName a
 name_b = mkName b
 name_c = mkName c
 var_a = varT name_a
 var_b = varT name_b
 var_c = varT name_c
 dec - instanceD (sequence [appT conIncrSelf var_a,appT conIncrSelf var_b])
(appT conIncrSelf
  (appT
 (appT (tupleT 2)
   var_a
 )
 var_b
   )
 )
listOfDecQ
 return [dec]
 where qOfDecs = [d|
incrSelf value =
let
value1 = maybe Nothing (Just . fst) value
value2 = maybe Nothing (Just . snd) value
in error adfasf -- (incrSelf value1, incrSelf value2)
|]



{-# OPTIONS -fglasgow-exts -fth -fallow-undecidable-instances  #-}

module THTest1
where
import THTest1TH


instance IncrSelf String where
incrSelf x = x ++ x

$(instanceIncrSelfTuple 2)


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


Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-11-19 Thread Gracjan Polak
2005/11/19, Benjamin Franksen

 [You should read some of his papers, for instance the most unreliable
 techique in the world to compute pi. I was ROTFL when I saw the title
 and reading it was an eye-opener and fun too.]


Care to post a link? Seems interesting, but unknown to google :)

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


[Haskell-cafe] hPutStrLn and hFlush

2006-01-09 Thread Gracjan Polak
Hi all,A bit strange behaviour with hPutStrLn. Consider following program:main = do handle - openFile output.txt WriteMode hPutStrLn handle (unlines contLines2) -- hFlush houtput
 where contLines2 = flip map [1..2000] $  \x - show x ++  been there done thatOutputs file which ends with following lines:1989 been there done that1990 been there done that
1991 been there done that1992 been there done that199(END)So the output is truncated. When I uncomment hFlush, file is fully written. Is this expected/documented behaviour?Platform: WinXP, GHC version 
6.4.1-- Regards,Gracjan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] hPutStrLn and hFlush

2006-01-09 Thread Gracjan Polak
Thanks for the answers. I can go with hFlush or hClose, no problem here. Anyway this is a bit surprising that default stdout behaves different than file opened with default options. -- Gracjan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell to call Microsoft COM (Dispatch)

2006-01-30 Thread Gracjan Polak
Hi all,Is there any library to make Haskell call Microsoft COM functions using Dispatch? E.g I don't need the full COM binary functionality, scripting is enough. Google didn't seem to find anything interesting... beside rolling my own using FFI :)
Thanks in advance!-- Gracjan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell to call Microsoft COM (Dispatch)

2006-01-31 Thread Gracjan Polak
2006/1/30, Paul Moore [EMAIL PROTECTED]:
On 1/30/06, Gracjan Polak [EMAIL PROTECTED] wrote: Is there any library to make Haskell call Microsoft COM functions using Dispatch? E.g I don't need the full COM binary functionality, scripting is
 enough. Google didn't seem to find anything interesting... beside rolling my own using FFI :)I believe that HDirect allows you to do this. Unfortunately, I don'tknow of a binary build of a recent version, and I have yet to manage
to build it myself :-(Latest version is from January 2004, hierarchical library layout has changed a bit since then :( It doesn't compile for me, either.Anyway it seems to be a bit of overkill for what I want to do.
I'm not aware of any other libraries to do this.Thanks for the pointer! 
Paul.-- Gracjan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Embedded scripting Language for haskell app

2010-08-17 Thread Gracjan Polak
Bulat Ziganshin bulat.ziganshin at gmail.com writes:

 
 Hello Hemanth,
 
 Tuesday, August 17, 2010, 2:05:44 PM, you wrote:
 
 btw, i've written unfinished hslua tutorial:
 http://haskell.org/haskellwiki/HsLua
 

And in related news embedded Lua interpreter recently got upgraded
to version 5.1.4.

-- 
Gracjan


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


[Haskell-cafe] Re: Error Calling Lua Function

2010-10-23 Thread Gracjan Polak

Change this:

succ - Lua.loadfile l /Haskell2Lua.lua

into

succ - Lua.loadfile l Haskell2Lua.lua

Note that 0 at the beginning says there was an error loading a script.

I should make it an exception I guess...

-- 
Gracjan


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


[Haskell-cafe] Re: Converting Values Between Lua And Haskell

2010-10-25 Thread Gracjan Polak
aditya siram aditya.siram at gmail.com writes:
 
 I was fooled :). Some indication of that on the page would be very
 helpful.-deech

Bulat was dreaming about better Lua support, but since the thing fulfilled
my purpose, Bulat's dreams never got implemented.

Aditya, I'm eager to accept patches, if you produce some :)

-- 
Gracjan


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


[Haskell-cafe] Re: What's the problem with iota's type signature?

2009-05-28 Thread Gracjan Polak
michael rice nowgate at yahoo.com writes:

 I've been digging into this stuff for months and it's still tripping me up.

For exploration use GHCi. It can tell you the type of thing you have written. It
has command to tell you type of thing, the :t. See here:

Prelude let double x = Just (x + x)
Prelude :t double
double :: (Num a) = a - Maybe a

Prelude let iota n = [1..n]
Prelude :t iota
iota :: (Num t, Enum t) = t - [t]

Prelude [3,4,5] = iota
[1,2,3,1,2,3,4,1,2,3,4,5]

You don't have to guess then, Haskell compiler can do the guessing for you. It
is called type inference.

-- 
Gracjan


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


[Haskell-cafe] Don't “accidentallyparallelize”

2009-09-05 Thread Gracjan Polak

Hi all,

In DEFUN 2009: Multicore Programming in Haskell Now!
(http://donsbot.wordpress.com/2009/09/05/defun-2009-multicore-programming-in-haskell-now/),
slide 30 I see:

Don't “accidentally parallelize”:
– f `par` f + e

and that the correct way of achieving parallelism is:
– f `par` e `pseq` f + e

Actually I don't understand the difference between these two forms. Could any
brave soul explain it to me, please?

As a bonus question: what is the difference between `seq` and `pseq`?

-- 
Gracjan


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


[Haskell-cafe] Re: Don't “accidentallyparallelize”

2009-09-05 Thread Gracjan Polak

Thanks for great response!

Brent Yorgey byorgey at seas.upenn.edu writes:
 
 x `pseq` y guarantees to evaluate x before y.  There is no such
 guarantee with x `seq` y; the only guarantee with `seq` is that x
 `seq` y will be _|_ if x is.
 


I found an old thread here
http://www.mail-archive.com/glasgow-haskell-us...@haskell.org/msg11022.html

where Simon states

[quote]
Indeed, if GHC was in the habit of causing the second argument of seq to be
evaluated before the first, then a lot of people would probably be surprised.
eg. imagine what happens to foldl':

  foldl' f a [] = a
  foldl' f a (x:xs) = let a' = f a x in a' `seq` foldl' f a' xs

It wouldn't do what you want at all.
[/quote]

So... seems foldl' relies on `seq` having unstated evaluation order in GHC. 
So, what guarantees does foldl' have in turn? Semantics only or operational?
Shouldn't it be written using `pseq`?

Seems I have always used (this `seq` that) when I meant (this `before` that).
Is it time to revisit my code and use `pseq` more? 
What does Haskell' say about this?

-- 
Gracjan




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


[Haskell-cafe] Re: Don't “accidentallyparallelize”

2009-09-06 Thread Gracjan Polak
Dan Doel dan.doel at gmail.com writes:
 On Sunday 06 September 2009 2:18:31 am David Menendez wrote:
  
  It turns out, pseq limits the effectiveness of strictness analysis,
  because it forces the order of evaluation. John Meacham described this
  pretty well last week in the Haskell' list
  http://www.haskell.org/pipermail/haskell-prime/2009-August/003006.html.
 
 Interesting. I hadn't thought of this before, but it certainly makes sense.

Thank to all of you! This thread is fascinating! :)

I used `seq` to duct tape my space leaks and stack overflow issues. Now
looked for `pseq` for parallelism. And I think I understand enough to use
both reasonably.

Thanks!
Gracjan

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


[Haskell-cafe] Optimizing 'sequence'

2008-07-21 Thread Gracjan Polak

Hi all,

On the other day I noticed that we could optimize 'sequence' more.
I needed it for my monadic parser. Below is my small experiment.
Sequence from standard library needs 2.3s to finish (and additional
stack space), my version uses only 0.65s and default stack.

Is my version better or am I missing something obvious?

-- standard
sequence1   :: Monad m = [m a] - m [a]
sequence1 ms = foldr k (return []) ms
where
  k m m' = do { x - m; xs - m'; return (x:xs) }

-- accumulator version
sequence2   :: Monad m = [m a] - m [a]
sequence2 ms = sequence' [] ms
where
sequence' vs [] = return (reverse vs)
sequence' vs (m:ms) = m = (\v - sequence' (v:vs) ms)

main = do
let l = map return [1..100]
w - sequence1 l
print (sum w)
return ()

[EMAIL PROTECTED]:~/some_faster time ./Some1 +RTS -K100M
5050

real0m2.318s
user0m2.284s
sys 0m0.032s


[EMAIL PROTECTED]:~/some_faster time ./Some2
5050

real0m0.652s
user0m0.592s
sys 0m0.052s

--
Gracjan


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


[Haskell-cafe] Re: Optimizing 'sequence'

2008-07-22 Thread Gracjan Polak
Antoine Latter aslatter at gmail.com writes:
 
 The function runIdentity is found in Control.Monad.Identity in the
 mtl package.
 

Thanks, I see it now! Laziness is not there!

But still... Identity is a bit special monad. What other monads need full
laziness in sequence? As far as I know IO is strict. What about lazy/strict
state monad?

Initially I spotted this possible optimization in context of monadic parser. I
am not really sure if I need this property there or not. How do I prove this to
myself?

Thanks to others who responded.

-- 
Gracjan


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


[Haskell-cafe] Re: Optimizing 'sequence'

2008-07-23 Thread Gracjan Polak
Chaddaï Fouché chaddai.fouche at gmail.com writes:
 2008/7/22 Luke Palmer lrpalmer at gmail.com:
  A little formal reasoning reveals that sequence1 = sequence2 exactly
  when (=) is strict in its left argument.  There are four common
  monads which are _not_: Identity, Reader, Writer, State (and RWS by
  extension).
 
 Still if that makes that much of a difference, maybe we could envision
 putting a sequence' in the library ?
 

Yes, in my experiments this is to be or not to be. Stack space is limited. 
Also processing time goes down by 800%, so it is a big deal sometimes.

Incomplete list of functions affected:

sequence
mapM
foldM
Text.ParserCombinators.Parsec.Combinator(many1,sepBy,endBy,manyTill)
Text.ParserCombinators.ReadP(many,many1,count,sepBy,endBy,manyTill)
...

As far as I know sequence could be specialized to IO monad and use my
transformation.

How do I reason if = for parsers is lazy in its first argument?

-- 
Gracjan


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


[Haskell-cafe] Re: language proposal: ad-hoc overloading

2008-09-01 Thread Gracjan Polak
Philippa Cowderoy flippa at flippac.org writes:
   Haskell already has one method of overloading: type classes. What you
   propose is a seemingly innocent extension that I now doubt has
   extremely far-reaching consequences into the language. Such a feature
   should be properly researched before it is added to the language.

http://homepages.dcc.ufmg.br/~camarao/CT/

-- 
Gracjan


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


Re: [Haskell-cafe] Re: Hugs vs GHC (again)

2005-01-11 Thread Gracjan Polak

Marcin 'Qrczak' Kowalczyk wrote:

 fileRead :: File - FileOffset - Integer - Buffer - IO ()

 This is unimplementable safely if the descriptor is read concurrently
 by different processes. The current position is shared.

UNIX98 defines function:
extern ssize_t pread (int __fd, void *__buf, size_t __nbytes,
  __off_t __offset);
Windows has:
BOOL ReadFile(
  HANDLE hFile,
  LPVOID lpBuffer,
  DWORD nNumberOfBytesToRead,
  LPDWORD lpNumberOfBytesRead,
  LPOVERLAPPED lpOverlapped
);
Where that OVERLAPPED structure contains information where to start read.
Seems implementable to me, or am I wrong?
--
Gracjan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Hugs vs GHC (again) was: Re: Somerandomnewbiequestions

2005-01-11 Thread Gracjan Polak

Simon Marlow wrote:
 There's a big lock on File.  If you want to do truly concurrent reading,
 you can make multiple FileInputStreams, each of which has its own file
 descriptor (the Unix implementation uses dup(2)).

Original and descriptor returned by dup or dup2 share file pointer.
--
Gracjan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Linear shuffle

2005-01-14 Thread Gracjan Polak
Hi,
I want to implement linear list shuffle in Haskell 
(http://c2.com/cgi/wiki?LinearShuffle) and I invented code:

shuffle :: [a] - IO [a]
shuffle [] = return []
shuffle x = do
r - randomRIO (0::Int,length x - 1)
s - shuffle (take r x ++ drop (r+1) x)
return ((x!!r) : s)
This algorithm seems not effective, length, take, drop and (!!) are 
costly. Is there any better way to implement shuffle?

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


Re: [Haskell-cafe] Linear shuffle

2005-01-14 Thread Gracjan Polak

Henning Thielemann wrote:
Is it a good idea to use IO monad for this plain computation?
It is needed as random number supply.
--
Gracjan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Linear shuffle

2005-01-14 Thread Gracjan Polak

John Meacham wrote:
 Oleg wrote a great article on implementing the perfect shuffle. with
 some sample code.

 http://okmij.org/ftp/Haskell/misc.html#perfect-shuffle

Thats the kind of answer I was hoping to get :) Thanks.
shuffle could be useful in standard library. At least Python has it. I 
was translating some small Python program, the hardest part was the 
missing shuffle function. What do you think?

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


[Haskell-cafe] Control.Monad.State.Strict, mdo and let

2007-05-28 Thread Gracjan Polak

Hi,

I stumbled at some interaction of Control.Monad.State.Strict, mdo and let I do
not understand. The following program:


{-# OPTIONS_GHC -fglasgow-exts #-}
module Main where
import Control.Monad.State.Strict

thenumber :: Float
thenumber = flip execState 1.3 $ mdo
c - donothing []  
let donothing x = return x
return ()

main = print thenumber

Says (in GHC 6.6.1):

Stack space overflow: current size 8388608 bytes.
Use `+RTS -Ksize' to increase it.

Why is this so?

-- 
Gracjan


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


[Haskell-cafe] ANN: Scripting.Lua 0.1

2007-06-26 Thread Gracjan Polak

Hi all,

I'm pleased to announce the first public release of Scripting.Lua.

The package hslua-0.1 contains Haskell FFI bindings for a Lua interpreter
along with some Haskell utility functions simplifying Haskell to Lua and
Lua to Haskell calls. Full Lua interpreter is included in the package.

Example

 import qualified Scripting.Lua as Lua

 main = do
 l - Lua.newstate
 Lua.openlibs l
 Lua.callproc l print Hello from Lua
 Lua.close l

More information

 http://home.agh.edu.pl/~gpolak/hslua

The Lua language
   
 http://www.lua.org

--
Gracjan


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


[Haskell-cafe] Re: ANN: Scripting.Lua 0.1

2007-06-26 Thread Gracjan Polak
Donald Bruce Stewart dons at cse.unsw.edu.au writes:

 
 Great work! would you like to upload it to hackage.haskell.org too, so
 it will be archived for the ages?
 


I surely will, but I'd like to wait a moment and first see what people say :)

-- 
Gracjan\

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


[Haskell-cafe] Re: ANN: Scripting.Lua 0.1

2007-06-27 Thread Gracjan Polak
Andrea Rossato mailing_list at istitutocolli.org writes:

 I quote: this is a really nice news. I'll be trying to use it in
 project of mine very soon (I'm developing a sort of Ion3 like status
 bar, which is scriptable through Lua).

Exactly such a scenario I had in mind. Calling Lua from Haskell was easy, the
hard part was to call Haskell from Lua. 

Give me a sign how it worked.

 
 Please follows Donald's suggestion and upload it on Hackage.

Uploaded. 

-- 
Gracjan




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


[Haskell-cafe] Re: Comments from OCaml Hacker Brian Hurt

2009-01-16 Thread Gracjan Polak
Ketil Malde ketil at malde.org writes:
 
 On Thu, Jan 15, 2009 at 07:46:02PM +, Andrew Coppin wrote:
 
  If we *must* insist on using the most obscure possible name for  
  everything, 
 
 I don't think anybody even suggests using obscure names.  Some people
 insist on precise names.  
 

Ketil, to second your here: Appendable *is* an obscure name! Even more
 
than Monoid.

I remember my early CS algebra courses. I met cool animals there: Group,

Ring, Vector Space. Those beasts were very strong, but also very calm at
the same time. Although I was a bit shy at first, after some work we
became friends.

When I first saw Monad, Monoid, Functor and others, I wasn't scared.
They must be from the same zoo as my old friends! Some work is needed
to establish a connection, but it is doable. And it is very rewarding,
because then you get very powerful, dependable friends that give you
strong guaranties!

Now compare ICollecion, IAppendable or the alike. These are warm, and
fuzzy, and don't hurt me please, so the guaranties they give depend
on mood or something as intuitive as phase of the moon. And don't
feed corner cases to them, because they may scratch you!

So:

Warm, fuzzy: under defined, intuitive, sloppy...
Cool, strong: well defined, dependable, concrete...

There are plenty of warm, fuzzy languages out there, if you want Java,
you know where to find it. And *real programmers* seem to look for
something more these days.

I need to sleep well knowing my programs work. I need powerful, strong
abstraction. I use Haskell wherever possible because it is based on
the strongest thing we have: MATHS! Keep it that way!

Monads aren't warm, they are COOL!

--
Gracjan


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


[Haskell-cafe] Re: GHCi Memory Leak in Windows Vista

2009-01-20 Thread Gracjan Polak

Same here:

Vista, GHC 6.8.3

Tested a bit changed scenario: instead of 20 separate compilations it is
worthwhile to run single, longer build, e.g. ghc --make of same package.

Seems like GHCi does not run garbage collection when machine is busy. And then
it accumulates memory. This renders Vista totally unresponsive and even can lead
to automatic reboot (happened once to me).

:)

-- 
Gracjan


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


Re: [Haskell-cafe] Haskell IDE

2011-03-04 Thread Gracjan Polak
Alexander Danilov alexander.a.danilov at gmail.com writes:

 
 03.03.2011 16:05, Hauschild, Klaus (EXT) пишет:
  Hi Haskellers,
  whats your Haskell IDE of choise? Currently I use leksah. Is the
  EclipseFP Plugin for Eclipse a real alternative?
  Thanks
  Klaus
 
 
 
 Emacs, look at haskell wiki for details about haskell-mode.
 

Emacs is good as an editor for Haskell. Indentation is problematic.

I'd like to have a indent mode that has following bindings:
- TAB indents 4 chars more
- Shift-TAB indents 4 chars less
- RET - indents a line same as previous line unless last line had a block
  opening keyword


Indentation indents mostly too far right in current haskell-mode for my taste.

-- 
Gracjan



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


Re: [Haskell-cafe] Haskell IDE

2011-03-04 Thread Gracjan Polak
Ivan Lazar Miljenovic ivan.miljenovic at gmail.com writes:
 
 Sounds similar to what haskell-indent does, except that it uses 2
 spaces rather than 4, backspace does the chars less, and TAB also has
 a version (albeit not as nice as the one in haskell-indentation) of
 the tab-cycle.
 


I rejected haskell-indent some time ago, do not remember the reason now.

I think I'll give it a second chance.

-- 
Gracjan



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


[Haskell-cafe] How to keep cabal and ghci package versions in sync?

2011-04-24 Thread Gracjan Polak

Hi all,

I have a project with a .cabal file listing package dependencies using
the usual version constraints ==X.Y.* Z.W or =K.J syntax.
Standard route cabal configure; cabal build works correctly as it is able
to select working set of package versions.

I have also a .ghci file. When I run GHCi it uses all latest installed packages
in the system. This prevents the project from loading.

I tried to use 'cabal-dev ghci', but this still selects latest global packages.

So, how to I load up ghci with the same package versions as selected by cabal?

Thanks!

-- 
Gracjan



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


Re: [Haskell-cafe] How to keep cabal and ghci package versions in sync?

2011-04-26 Thread Gracjan Polak
Henning Thielemann schlepptop at henning-thielemann.de writes:
 You can manually select packages for GHCi with '-package' option.
 However I do not know a way to automatically syncronise this with the
 dependencies from the Cabal file.
 

I kind of expected 'cabal-dev ghci' to do this for me.

Thanks for help, I'm cleaning my packages for now.

-- 
Gracjan





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


Re: [Haskell-cafe] Python is lazier than Haskell

2011-04-28 Thread Gracjan Polak
Ketil Malde ketil at malde.org writes:
 
 In Haskell, I often need to add stubs of undefined in order to do
 this.  I don't mind, since it is often very useful to say *something*
 about the particular piece - e.g. I add the type signature, establishing
 the shape of the missing piece without bothering with the actual
 implementation just yet.

Seconded.

Sometimes I wish for a -fphp flag that would turn some type errors into
warnings. Example: 

v.hs:8:6:
Couldn't match expected type `[a]' against inferred type `()'
In the first argument of `a', namely `y'
In the expression: a y
In the definition of `c': c = a y

GHC could substitute 'y = error Couldn't match expected type `[a]' against
inferred type `()'' and compile anyway.

Would that bring Haskell closer to Python?

-- 
Gracjan



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


[Haskell-cafe] ErrorT vs Either

2011-05-16 Thread Gracjan Polak

Hi all,

A why question: Why:

Control.Monad.Error Prelude runErrorT (fail msg) :: IO (Either String Int)
Left msg

but

Control.Monad.Error Prelude (fail msg) :: (Either String Int)
*** Exception: msg

?

-- 
Gracjan



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


Re: [Haskell-cafe] ErrorT vs Either

2011-05-16 Thread Gracjan Polak

Thanks Daniel, Yves and Edward for explanation. Two things come to my mind now.

1. It should be unified. Why? Because conceptually:

runIdentity (runErrorT (fail msg)) :: Either String Int
Left msg

and 

fail msg :: Either String Int
*** Exception: msg

Should be the same as Identity monad should not add structure.

2. I need a Failure monad that works well with pattern match failures (that call
fail). I'd like to use it like this:

runErrorT $ do
 Active - getStatus-- ensure proper status
 Just elm - lookup stuff there -- lookup element
 when (condition) $ fail wrong!   -- check condition
 return 1234-- return useful value

sort of... Any ideas what could be used in place of Either monad? Basically I
need working pattern match failures (I guess that means I need working fail
method that is not equal to error).

-- 
Gracjan



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


Re: [Haskell-cafe] ErrorT vs Either

2011-05-16 Thread Gracjan Polak
Daniel Fischer daniel.is.fischer at googlemail.com writes:

 
 On Monday 16 May 2011 23:41:44, Gracjan Polak wrote:
  Thanks Daniel, Yves and Edward for explanation. Two things come to my
  mind now.
  
  1. It should be unified.
 
 The (Either e) Monad instance was recently changed after people have long 
 complained that there shouldn't be an (Error e) constraint.
 It's unlikely that that will be reverted soon.

I did not request a revert, I asked about consistent behavior.
 
 It's the (Error e) Monad which adds the structure [nowadays, Error e = 
 ErrorT e Identity].

I do not understand this part. Can you elaborate?

 
  
  2. I need a Failure monad that works well with pattern match failures
  (that call fail). I'd like to use it like this:
  
  runErrorT $ do
   Active - getStatus-- ensure proper status
   Just elm - lookup stuff there -- lookup element
   when (condition) $ fail wrong!   -- check condition
   return 1234-- return useful value
  
  sort of...
 
 That does work, doesn't it?

Indeed this does work, but it is fragile wrt refactorings.

Suppose we have the code:

  result - runErrorT $ do
 lift $ print was here
 fail msg

  (result = Left msg)

after a while the print statement may be removed:

  result - runErrorT $ do
 fail msg

  (result = Left msg)

and then somebody will see that inner 'do' does not depend on outer
monad so next refactoring will be:

  let result = do
 fail msg

  (result = error msg)

And here code breaks...

 
 Roll your own,

That is a good idea. I looked also at Attempt.

Thanks for responses.

-- 
Gracjan



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


[Haskell-cafe] Exclusive mode in openFile

2011-06-28 Thread Gracjan Polak

Hi all,

It seems I'm not allowed to open same file both for writing and for reading:

Prelude System.IO f_out - openFile mylog.log AppendMode
Prelude System.IO f_in - openFile mylog.log ReadMode
*** Exception: mylog.log: openFile: resource busy (file is locked)

Usage scenario:

I use hslogger to write to logs, but I'd like to read parts of these logs *from
inside same Haskell application*.

How do I get around exclusive mode in openFile?

-- 
Gracjan



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


Re: [Haskell-cafe] Exclusive mode in openFile

2011-06-28 Thread Gracjan Polak

Max Bolingbroke batterseapower at hotmail.com writes:
 This behaviour is part of the Haskell 98 specification (section
 21.2.3, http://www.haskell.org/onlinereport/io.html):

Thanks for the explanation. Such sharing behavior should be mentioned in
documentation:

http://hackage.haskell.org/packages/archive/haskell98/latest/doc/html/IO.html#v:openFile

What was the rationale behind such strict non-sharing policy?

Anyway, where do I find an 'openFileShared' function? Packages unix/Win32 do not
have obvious leads...

 
 
 Implementations should enforce as far as possible, at least locally to
 the Haskell process, multiple-reader single-writer locking on files.
 That is, there may either be many handles on the same file which
 manage input, or just one handle on the file which manages output. If
 any open or semi-closed handle is managing a file for output, no new
 handle can be allocated for that file.
 
 
 I've been bitten by this before and don't like it. It would be
 possible for GHC to enforce Unix semantics instead (there are
 appropriate flags to CreateFile that get those semantics on Windows),
 which would support more use cases. This change would have to be
 carefully thought through, and the report would have to be amended.
 
 Cheers,
 Max
 


-- 
Gracjan



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


Re: [Haskell-cafe] Exclusive mode in openFile

2011-06-29 Thread Gracjan Polak
Max Bolingbroke batterseapower at hotmail.com writes:

http://hackage.haskell.org/packages/archive/unix/2.4.2.0/doc/html/System-Posix-IO.html.

Thanks for the link. I tried to use it:

Prelude System.Posix.IO fd1 - openFd xxx.tmp WriteOnly (Just 0666)
defaultFileFlags
Loading package unix-2.4.0.2 ... linking ... done.
Prelude System.Posix.IO fd2 - openFd xxx.tmp WriteOnly (Just 0666)
defaultFileFlags
Prelude System.Posix.IO print (fd1,fd2)
(5,7)
Prelude System.Posix.IO h1 - fdToHandle fd1
Prelude System.Posix.IO h2 - fdToHandle fd2
*** Exception: openFile: resource busy (file is locked)

So I can open file twice. So far so good. Then I convert Fds to Handles and
second conversion fails.

I'm looking for file locking code in GHC.IO.* modules, but cannot find any.

How do I convince fdToHandle to create an independent handle to non-locked file?

-- 
Gracjan



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


  1   2   >