[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.

[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

[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

[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

[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

[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

[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

[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

[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] 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 (

[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:

[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] 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] 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

[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

Re: [Haskell-cafe] ReadP and MonadFix

2006-06-24 Thread Gracjan Polak
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

[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 )

[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

[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

[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

[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

[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

[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] 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] 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

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

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

[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

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

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

[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

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

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

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

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

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

[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

[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

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

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

[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

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:

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!

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

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

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

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

[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

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

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

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?

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

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

[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

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

[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

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

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

[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

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

Re: [Haskell-cafe] Template Haskell and Types

2005-09-26 Thread Gracjan Polak
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

[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

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 :) --

[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

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

[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

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

[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.

[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

[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,

[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)

[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

[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

[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

[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

[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

[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

[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

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,

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] 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

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

[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 []

[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.

[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] 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

[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.

[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

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

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-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

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.

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

[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

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

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

[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

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:

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

  1   2   >