Re: [Haskell-cafe] GHC, odd concurrency space leak

2010-04-14 Thread Daniel Fischer
Am Donnerstag 15 April 2010 00:52:22 schrieb Jason Dagit: The bad version, ghc --make NonTermination.hs: \begin{code} {-# OPTIONS -O2 #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} -- Note: Change the optimization to -O1 to get a terminating version Doesn't seem to terminate with -O1 here

Re: [Haskell-cafe] Can't login to GHC trac

2010-04-15 Thread Daniel Fischer
Am Donnerstag 15 April 2010 05:38:23 schrieb Jason Dagit: On Tue, Apr 13, 2010 at 3:47 AM, Erik de Castro Lopo mle...@mega-nerd.commle%2...@mega-nerd.com wrote: Daniel Fischer wrote: Am Dienstag 13 April 2010 09:29:18 schrieb Erik de Castro Lopo: Anyone else have the same problem

Re: [Haskell-cafe] Automating injections: adding a type parameter

2010-04-15 Thread Daniel Fischer
Am Donnerstag 15 April 2010 19:19:15 schrieb Romulus: Hello everyone, I'm stuck with the definition of the helper for LAnd'. I expect : land' :: ((LAnd' p) :: (f p)) = Mu (f p) - Mu (f p) - Mu (f p) land' = \x y - inject (LAnd' x y) ... but ghci 6.10.4 does not really like this

Re: [Haskell-cafe] ghc package problem

2010-04-16 Thread Daniel Fischer
Am Freitag 16 April 2010 11:28:54 schrieb Phyx: Hi all, I'm having a rather weird problem, Ghc-pkg list shows a package installed but doing a ghc -make will give an error saying that It can't find a module that's supposed to be in the installed package. And cabal install always

Re: [Haskell-cafe] ghc package problem

2010-04-16 Thread Daniel Fischer
Am Freitag 16 April 2010 14:06:16 schrieb Phyx: (sorry for the duplication, forgot to reply to the mailing list too) Well, I did, I've completely unregistered the package, Did a check and recache, both completed with no problem. In detail what's happening is, I'm building a tool that

Re: [Haskell-cafe] ghc package problem

2010-04-16 Thread Daniel Fischer
Am Freitag 16 April 2010 15:06:55 schrieb Phyx: I'm using cabal install, $ ghc --make -O2 WinDll WinDll\Lib\NativeMapping.hs:51:18: Could not find module `Language.Haskell.Exts': Use -v to see a list of the files searched for. Is the error message I get when I try to just

Re: [Haskell-cafe] ghc package problem

2010-04-16 Thread Daniel Fischer
Am Freitag 16 April 2010 15:40:38 schrieb Phyx: For the first part $ cat foo.hs module Main (main) where import Language.Haskell.Exts main :: IO () main = print $ readExtensions BangPatterns $ ghc --make foo.hs foo.hs:3:8: Could not find module `Language.Haskell.Exts': Use

Re: [Haskell-cafe] Floyd Warshall performance (again)

2010-04-16 Thread Daniel Fischer
Am Freitag 16 April 2010 17:41:06 schrieb John Lato: From: Mathieu Boespflug mb...@tweag.net Dear haskell-cafe, I implemented the Floyd Warshall algorithm for finding the shortest path in a dense graph in Haskell, but noted the performance was extremely poor compared to C. Even using

Re: [Haskell-cafe] Re: statistics build error

2010-04-16 Thread Daniel Fischer
Am Freitag 16 April 2010 19:11:13 schrieb Keith Sheppard: Sorry, I forgot to add my ghc version is 6.10.1 on OSX k...@catskill:~/projects/ ghc --version The Glorious Glasgow Haskell Compilation System, version 6.10.1 On Fri, Apr 16, 2010 at 1:08 PM, Keith Sheppard keiths...@gmail.com wrote:

Re: [Haskell-cafe] US Patent for the idea of using Haskell to implement UAX #9

2010-04-16 Thread Daniel Fischer
Am Freitag 16 April 2010 20:50:25 schrieb Brian Hulley: revealed a link to a US Patent (7120900) for the idea of implementing the Unicode Bidirectional Algorithm (UAX #9 http://www.unicode.org/reports/tr9) in Haskell, making use, as far as I can tell, of nothing more than the normal approach

Re: [Haskell-cafe] GHC, odd concurrency space leak

2010-04-17 Thread Daniel Fischer
Am Samstag 17 April 2010 14:41:28 schrieb Simon Peyton-Jones: I have not been following the details of this, I'm afraid, but I notice this: forever' m = do _ - m forever' m When I define that version of forever, the space leak goes away. What was the old version of

Re: [Haskell-cafe] Functional Dependencies conflicts

2010-04-17 Thread Daniel Fischer
Am Samstag 17 April 2010 19:14:02 schrieb Limestraël: Hello, Well, here comes the trouble: GameStructs.hs:16:9: Functional dependencies conflict between instance declarations: instance (Binary a) = Binarizable a a -- Defined at MagBots/GameStructs.hs:16:9-37

Re: [Haskell-cafe] Functional Dependencies conflicts

2010-04-17 Thread Daniel Fischer
Am Samstag 17 April 2010 22:01:23 schrieb Limestraël: Yes! Sorry, I forgot a bit: Binary types are automatically made instances of Binarizable/Unbinarizable (that's my line 16): instance (Binary a) = Binarizable a a where toBinary = id instance (Binary a, Monad m) = Unbinarizable a a m

Re: [Haskell-cafe] redirecting cabal-install from /tmp

2010-04-17 Thread Daniel Fischer
Am Sonntag 18 April 2010 00:02:52 schrieb Chris Dornan: Hi Everyone, I am trying to get cabal-install to work on a system in which /tmp is mounted noexec. Is there any way to configure it to use another directory? cabal-install gets its temporary directory via

Re: [Haskell-cafe] GHC, odd concurrency space leak

2010-04-17 Thread Daniel Fischer
Am Samstag 17 April 2010 22:11:05 schrieb Bertram Felgenhauer: Daniel Fischer wrote: Am Samstag 17 April 2010 14:41:28 schrieb Simon Peyton-Jones: I have not been following the details of this, I'm afraid, but I notice this: forever' m = do _ - m forever' m

Re: [Haskell-cafe] Functional Dependencies conflicts

2010-04-17 Thread Daniel Fischer
Am Sonntag 18 April 2010 01:23:07 schrieb Ben Millwood: On Sat, Apr 17, 2010 at 9:50 PM, Daniel Fischer daniel.is.fisc...@web.de wrote: {-# LANGUAGE OverlappingInstances, [...] but with caution: quicksilver using OverlappingInstances is the haskell equivalent of buying a new car

Re: [Haskell-cafe] GHC, odd concurrency space leak

2010-04-17 Thread Daniel Fischer
Am Sonntag 18 April 2010 02:05:30 schrieb Bertram Felgenhauer: Which is     always = \a_aeO - let k_sYz = always a_aeO                        in  a_aeO k_sYz specialised to IO, and with () inlined. Where is the knot? Nowhere. Got confused by all the a_aAe and `cast` (GHC.Types...).

Re: GUI (was: Re: [Haskell-cafe] DLL on Windows)

2010-04-18 Thread Daniel Fischer
Am Sonntag 18 April 2010 20:59:25 schrieb Neil Mitchell: Hi, I thought this thread suggested that a cabal install wx would now work? It does, as far as I can tell. I just tried it and got: ... generated 2439 constant definitions ok. setup.exe: wx-config: does not exist That's not our

Re: GUI (was: Re: [Haskell-cafe] DLL on Windows)

2010-04-18 Thread Daniel Fischer
Am Sonntag 18 April 2010 21:41:06 schrieb Daniel Fischer: wx-config should have been installed as part of the wxWidgets package. Is that not included in the windows-installer of wxWidgets? Seems it's not so. http://www.haskell.org/haskellwiki/WxHaskell/Building says Windows users should also

Re: [Haskell-cafe] hamming distance allocation

2010-04-18 Thread Daniel Fischer
Am Montag 19 April 2010 01:03:14 schrieb Arnoldo Muller: Hello all: I want to generate some hamming distance statistics about a set of strings. As explained in another e-mail in this list, I used the following code to call the functions: (exampl holds the list of strings of size w) filter

Re: [Haskell-cafe] Re: hamming distance allocation

2010-04-19 Thread Daniel Fischer
Am Montag 19 April 2010 14:13:53 schrieb Heinrich Apfelmus: Arnoldo Muller wrote: I want to generate some hamming distance statistics about a set of strings. filter (\x - x /= 0) $ map (uncurry hammingX) [(xs, ys) | xs - exampl, ys - exampl] [...] -- function posted in

Re: [Haskell-cafe] hamming distance allocation

2010-04-19 Thread Daniel Fischer
Am Montag 19 April 2010 14:37:33 schrieb John Lato: Is it really necessary to use Strings?  I think a packed type, e.g. Vector or ByteString, would be much more efficient here. Not very much if the strings are fairly short (and the list isn't too long, so there's not a big difference in

Re: [Haskell-cafe] hamming distance allocation

2010-04-19 Thread Daniel Fischer
am still unable to find the source of my memory leak. Allocation as such is not a problem, resident memory is the important thing. Try heap profiling to see what holds on to memory (+RTS -hc would be a good first run). Regards, Arnoldo On Mon, Apr 19, 2010 at 3:47 PM, Daniel Fischer

Re: [Haskell-cafe] hamming distance allocation

2010-04-19 Thread Daniel Fischer
) [(xs, ys) | xs - exampl, ys - exampl] filter (/= 0) [hamming xs ys | xs - example, ys - example] And of course, you can trivially avoid half of the work. Best Regards, Arnoldo Muller On Mon, Apr 19, 2010 at 3:18 AM, Daniel Fischer daniel.is.fisc...@web.dewrote: Am Montag 19 April

Re: [Haskell-cafe] Profiling

2010-04-20 Thread Daniel Fischer
Am Dienstag 20 April 2010 18:59:23 schrieb C K Kashyap: Hi Ivan, I tried doing cabal install parsec = 3 --reinstall --enable-library-profiling This complained about bytestring ... so I did this - cabal install bytestring --reinstall --enable-library-profiling And this complained about

Re: [Haskell-cafe] I need help getting started

2010-04-25 Thread Daniel Fischer
Am Sonntag 25 April 2010 06:34:32 schrieb mitch...@kaplan2.com: Luke already explained the type error, so I'll focus on the implementation. Hi, I'm just starting to learn, or trying to learn Haskell. I want to write a function to tell me if a number's prime. This is what I've got: f

Re: [Haskell-cafe] I need help getting started

2010-04-25 Thread Daniel Fischer
Am Sonntag 25 April 2010 17:49:05 schrieb mitch...@kaplan2.com: Hi David, Thanks for the suggestion.  I took a quick look at your article, and I'll have to spend a little more time on it.  Delicious Primes?  Great name. And it's a good read. I find this definition of prime numbers

Re: [Haskell-cafe] Broken ghc documentation links

2010-04-26 Thread Daniel Fischer
Am Montag 26 April 2010 13:36:22 schrieb Ivan Lazar Miljenovic: So, the problem is that there are broken links _in Hoogle_; No, hoogle just sends you to http://www.haskell.org/ghc/docs/6.12.2/html/libraries/base-4.2.0.1/Prelude.html#t%3AIO , which does exist. It's the 'Source' link in the

Re: [Haskell-cafe] and [] = True; or [] = False

2010-04-26 Thread Daniel Fischer
Am Montag 26 April 2010 14:15:40 schrieb Bjorn Buckwalter: Dear all, Does it make good sense that 'and []' returns 'True' and 'or []' returns 'False'? The Haskell Road to Logic, Maths and Programming says so: The function or takes a list of truth values and returns True if at least one

Re: [Haskell-cafe] Why does cabal select base-3.0.3.2 when base-4.2.0.0 is available?

2010-04-26 Thread Daniel Fischer
Am Montag 26 April 2010 14:32:03 schrieb Bjorn Buckwalter: So what would be the fix, to set an upper bound on base? Is the general recommendation that all packages should specify upper bounds on all dependencies (if so why doesn't Cabal tell us?)? Yes, that's the general recommendation.

Re: [Haskell-cafe] Broken ghc documentation links

2010-04-26 Thread Daniel Fischer
Am Montag 26 April 2010 15:15:03 schrieb Ivan Lazar Miljenovic: Daniel Fischer daniel.is.fisc...@web.de writes: Am Montag 26 April 2010 13:36:22 schrieb Ivan Lazar Miljenovic: So, the problem is that there are broken links _in Hoogle_; No, hoogle just sends you to http://www.haskell.org

Re: [Haskell-cafe] Haddock infix constructors in markup

2010-04-26 Thread Daniel Fischer
Am Montag 26 April 2010 18:15:02 schrieb Ozgur Akgun: Hi all, If I have the following data type: data Expr = Num Int | Expr :+: Expr | Expr :-: Expr Haddock handles the infix constructors, and generates a very nice output (html in this case) However when I try to reference to one of the

Re: [Haskell-cafe] Rank-2 polymorphism and overloading

2010-04-26 Thread Daniel Fischer
Am Montag 26 April 2010 19:52:23 schrieb Thomas van Noort: Hello all, I'm having difficulties understanding rank-2 polymorphism in combination with overloading. Consider the following contrived definition: f :: (forall a . Eq a = a - a - Bool) - Bool f eq = eq True True Then, we pass f

Re: [Haskell-cafe] Haddock infix constructors in markup

2010-04-26 Thread Daniel Fischer
Am Montag 26 April 2010 22:05:48 schrieb Ozgur Akgun: So, how can we make use of this fix? My guess: $ cabal install haddock-2.7.2 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Build problems (hsp, trhsx, ultimately Happstack)

2010-04-26 Thread Daniel Fischer
Am Montag 26 April 2010 22:23:42 schrieb Gregory Collins: Alexander Solla a...@2piix.com writes: On Apr 26, 2010, at 12:30 PM, Jeremy Shaw wrote: Does trying to install hsp-0.5.1 work any better? I hadn't tried it, since it forces hsx-0.7 to install. But I gave it a shot, and it fails

Re: [Haskell-cafe] Re: FRP for game programming / artifical life simulation

2010-04-29 Thread Daniel Fischer
Am Donnerstag 29 April 2010 20:08:00 schrieb Ben: A technical question: it seems like the instance of ArrowLoop is too strict (this is something I've wondered about in Liu's paper too.) Shouldn't it be  instance ArrowLoop SFAuto where      loop (SFAuto s f) = SFAuto s f'          where    

Re: [Haskell-cafe] Re: FRP for game programming / artifical life simulation

2010-04-30 Thread Daniel Fischer
Am Freitag 30 April 2010 17:23:19 schrieb Antoine Latter: On Fri, Apr 30, 2010 at 3:37 AM, Daniel Fischer daniel.is.fisc...@web.de wrote: Am Donnerstag 29 April 2010 20:08:00 schrieb Ben: A technical question: it seems like the instance of ArrowLoop is too strict (this is something I've

Re: [Haskell-cafe] why does Data.Text.Lazy.IO.readFile return the internal type Data.Text.Lazy.Internal.Text, when Data.Text.IO.readFile returns plain IO Data.Text.Text?

2010-04-30 Thread Daniel Fischer
Am Freitag 30 April 2010 22:37:38 schrieb Thomas Hartman: *Main :t Data.Text.IO.readFile Data.Text.IO.readFile :: FilePath - IO T.Text but *Main :t Data.Text.Lazy.IO.readFile Data.Text.Lazy.IO.readFile :: FilePath - IO text-0.7.1.0:Data.Text.Lazy.Internal.Text Hmm, Prelude :t

Re: [Haskell-cafe] why does Data.Text.Lazy.IO.readFile return the internal type Data.Text.Lazy.Internal.Text, when Data.Text.IO.readFile returns plain IO Data.Text.Text?

2010-04-30 Thread Daniel Fischer
Am Freitag 30 April 2010 23:20:59 schrieb Edward Kmett: On Fri, Apr 30, 2010 at 5:09 PM, Daniel Fischer daniel.is.fisc...@web.dewrote: and how can I get from internal type to regular type when using Data.Text? Use id :: a - a ;) Not quite, there is still a distinction between

Re: [Haskell-cafe] why does Data.Text.Lazy.IO.readFile return the internal type Data.Text.Lazy.Internal.Text, when Data.Text.IO.readFile returns plain IO Data.Text.Text?

2010-04-30 Thread Daniel Fischer
Am Samstag 01 Mai 2010 00:26:26 schrieb Bryan O'Sullivan: On Fri, Apr 30, 2010 at 3:14 PM, Daniel Fischer daniel.is.fisc...@web.dewrote: Yes, I understood it so that he wanted to convert from Data.Text.Lazy.Internal.Text to Data.Text.Lazy.Text. It's the same type. That's why I suggested

Re: [Haskell-cafe] why does Data.Text.Lazy.IO.readFile return the internal type Data.Text.Lazy.Internal.Text, when Data.Text.IO.readFile returns plain IO Data.Text.Text?

2010-04-30 Thread Daniel Fischer
Am Samstag 01 Mai 2010 00:58:23 schrieb Felipe Lessa: It depends on what is on your scope: Prelude :t Data.Text.Lazy.IO.readFile Data.Text.Lazy.IO.readFile :: FilePath - IO text-0.7.1.0:Data.Text.Lazy.Internal.Text Prelude :m Data.Text.Lazy Prelude Data.Text.Lazy :t

Re: [Haskell-cafe] Happy: PATH issue

2010-05-01 Thread Daniel Fischer
Am Samstag 01 Mai 2010 13:16:55 schrieb Limestraël: Hello Café, When I was trying to cabal-install haskell-src, I came up with: cabal: The program happy is required but it could not be found However, the happy package was actually installed and the 'happy' executable was in ~/.cabal/bin

Re: [Haskell-cafe] Build problems (hsp, trhsx, ultimately Happstack)

2010-05-01 Thread Daniel Fischer
Am Samstag 01 Mai 2010 19:06:33 schrieb Warren Harris: On May 1, 2010, at 3:39 AM, Daniel Fischer wrote: Try $ cabal install --constraint=Crypto4.2.1 -- constraint=HJScript0.5 happs-tutorial This had the same problem building containers: Building containers-0.2.0.1... Data

Re: [Haskell-cafe] Happy: PATH issue

2010-05-02 Thread Daniel Fischer
Am Sonntag 02 Mai 2010 22:26:43 schrieb Brandon S. Allbery KF8NH: On May 2, 2010, at 05:33 , Limestraël wrote: Yes, it's weird, but it works! Thanks. It's normal, actually. ~ is only understood by the shell, so unless the shell is invoked to expand it a program will fail to understand it.

Re: [Haskell-cafe] Happy: PATH issue

2010-05-02 Thread Daniel Fischer
Am Montag 03 Mai 2010 00:28:31 schrieb Ivan Lazar Miljenovic: Daniel Fischer daniel.is.fisc...@web.de writes: If the default shell is bash and the PATH is set and exported in ~/.bashrc, it should work with '~' unless the string is quoted, shouldn't it? bash expands the tildes when

Re: [Haskell-cafe] Happy: PATH issue

2010-05-02 Thread Daniel Fischer
On Montag 03 Mai 2010 02:12:20, Ivan Miljenovic wrote: On 3 May 2010 08:49, Daniel Fischer daniel.is.fisc...@web.de wrote: Am Montag 03 Mai 2010 00:28:31 schrieb Ivan Lazar Miljenovic: bash expands it when you use it within bash, but when it's used within another program this might

Re: [Haskell-cafe] Happy: PATH issue

2010-05-02 Thread Daniel Fischer
On Montag 03 Mai 2010 02:34:51, Ivan Miljenovic wrote: This is on my ubuntu box at uni: iv...@feitpc02 ~ $export DUMMY=~/bin:~/cabal You put quotes around the string, that means tildes aren't expanded ($VARIABLEs still are: da...@linux-mkk1:~/Haskell export

Re: [Haskell-cafe] eclipse, haskell-platform and windows. Installation problem.

2010-05-03 Thread Daniel Fischer
On Montag 03 Mai 2010 19:58:54, Han Joosten wrote: Hi all Then, again i tried 'runhaskell setup.hs configure', but this failed again with exactly the same message as before. It seems that all packages that I installed dissapeared! I think it's the fact that cabal-install by default does

Re: [Haskell-cafe] Building regex-posix for windows

2010-05-03 Thread Daniel Fischer
On Montag 03 Mai 2010 21:40:13, Stanislav Chernichkin wrote: I think it would be nice if someone will write an article on Haskell Wiki on building regex-posix, but my English is not good enough for such things. You could start the article nevertheless and let others polish the English then. I

Re: [Haskell-cafe] Why cabal forces reinstallation of happstack-utils?

2010-05-04 Thread Daniel Fischer
On Mittwoch 05 Mai 2010 00:55:38, Maciej Piechotka wrote: I try to configure happstack with parsec 3.1. It seems to fail due to cabal: happstack-util.cabal says parsec 3, so --constraint=parsec 3 and the given dependencies are incompatible, hence it can't be configured. Probably parsec 3

Re: [Haskell-cafe] Re: Why cabal forces reinstallation of happstack-utils?

2010-05-04 Thread Daniel Fischer
On Wednesday 05 May 2010 01:45:29, Maciej Piechotka wrote: I updated local copy, as shown, but cabal wants to rebuild it anyway. My question was rather why the repo is considered at all when the package is installed. Regards Okay, I didn't quite understand your question, sorry. So, what's

Re: [Haskell-cafe] Re: Why cabal forces reinstallation of happstack-utils?

2010-05-05 Thread Daniel Fischer
On Wednesday 05 May 2010 15:45:38, Henning Thielemann wrote: Maciej Piechotka schrieb: On Wed, 2010-05-05 at 01:09 +0200, Daniel Fischer wrote: On Mittwoch 05 Mai 2010 00:55:38, Maciej Piechotka wrote: I try to configure happstack with parsec 3.1. It seems to fail due to cabal

Re: [Haskell-cafe] posting UTF8 data with Curl library

2010-05-05 Thread Daniel Fischer
On Wednesday 05 May 2010 23:05:10, Eugeny N Dzhurinsky wrote: Hello! I need to submit data to HTTP server using UTF8 encoding. I found out that libcurl for haskell can work with Data.ByteString - but it seems not able to work with Data.ByteString.UTF8. Can you please advice, how do I

Re: [Haskell-cafe] Re: Haskell and scripting

2010-05-05 Thread Daniel Fischer
On Wednesday 05 May 2010 23:36:26, Limestraël wrote: but you will not object if I say that scheme is quicker to learn than Haskell. Well, I do object. Learning Haskell went like a breeze (not to perfection, but well enough). Only Python was nearly as easy and quick to learn. Learning Lisp

Re: [Haskell-cafe] Re: Haskell and scripting

2010-05-06 Thread Daniel Fischer
On Thursday 06 May 2010 16:32:50, Limestraël wrote: ^^ That's an interesting debate: How do you imagine the future programming languages? But not today's topic. It's strange that, since Lisp is still used now, especially for teaching purposes, and since everybody complains about

Re: [Haskell-cafe] Mystery Parse Error in LHS file

2010-05-06 Thread Daniel Fischer
On Thursday 06 May 2010 17:02:59, Iæfai wrote: I have an lhs file, 'starsystem.lhs' that is not compiling because of a parse error. I cannot figure out what the problem here is. Apparently, unlit doesn't manage to cope with mixed LaTeX and bird-track.

Re: [Haskell-cafe] Mystery Parse Error in LHS file

2010-05-06 Thread Daniel Fischer
On Thursday 06 May 2010 17:35:58, Daniel Fischer wrote: Apparently, unlit doesn't manage to cope with mixed LaTeX and bird-track. Ah, overlooked The program text is recovered by taking only those lines beginning with , and replacing the leading with a space. Layout and comments apply exactly

[Haskell-cafe] Re: [Long, probably not-beginners anymore] Parallel folds and folds as arrows (was: Re: [Haskell-beginners] Re: When, if ever, does Haskell calculate once?)

2010-05-07 Thread Daniel Fischer
On Friday 07 May 2010 03:15:19, Maciej Piechotka wrote: On Thu, 2010-05-06 at 23:46 +0200, Daniel Fischer wrote: Share.share :: GHC.Types.Int GblId [Str: DmdType] Share.share = case GHC.List.$wlen @ GHC.Integer.Type.Integer Share.share_a 0 of ww_amc { __DEFAULT - GHC.Types.I

[Haskell-cafe] Re: [Long, probably not-beginners anymore] Parallel folds and folds as arrows (was: Re: [Haskell-beginners] Re: When, if ever, does Haskell calculate once?)

2010-05-07 Thread Daniel Fischer
On Friday 07 May 2010 16:15:41, Daniel Fischer wrote: b) using Don Stewart's ghc-core (http://hackage.haskell.org/package/ghc- core), e.g. ghc.core -f html -- -O2 Source.hs Source.html And of course, the html backend of ghc-core was removed with version 0.5 :( If you want html output, $ cabal

Re: [Haskell-cafe] accents

2010-05-07 Thread Daniel Fischer
On Friday 07 May 2010 17:05:08, Dupont Corentin wrote: Hello, i'm still struggling with ghci and accents. Prelude é \233 That uses the Show instance of Char, which escapes all characters greater than '\127' ('\DEL'), so that's no problem, jut inconvenient. I've installed GHC 6.12.1,

Re: [Haskell-cafe] corner case in Text.JSON 0.4.3

2010-05-12 Thread Daniel Fischer
On Wednesday 12 May 2010 21:53:41, Martin Hilbig wrote: hi, since i got no answer from the maintainer, maybe someone else can take care of it, or at least point out, what i did wrong. so, i recently stumbled upon some error while using Text.JSON 0.4.3 [1]:

Re: [Haskell-cafe] Data creation pattern?

2010-05-13 Thread Daniel Fischer
On Thursday 13 May 2010 20:43:44, Eugeny N Dzhurinsky wrote: On Thu, May 13, 2010 at 07:14:25PM +0100, Stephen Tetley wrote: Hi Eugene Is something like this close to what you want: Not really. First of all, there're many properties, not 3. So it may end up with plenty of support

Re: [Haskell-cafe] debugging a hanging program: where to start?

2010-05-13 Thread Daniel Fischer
On Thursday 13 May 2010 21:28:21, Aran Donohue wrote: I have an accept-loop: do (conn, _saddr) - accept sock forkIO $ initializeConnection conn Which allocates memory iff accept allocates, I suppose. To test the theory, is there a way I can force an allocation that won't get optimized

Re: [Haskell-cafe] MultiParamTypeClasses, FunctionalDependencies and FlexibleInstances using GHCi

2010-05-14 Thread Daniel Fischer
On Friday 14 May 2010 15:32:10, Bulat Ziganshin wrote: Hello Julian, Friday, May 14, 2010, 4:18:42 PM, you wrote: Now, if I type 3 + 4 it does not work, and i really don't understand why. If i ask GHCi for 3's type ($ :t 3) it will answer 3 :: (Prelude.Num t) = t. But, if 3 and 4

Re: [Haskell-cafe] Help debugging code broken after upgrading debian to GHC 6.12: invalid argument

2010-05-14 Thread Daniel Fischer
On Saturday 15 May 2010 02:53:43, Brandon S. Allbery KF8NH wrote: On May 14, 2010, at 20:24 , Brandon Simmons wrote: The other baffling thing is this: if the debugging line 426 is uncommented, then even running: $ runghc Befunge.hs --quiet mycology.b98 ...will fail. But all we're

Re: [Haskell-cafe] Help debugging code broken after upgrading debian to GHC 6.12: invalid argument

2010-05-15 Thread Daniel Fischer
On Saturday 15 May 2010 15:18:28, Brandon Simmons wrote: On May 14, 2010, at 20:24 , Brandon Simmons wrote: The other baffling thing is this: if the debugging line 426 is uncommented, then even running: $ runghc Befunge.hs --quiet mycology.b98 ...will fail. But all we're doing is a

Re: [Haskell-cafe] Getting a string from url-converted UTF8 input

2010-05-16 Thread Daniel Fischer
On Sunday 16 May 2010 18:13:30, Eugene Dzhurinsky wrote: On Sun, May 16, 2010 at 06:56:58PM +0300, Roman Cheplyaka wrote: I assume you are using GHC 6.12. The trouble is in conversion done by putStrLn. Use one from System.IO.UTF8. Or try to upgrade to GHC 6.12 which respects the locale

Re: [Haskell-cafe] Help with Bird problem 1.4.1

2010-05-18 Thread Daniel Fischer
On Tuesday 18 May 2010 21:49:50, R J wrote: Newbie trying to get through Bird. Could someone provide a clean solution, with proof (so I can see how these proofs are laid out), to this: Given: f :: Integer - Integer g :: Integer - (Integer - Integer) h :: ... h x y = f (g x y) Questions:

Re: [Haskell-cafe] TagSoup 0.9

2010-05-19 Thread Daniel Fischer
On Wednesday 19 May 2010 19:46:57, Ralph Hodgson wrote: Forgot to add: I now need to understand the following warnings on this line import Text.HTML.Download: In Text.HTML.Download, there's the following: {-| /DEPRECATED/: Use the HTTP package instead: import Network.HTTP

Re: [Haskell-cafe] String rewriting

2010-05-20 Thread Daniel Fischer
On Thursday 20 May 2010 15:49:59, Roly Perera wrote: Hi, I'm looking for a simple way to rewrite strings according to simple composable rules like: replace _ by \\(\\hole\\) replace -n where n matches an integer by ^{n} so that I can import some pretty-printed output into a LaTeX alltt

Re: [Haskell-cafe] Proposal to solve Haskell's MPTC dilemma

2010-05-20 Thread Daniel Fischer
On Thursday 20 May 2010 16:34:17, Carlos Camarao wrote: In the context of MPTCs, this rule alone is not enough. Consider, for example (Example 1):    class F a b where f:: a-b    class O a where o:: a and     k = f o:: (C a b,O a) = b Type forall a b. (C a b,O a) = b can be considered to

Re: [Haskell-cafe] FW: Why does this Ord-class instance crash?

2010-05-21 Thread Daniel Fischer
On Friday 21 May 2010 19:06:51, R J wrote: Why does the following, trivial code snippet below hang GHCi when I typeScalene Failure, and what's the fix? For an Ord instance, you need to define at least one of compare and (=) or the other functions from the class won't work. All methods have

Re: [Haskell-cafe] Exception: : changeWorkingDirectory: does not exist (No such file or directory)

2010-05-21 Thread Daniel Fischer
On Friday 21 May 2010 20:50:39, Anatoly Yakovenko wrote: anyone else seeing this behavior? anato...@anatolyy-linux ~ $ ghci GHCi, version 6.12.1: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading

Re: [Haskell-cafe] double2Float is faster than (fromRational . toRational)

2010-05-21 Thread Daniel Fischer
On Friday 21 May 2010 22:06:43, Henning Thielemann wrote: On Fri, 21 May 2010, Daniel van den Eijkel wrote: Dear Haskellers, I just want to share an observation. I had to convert a Double to a Float value in an inner loop of an application, and I used somethin like this: xf =

Re: [Haskell-cafe] Performance Issue

2010-05-22 Thread Daniel Fischer
On Saturday 22 May 2010 15:00:25, Thomas Schilling wrote: Actually, in this case it would be safe to do CSS. Because a) the function is strict in both arguments so GHC creates a worker which only uses unboxed types b) this cannot cause any space leaks (it contains no pointers) The

Re: [Haskell-cafe] Performance Issue

2010-05-22 Thread Daniel Fischer
On Saturday 22 May 2010 16:48:27, Daniel Fischer wrote: The boxing is due to the use of (^). If you write x*x instead of x^2, it can use the primop *## and needn't box it. As a side effect, the original time leak probably wouldn't have occured with x*x instead of x^2 because one would've made

Re: [Haskell-cafe] How to construct a lazy list of eagerly-evaluated items?

2010-05-22 Thread Daniel Fischer
On Sunday 23 May 2010 01:10:54, Vladimir Ch. wrote: I'm using Project Euler to learn Haskell. In particular, I'm writing a program for Problem 18: snip The program works, but consumes obscene amount of memory. Not if it's compiled. Even interpreted I wouldn't call it obscene, though it is

Re: [Haskell-cafe] double2Float is faster than (fromRational . toRational)

2010-05-23 Thread Daniel Fischer
On Sunday 23 May 2010 13:12:16, wren ng thornton wrote: Daniel Fischer wrote: There are more rules elsewhere. If you compile with optimisations, GHC turns your realToFrac into double2Float# nicely, so it's okay to use realToFrac. However, without optimisations, no rules fire, so you'll

Re: [Haskell-cafe] Declaring a tuple of instances of Enums as an instance of the Enum class

2010-05-23 Thread Daniel Fischer
On Sunday 23 May 2010 15:33:58, Ivan Lazar Miljenovic wrote: R J rj248...@hotmail.com writes: Say I've got a type Month declared as an instance of the Enum class, and a type MonthPair declared as a pair of months: data Month = January | February | March | April | May | June | July |

Re: [Haskell-cafe] Clean proof -- correction

2010-05-23 Thread Daniel Fischer
On Sunday 23 May 2010 18:24:50, R J wrote: Correction:  the theorem is     h . either (f, g) = either (h . f, h . g) Still not entirely true, const True . either (undefined, undefined) $ undefined = True while either (const True . undefined, const True . undefined) undefined = undefined

Re: [Haskell-cafe] Re: Proof question -- (==) over Bool

2010-05-24 Thread Daniel Fischer
On Monday 24 May 2010 15:48:14, Jonas Almström Duregård wrote: Consider that calling id undefined requires evaluating undefined before you can call id. The program will crash before you ever call id. Of course, the identity function should have produced a value that crashed in

Re: [Haskell-cafe] problem with regex replace with back references

2010-05-24 Thread Daniel Fischer
On Monday 24 May 2010 17:08:50, Juan Maiz wrote: I'm trying use subRegex to replace using back references just like the docs says: http://hackage.haskell.org/packages/archive/regex-compat/0.92/doc/html/T ext-Regex.html#v%3AsubRegex But when i try to replace with \1 i got \SOH and not e. Can

Re: [Haskell-cafe] Exception: : changeWorkingDirectory: does not exist (No such file or directory)

2010-05-24 Thread Daniel Fischer
On Monday 24 May 2010 21:35:10, Anatoly Yakovenko wrote: :set -fglasgow-exts Can't you be more discriminating and turn on only those extensions you regularly use? :set prompt Thats all i have in my .ghci file Shouldn't cause a cd. Maybe $ ghci -v4 would give a hint?

Re: [Haskell-cafe] How to deal with huge text file?

2010-05-24 Thread Daniel Fischer
On Tuesday 25 May 2010 04:26:07, Ivan Miljenovic wrote: On 25 May 2010 12:20, Magicloud Magiclouds magicloud.magiclo...@gmail.com wrote: This is the function. The problem sure seems like something was preserved unexpected. But I cannot find out where is the problem. seperateOutput file

Re: [Haskell-cafe] How to deal with huge text file?

2010-05-25 Thread Daniel Fischer
On Tuesday 25 May 2010 08:14:13, Ivan Miljenovic wrote: On 25 May 2010 16:12, Magicloud Magiclouds magicloud.magiclo...@gmail.com wrote: Yes, this code works with a little hack. Thank you. I'm scared to ask: what pray tell is this little hack? Looking at it again, probably making it work

Re: [Haskell-cafe] How to deal with huge text file?

2010-05-25 Thread Daniel Fischer
On Tuesday 25 May 2010 10:44:57, Ivan Lazar Miljenovic wrote: Daniel Fischer daniel.is.fisc...@web.de writes: On Tuesday 25 May 2010 08:14:13, Ivan Miljenovic wrote: On 25 May 2010 16:12, Magicloud Magiclouds magicloud.magiclo...@gmail.com wrote: Yes, this code works with a little hack

Re: [Haskell-cafe] TDD in Haskell

2010-05-25 Thread Daniel Fischer
On Tuesday 25 May 2010 13:36:01, Ionut G. Stan wrote: Hi, I'm doing TDD in pretty much all of the languages that I know, and I want to introduce it early in my Haskell learning process. I wonder though, if there's some established process regarding TDD, not unit testing. I've heard of

Re: [Haskell-cafe] TDD in Haskell

2010-05-25 Thread Daniel Fischer
On Tuesday 25 May 2010 14:36:46, Ionut G. Stan wrote: On 5/25/10 2:50 PM, Daniel Fischer wrote: On Tuesday 25 May 2010 13:36:01, Ionut G. Stan wrote: Hi, I'm doing TDD in pretty much all of the languages that I know, and I want to introduce it early in my Haskell learning process. I

Re: [Haskell-cafe] MultiParamClasses question

2010-05-25 Thread Daniel Fischer
On Tuesday 25 May 2010 20:51:06, Eugeny N Dzhurinsky wrote: Hello, all! I'm trying to create set of polymorphic functions for working with custom containers. I decided to try out typeclass and define generic function, which uses the methods from the typeclass. The quick and naive solution is

Re: [Haskell-cafe] Math questions

2010-05-25 Thread Daniel Fischer
On Tuesday 25 May 2010 23:47:30, Mujtaba Boori wrote: Hello I am try to solve this equation Define a higher order function that tests whether two functions , both defined on integers , coincide for all integers between 1 and 100 how can I solve this ? is there any thing in Haskell

Re: [Haskell-cafe] Re: [Gtk2hs-users] Problem when installing gtk2hs.

2010-05-27 Thread Daniel Fischer
On Thursday 27 May 2010 08:46:04, Magicloud Magiclouds wrote: I only have one alex installed under ~/.cabal/bin. It seems working with shell environment, but not cabal. My guess: You added ~/.cabal/bin to the path, but have quoted the path, like export PATH=~/.cabal/bin:$PATH in your

Re: [Haskell-cafe] Why Either = Left | Right instead of something like Result = Success | Failure

2010-05-28 Thread Daniel Fischer
On Friday 28 May 2010 20:44:20, Donn Cave wrote: Quoth Vo Minh Thu not...@gmail.com, ... Control.Monad.Error provides an instance for Either. ... in the mtl transformer library, in case anyone else besides myself didn't know that. And I see it has to be there because it depends on the

Re: [Haskell-cafe] Why Either = Left | Right instead of something like Result = Success | Failure

2010-05-28 Thread Daniel Fischer
On Saturday 29 May 2010 01:28:59, Ivan Lazar Miljenovic wrote: Daniel Fischer daniel.is.fisc...@web.de writes: On Friday 28 May 2010 20:44:20, Donn Cave wrote: Quoth Vo Minh Thu not...@gmail.com, ... Control.Monad.Error provides an instance for Either. ... in the mtl transformer

Re: [Haskell-cafe] Why Either = Left | Right instead of something like Result = Success | Failure

2010-05-28 Thread Daniel Fischer
On Saturday 29 May 2010 02:26:38, Ivan Lazar Miljenovic wrote: Daniel Fischer daniel.is.fisc...@web.de writes: But if you want to have instance Monad (Either ConcreteType) where ... , you can have fail msg = Left someDefaultValue (or let the value depend on the message

Re: [Haskell-cafe] Pugs with GHC 6.12

2010-06-01 Thread Daniel Fischer
On Tuesday 01 June 2010 16:58:53, Simon Thompson wrote: Has anyone successfully compiled Pugs with GHC 6.12? $ pugs +RTS --info [(GHC RTS, YES) ,(GHC version, 6.12.1) ,(RTS way, rts_v) ,(Host platform, i386-unknown-linux) ,(Host architecture, i386) ,(Host OS, linux) ,(Host vendor,

Re: [Haskell-cafe] Installing Curl on Windows 7 - permissions problem

2010-06-01 Thread Daniel Fischer
On Monday 31 May 2010 23:50:58, Ralph Hodgson wrote: Don, More angst with Windows 7 permissions. I hope this is a simple thing for you or someone else to help me with. I have successfully installed other packages into my private cabal area. When it came to the Haskell curl package,

Re: [Haskell-cafe] Difference between div and /

2010-06-01 Thread Daniel Fischer
On Tuesday 01 June 2010 20:26:55, Jonas Almström Duregård wrote: One might expect a == (a/b)*b and other common arithmetic formulas to hold for division? /Jonas Better not if one's using Float or Double. ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Dependency issues with GHC 6.12.2 installing parsec and others

2010-06-01 Thread Daniel Fischer
On Tuesday 01 June 2010 22:31:21, Ralph Hodgson wrote: base-3.0.3.2-b2241f4c659fe250ebb821a4173f40c9 doesn't exist (use --force to override) You probably have a package.conf from the previous GHC still lying around. If your new GHC is in the system space, it'll probably be enough to remove

Re: [Haskell-cafe] Difference between div and /

2010-06-01 Thread Daniel Fischer
division in Python, C, Java or C#. Of course this doesn't work on Integers... /J On 1 June 2010 21:08, Daniel Fischer daniel.is.fisc...@web.de wrote: On Tuesday 01 June 2010 20:26:55, Jonas Almström Duregård wrote: One might expect a == (a/b)*b and other common arithmetic formulas

Re: [Haskell-cafe] A question on existential types and Church encoding

2010-06-01 Thread Daniel Fischer
On Tuesday 01 June 2010 23:21:35, Dan Doel wrote: I think SPJ is on record as saying it would add a lot of complexity to the current GHC type system, and I'm inclined to believe him. In matters concerning the GHC type system, that's a fairly natural stance, I think.

<    1   2   3   4   5   6   7   8   9   10   >