Re: Multiple imports on a single line

2017-02-01 Thread Malcolm Wallace
You can already write this, with only a tiny bit of syntax: module MyApp where import Data.Text; import Data.Foldable; import Control.Concurrent Whether it is good style is another matter, but all compilers will certainly accept it. Regards, Malcolm On 1 Feb 2017, at 14:18, Vassil

Re: type error formatting

2015-10-24 Thread Malcolm Wallace
On 24 Oct 2015, at 09:17, Joachim Breitner wrote: > For example in > >>Relevant bindings include >> syllables :: [(a1, Syllable)] >> (bound at Derive/Call/India/Pakhawaj.hs:141:16) >> best_match :: [(a1, Syllable)] >> -> Maybe (Int, ([(a1, Syllable)],

Re: [Haskell-cafe] MRP, 3-year-support-window, and the non-requirement of CPP

2015-10-06 Thread Malcolm Wallace
On 6 Oct 2015, at 17:47, Herbert Valerio Riedel wrote: > >> The problem by discussions is that they are done between two groups with >> quite a difference in experience. On one hand you have people like Bryan, >> who have considerable contributions to the Haskell ecosystem and much >>

Re: Monad of no `return` Proposal (MRP): Moving `return` out of `Monad`

2015-10-05 Thread Malcolm Wallace
mation about Haskell, is a powerful disincentive to continue with it. Regards, Malcolm > On 5 Oct 2015, at 10:05, Malcolm Wallace wrote: > >> I am also a strong -1 on small changes that break huge numbers of things for >> somewhat trivial benefits. >> >> Regards, &

Re: [Haskell-cafe] RFC: Native -XCPP Proposal

2015-05-08 Thread Malcolm Wallace
exist. Maybe they do but are too afraid to speak up (due to corporate policy or whatever). On Thu, May 7, 2015 at 10:41 PM, Malcolm Wallace malcolm.wall...@me.com wrote: I also note that in this discussion, so far not a single person has said that the cpphs licence would actually

Re: [Haskell-cafe] RFC: Native -XCPP Proposal

2015-05-08 Thread Malcolm Wallace
On 8 May 2015, at 00:06, Richard A. O'Keefe wrote: I think it's important that there be *one* cpp used by Haskell. fpp is under 4 kSLOC of C, and surely Haskell can do a lot better. FWIW, cpphs is about 1600 LoC today. Regards, Malcolm ___

Re: RFC: Native -XCPP Proposal

2015-05-07 Thread Malcolm Wallace
licensing issues: perhaps we should simply ask Malcolm Wallace if he would consider changing the license for the sake of GHC? Or perhaps he could grant a custom-tailored license to the GHC project? After all, the project page [1] says: If that's a problem for you, contact me to make other arrangements

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Malcolm Wallace
On 20 Jan 2015, at 11:20, Björn Peemöller wrote: The reason is the usage of foldr, which changed its type from foldr :: (a - b - b) - b - [a] - b -- GHC 7.8.4 to foldr :: Foldable t = (a - b - b) - b - t a - b -- GHC 7.10.1 Thus, the use of foldr is now ambiguous. I can fix this by

Re: ANNOUNCE: GHC 7.10.1 Release Candidate 1 - feedback on Mac OS

2015-01-01 Thread Malcolm Wallace
On 1 Jan 2015, at 13:58, George Colpitts wrote: Configuring cpphs-1.13... Building cpphs-1.13... Warning: cpphs.cabal: Unknown fields: build-depends (line 5) Could not find module ‘Prelude’ It is a member of the hidden package ‘base-4.8.0.0’. Perhaps you need to add ‘base’ to

Re: The future of the haskell2010/haskell98 packages - AKA Trac #9590

2014-09-30 Thread Malcolm Wallace
How about doing the honest thing, and withdrawing both packages in ghc-7.10? Haskell'98 is now 15 years old, and the 2010 standard was never really popular anyway. Regards, Malcolm On 30 Sep 2014, at 21:21, Austin Seipp aus...@well-typed.com wrote: Hello developers, users, friends, I'd

Re: RFC: changes to -i flag for finding source files

2014-04-25 Thread Malcolm Wallace
On 25 Apr 2014, at 14:17, Simon Marlow wrote: The problem we often have is that when you're writing code for a library that lives deep in the module hierarchy, you end up needing a deep directory structure, where the top few layers are all empty. I don't see how this is a problem at all.

Re: Mac CPP problem with ghc-clang-wrapper

2014-03-18 Thread Malcolm Wallace
Yes, this is a known problem. I intend to put out a fresh version of HaXml soon to fix it. Regards, Malcolm On 18 Mar 2014, at 15:17, Christian Maeder wrote: Hi, under mavericks using the ghc-clang-wrapper (ghc-7.6) or using ghc-7.8.20140130 I can no longer install the HaXml

Re: [Haskell-cafe] A question regarding reading CPP definitions from a C header

2013-10-07 Thread Malcolm Wallace
If you use cpphs as a library, there is an API called runCpphsReturningSymTab. Thence you can throw away the actual pre-preprocessed result text, keep only the symbol table, and lookup whatever macros you wish to find their values. I suggest you make this into a little code-generator, to

Re: [Haskell-cafe] cpphs calls error when it finds an #error declaration

2013-08-28 Thread Malcolm Wallace
On 27 Aug 2013, at 08:33, Niklas Hambüchen wrote: @Malcolm, would you mind a change towards throwing an exception that is different from error so that it can be easily caught, or even better, a change from runCpphs :: ... - IO String to runCpphs :: ... - IO (Either String

Re: cascading type errors in ghc

2013-08-09 Thread Malcolm Wallace
On 6 Aug 2013, at 20:03, Evan Laforge wrote: I don't know how others like to work, but I like when a compiler bails early, because I fix errors one at a time, and I search for the easiest looking ones before worrying about the complicated looking ones. With C compilers, it is often the case

Re: [Haskell-cafe] Why GHC is written in Happy and not a monadic parser library?

2013-08-04 Thread Malcolm Wallace
On 3 Aug 2013, at 21:03, Jason Dagit wrote: Another con of using parsec that I forgot to mention in my previous email is that with Parsec you need to be explicit about backtracking (use of try). Reasoning about the correct places to put try is not always easy and parsec doesn't help you with

Re: [Haskell-cafe] Why GHC is written in Happy and not a monadic parser library?

2013-08-03 Thread Malcolm Wallace
On 3 Aug 2013, at 02:20, Jason Dagit wrote: Hi! Is there any specific reason why GHC is written in a parser GENERATOR (Happy) and not in MONADIC PARSER COMBINATOR (like parsec)? Is Happy faster / handles better errors / hase some great features or anything else? One reason is that it

Re: [Haskell-cafe] Casting newtype to base type?

2013-07-01 Thread Malcolm Wallace
On 1 Jul 2013, at 16:07, Vlatko Basic wrote: I had a (simplified) record data P = P { a :: String, b :: String, c :: IO String } deriving (Show, Eq) but to get automatic deriving of 'Show' and 'Eq' for 'data P' I have created 'newtype IOS' and its 'Show' and 'Eq'

Re: Overloaded record fields

2013-06-28 Thread Malcolm Wallace
On 28 Jun 2013, at 12:16, AntC wrote: Thanks Simon, I'm a little puzzled what your worry is. f r b = r.foo b With dot-notation baked in (non-orthogonally), f would get the type f :: (r { foo::Bool }) = r - Bool - Bool With the orthogonal proposal, f is equivalent to

Re: [Haskell-cafe] code to HTML

2013-06-03 Thread Malcolm Wallace
On 3 Jun 2013, at 20:38, Corentin Dupont wrote: I'd like to transform a .hs file into a .html file. The objective is that the .html file, when rendered, looks exactly the same that the .hs, with the exeption that every function in the code is a link to its haddock documentation. Is that

Re: [Haskell-cafe] GSoC proposal: Haskell AST-based refactoring and API upgrading tool

2013-04-29 Thread Malcolm Wallace
On 29 Apr 2013, at 07:00, Niklas Hambüchen wrote: I would like to propose the development of source code refactoring tool that operates on Haskell source code ASTs and lets you formulate rewrite rules written in Haskell. Seen this? http://www.haskell.org/haskellwiki/HaRe Regards,

Re: [Haskell-cafe] Prolog-style patterns

2013-04-09 Thread Malcolm Wallace
On 9 Apr 2013, at 14:46, Sturdy, Ian wrote: As far as the use of Eq goes, Eq is already enshrined in pattern matching by pattern matching against literals. Not true. Pattern-matching literals explicitly avoids any use of Eq. Demonstration: data Foo = Foo | Bar instance Eq Foo where _

Re: [Haskell-cafe] GSoC Project Proposal: Markdown support for Haddock

2013-04-08 Thread Malcolm Wallace
And cpphs strips C comments too. :-) But seriously, John's use-case is the exact opposite of what you suggest. John wants to keep the # inside the comment block. You suggest to remove the comment-block altogether? When I checked the example with cpphs, it turns out that the # line is

Re: [Haskell-cafe] GSoC Project Proposal: Markdown support for Haddock

2013-04-08 Thread Malcolm Wallace
On 8 Apr 2013, at 14:52, Roman Cheplyaka wrote: In my opinion, it is perfectly valid to have intentional preprocessor directives inside Haskell comments. Could you give an example where this is useful? ... macro expansions inside the comments are rather exotic. {- | Some module

Re: [Haskell-cafe] Layout section of Haskell 2010 Language Report -- Notes 12

2013-04-02 Thread Malcolm Wallace
On 1 Apr 2013, at 01:21, Seth Lastname wrote: Note 2 says, If the first token after a 'where' (say) is not indented more than the enclosing layout context, then the block must be empty, so empty braces are inserted. It seems that, in Note 2, the first token necessarily refers to a lexeme

Re: [Haskell-cafe] cabal install ghc-mod installs 3 years old version

2013-03-01 Thread Malcolm Wallace
Doesn't Cabal tend to install library packages under the .cabal folder? So blowing it away gets rid of the problematic ones. (And everything else.) On 25 Feb 2013, at 16:56, Brent Yorgey wrote: On Sun, Feb 24, 2013 at 02:33:55PM +, Niklas Hambüchen wrote: You are right, my ghc-7.4.2 was

[Haskell-cafe] ANN: lazy-csv - the fastest and most space-efficient parser for CSV

2013-02-25 Thread Malcolm Wallace
There are lots of Haskell CSV parsers out there. Most have poor error-reporting, and do not scale to large inputs. I am pleased to announce an industrial-strength library that is robust, fast, space-efficient, lazy, and scales to gigantic inputs with no loss of performance.

Re: [Haskell-cafe] ANN: lazy-csv - the fastest and most space-efficient parser for CSV

2013-02-25 Thread Malcolm Wallace
On 25 Feb 2013, at 11:14, Oliver Charles wrote: Obvious question: How does this compare to cassava? Especially cassava's Data.CSV.Incremental module? I specifically ask because you mention that it's It is lazier, faster, more space-efficient, and more flexible in its treatment of errors,

[Haskell] Call for Nominations: Haskell Prime language committee

2013-02-04 Thread Malcolm Wallace
Dear Haskell lovers, The Haskell Prime process for standardisation of new versions of the Haskell language is at something of an impasse. Since the Haskell 2010 Report was issued (at the end of 2009), there has been very little momentum to formalise existing extensions and generalisations,

Call for Nominations: Haskell Prime language committee

2013-02-04 Thread Malcolm Wallace
Dear Haskell lovers, The Haskell Prime process for standardisation of new versions of the Haskell language is at something of an impasse. Since the Haskell 2010 Report was issued (at the end of 2009), there has been very little momentum to formalise existing extensions and generalisations,

[Haskell-cafe] Call for Nominations: Haskell Prime language committee

2013-02-04 Thread Malcolm Wallace
Dear Haskell lovers, The Haskell Prime process for standardisation of new versions of the Haskell language is at something of an impasse. Since the Haskell 2010 Report was issued (at the end of 2009), there has been very little momentum to formalise existing extensions and generalisations,

Re: Status of Haskell'?

2013-01-05 Thread Malcolm Wallace
On 28/12/2012, at 1:01, Ramana Kumar ram...@member.fsf.org wrote: On Wed, Dec 12, 2012 at 6:40 PM, Malcolm Wallace malcolm.wall...@me.com wrote: There is a mailing list for the members of the language committee: haskell-2011-commit...@haskell.org. Hi Malcolm, could you (or someone

Re: [Haskell-cafe] Hackage suggestion: Gather the list of the licenses of all dependencies of a package

2012-12-15 Thread Malcolm Wallace
On 13 Dec 2012, at 18:40, Michael Snoyman wrote: I'm not quite certain what to make of: If you have a commercial use for cpphs, and feel the terms of the (L)GPL are too onerous, you have the option of distributing unmodified binaries (only, not sources) under the terms of a different

Re: [Haskell-cafe] Hackage suggestion: Gather the list of the licenses of all dependencies of a package

2012-12-15 Thread Malcolm Wallace
On 13 Dec 2012, at 10:41, Petr P wrote: In particular, we can have a BSD package that depends on a LGPL package, and this is fine for FOSS developers. But for a commercial developer, this can be a serious issue that is not apparent until one examines *every* transitive dependency. This

Re: [Haskell-cafe] Hackage suggestion: Gather the list of the licenses of all dependencies of a package

2012-12-15 Thread Malcolm Wallace
On 15 Dec 2012, at 16:54, Michael Snoyman wrote: I would strongly recommend reconsidering the licensing decision of cpphs. Even if the LICENSE-commercial is sufficient for non-source releases of software to be protected[1], it introduces a very high overhead for companies to need to

Re: Status of Haskell'?

2012-12-12 Thread Malcolm Wallace
I confess that I have not had enough free time in the last two years to have been a good chair for the language committee. (Using Haskell in the real world is just too absorbing!) I think the next chair should probably be an academic, who may have more incentive to spend effort on

Re: [Haskell-cafe] Is it possible to have constant-space JSON decoding?

2012-12-07 Thread Malcolm Wallace
See also the incremental XML parser in HaXml, described in Partial parsing: combining choice with commitment, IFL 2006. It has constant space usage (for some patterns of usage), even with extremely large inputs. http://www.google.co.uk/url?sa=trct=jq=malcolm+wallace+partial+parsingsource=webcd

Re: [GHC] #7473: getModificationTime gives only second-level resolution

2012-12-03 Thread Malcolm Wallace
Replying by email, since my account on the trac is blocked. Open Shake implements the finer resolution timestamps needed using the Win32 API. You may want to copy/adapt the code from there:

Re: [Haskell-cafe] tplot (out of memory)

2012-11-30 Thread Malcolm Wallace
For the record, it turned out that the key difference between the linux machines was the fonts packages installed via RPM. The strace utility told me that the crash happened shortly after cairo/pango attempted (and failed) to open some font configuration files. After installing some of the

Re: [Haskell-cafe] Survey: What are the more common Haskell IDEs in use ?

2012-11-24 Thread Malcolm Wallace
At my workplace, most people who code in Haskell use MS Visual Studio as their Haskell IDE. :-) But they don't read Haskell-cafe... Regards, Malcolm On 24 Nov 2012, at 07:28, Dan wrote: Because I see there are many preferences on what IDE to use for Haskell I've created a quick survey

Re: [Haskell] HaXml

2012-11-11 Thread Malcolm Wallace
On 9 Nov 2012, at 23:04, Michael Mossey wrote: Couldn't match expected type Text.XML.HaXml.Types.QName with actual type String. Poking around, I found this webpage describing an issue with a change to HaXml that happened after version 1.20.2:

Re: [Haskell-cafe] Optimal line length for haskell

2012-10-29 Thread Malcolm Wallace
It is kind of ironic that the wide code examples in the blog post are wrapped at 65 chars by the blog formatting. Regards, Malcolm On 29 Oct 2012, at 11:50, Rustom Mody wrote: There was a recent discussion on the python list regarding maximum line length. It occured to me that

Re: [Haskell-cafe] GHC maintenance on Arch

2012-10-29 Thread Malcolm Wallace
I think you will find that the Original Poster did not ask about ArchHaskell, but rather about Haskell on the Arch platform. He was completely unaware of ArchHaskell as a project. This might be a source of some confusion, and help to explain divergent attitudes. Regards, Malcolm On 29

Re: [Haskell-cafe] Either Monad and Laziness

2012-09-18 Thread Malcolm Wallace
On 12 Sep 2012, at 16:04, Eric Velten de Melo wrote: The behaviour I want to achieve is like this: I want the program when compiled to read from a file, parsing the PGM and at the same time apply transformations to the entries as they are read and write them back to another PGM file. Such

Re: [Haskell-cafe] COBOL-85 parser, anyone?

2012-07-20 Thread Malcolm Wallace
Ralf Laemmel would probably be the world's foremost expert in parsing and analysing Cobol using functional languages. Try contacting him directly at uni-koblenz.de Some of his relevant papers: http://homepages.cwi.nl/~ralf/padl03/ http://homepages.cwi.nl/~ralf/ctp/ On 20 Jul 2012, at 10:08,

Re: [Haskell-cafe] Performance with do notation, mwc-random and unboxed vector

2012-06-11 Thread Malcolm Wallace
On 11 Jun 2012, at 10:38, Dmitry Dzhus wrote: main = do g - create e' - VU.replicateM count $ standard g return () In all likelhood, ghc is spotting that the value e' is not used, and that there are no side-effects, so it does not do anything at runtime. If you expand the action

Re: Strange behavior in GHC-compiled code

2012-05-25 Thread Malcolm Wallace
Unless you show us the code, any answers will be guesses in the dark. Does your program use unsafePerformIO unsafely perhaps? Or a version of a library that happens to have a known bug? On 25/05/2012, at 14:33, Mark Conway Wirt markcw...@gmail.com wrote: I have a piece of Haskell code

Re: [Haskell-cafe] Generalizing (++) for monoids instead of using ()

2012-05-04 Thread Malcolm Wallace
On 4 May 2012, at 10:02, Alberto G. Corona wrote: Restrict (++) String - String - String that locally would restrict the type within the module. import qualified Prelude import Prelude hiding ((++)) (++) :: String - String - String (++) = Prelude.(++)

Re: What is a punctuation character?

2012-03-16 Thread Malcolm Wallace
no purpose to a completely overlapping category unless it is intended to relate to an earlier standard (say Haskell 1.4). I believe all Haskell Reports, even since 1.0, have specified that the language uses Unicode. If it helps to bring perspective to this discussion, it is my impression

Re: [Haskell-cafe] Impact of try on Parsec performance

2012-03-03 Thread Malcolm Wallace
On 3 Mar 2012, at 04:30, Omari Norman wrote: On the other hand, I notice that attoparsec and polyparse backtrack by default, and attoparsec claims to be faster than Parsec (I can't remember if polyparse makes this claim). In my benchmarks, polyparse has about the same performance as

Re: Error while installing new packages with GHC 7.4.1

2012-02-29 Thread Malcolm Wallace
On 29 Feb 2012, at 09:53, Antoras wrote: I updated my GHC version from 7.0.3 to 7.4.1. But after that GHC is unable to install some required packages. containers-0.4.2.1 (reinstall) changes: array-0.4.0.0 - 0.3.0.3 binary-0.5.1.0 (reinstall) changes: array-0.4.0.0 - 0.3.0.3 I believe

Re: Proposal: require spaces around the dot operator

2012-02-10 Thread Malcolm Wallace
-1. I agree with John. There is no point in fiddling with the dots, until we have real experience with a new records proposal (which can be implemented entirely without using dot, at least initially). Regards, Malcolm On 10 Feb 2012, at 03:14, John Meacham wrote: I mean, it is not

Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution

2012-02-08 Thread Malcolm Wallace
On 8/02/2012, at 14:16, Steve Horne sh006d3...@blueyonder.co.uk wrote: I haven't given a lot of thought to updates. I very much fail to see the point of replacing prefix function application with postfix dots, merely for field selection. There are already some imperfect, but adequate,

Re: [Haskell-cafe] FP activities and researchers in Warwickshire

2012-02-07 Thread Malcolm Wallace
Fun in the afternoon, a termly gathering of UK FP people, will be in Oxford on 28th Feb. http://sneezy.cs.nott.ac.uk/fun/ On 7/02/2012, at 18:32, Ivan Perez ivanperezdoming...@gmail.com wrote: Hello, I recently moved to Kenilworth, Warwickshire, UK, and I'd like to know if there are

Re: [Haskell-cafe] strict version of Haskell - does it exist?

2012-01-30 Thread Malcolm Wallace
On 29 Jan 2012, at 22:25, Ertugrul Söylemez wrote: A strict-by-default Haskell comes with the implication that you can throw away most of the libraries, including the base library. So yes, a strict-by-default Haskell is very well possible, but the question is whether you actually want that.

Re: [Haskell-cafe] [C][enums][newbie] What is natural Haskell representation of such enum?

2012-01-23 Thread Malcolm Wallace
2012/1/22 Данило Глинський abcz2.upr...@gmail.com What is natural Haskell representation of such enum? enum TypeMask { UNIT, GAMEOBJECT, CREATURE_OR_GAMEOBJECT = UNIT | GAMEOBJECT }; I don't think that definition makes any sense in C, because UNIT is 0, so UNIT | GAMEOBJECT

Re: [Haskell-cafe] Can't install hspec

2012-01-23 Thread Malcolm Wallace
On 23 Jan 2012, at 07:01, Erik de Castro Lopo wrote: /tmp/hspec-0.9.04062/hspec-0.9.0/Setup.lhs:2:10: Could not find module `System' It is a member of the hidden package `haskell98-2.0.0.0'. In ghc-7.2, you cannot use the haskell98 package in conjunction with the base

Posting etiquette, was Re: Records in Haskell

2012-01-19 Thread Malcolm Wallace
Sorry to pick on your post in particular Matthew, but I have been seeing a lot of this on the Haskell lists lately. I find it completely unreasonable for a reply to a very long post to quote the entire text, only to add a single line at the bottom (or worse, embedded in the middle somewhere).

Re: Composition operator [was: Re: Records in Haskell]

2012-01-12 Thread Malcolm Wallace
On 12 Jan 2012, at 18:41, Evan Laforge wrote: Unicode dot (∘) would be optimal, since that's what it's for. Is ∘ (U+2218 RING OPERATOR)* in Prelude yet? We should propose that.** However, changing the composition operator from (.) will involve huge amounts of changes to source code.

Re: [Haskell-cafe] HaXml 1.13 - 1.22 upgrade

2011-12-11 Thread Malcolm Wallace
The extra parameter i is for information attached to each node of the tree. As you have correctly guessed, the parser fills in this field with positional information relating to the original source document, which is useful for instance if you are validating or checking the original document.

Re: [Haskell-cafe] Tracing Prelude.read exceptions

2011-12-11 Thread Malcolm Wallace
I suggest switching from 'read' to a real parser that can give you proper error messages. I use Text.Parse from the polyparse package, which is designed to parse back exactly the format produced by derived Show instances. To derive the Parse class from your datatypes, the tool DRiFT is handy.

Re: [Haskell-cafe] Does anyone maintain trac.haskell.org?

2011-12-09 Thread Malcolm Wallace
The community Trac hosting server isn't sending email, which Trac requires. I've submitted several tickets to supp...@community.haskell.org but gotten no response. Does anyone maintain that server anymore? Had the same problem in July. Raised a ticket etc. I don't think there is anyone

Re: [Haskell-cafe] GHCi and Cairo on Windows

2011-12-05 Thread Malcolm Wallace
On Windows, it is necessary to add to your PATH variable the bin directory where the gtk+ DLL lives. Note, this is the C DLL, not the Haskell one produced by gtk2hs. For instance, on my machine the relevant directory is C:\workspace\ext\gtk+-2.20\bin. It is quite likely different on yours.

Re: [Haskell-cafe] Hackage down!

2011-12-01 Thread Malcolm Wallace
And, amusingly, http://downforeveryoneorjustme.com/ is also down, having exceeded its Google App Engine quota. [ But the similarly named .org site still works, and confirms that hackage is down. ] Regards, Malcolm ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Superset of Haddock and Markdown

2011-11-21 Thread Malcolm Wallace
On 20 Nov 2011, at 22:20, Ivan Lazar Miljenovic wrote: On 21 November 2011 03:19, David Fox dds...@gmail.com wrote: On Fri, Nov 18, 2011 at 1:10 AM, Ertugrul Soeylemez e...@ertes.de wrote: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote: Wasn't there talk at one stage of integrating

Re: [Haskell-cafe] Package documentation complaints -- and a suggestion

2011-10-30 Thread Malcolm Wallace
The problem isn't social pressure to be stable, it's the ambiguity of what stable means. If Hackage 2 institutes a policy whereby things claiming to be stable are treated better, then stable is likely to become the new experimental. I'd say, rather than rely on social agreement on what

Re: [Haskell-cafe] Fwd: how to increase the stack size

2011-10-17 Thread Malcolm Wallace
when I am running the program in my terminal on ubuntu its showing me GHC stack-space overflow: current limit is 536870912 bytes. Use the `-Ksize' option to increase it. how can i increase the stack sizePlz help me out Others have explained how to Use the `-Ksize' option,

Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-03 Thread Malcolm Wallace
Although I still wonder why something so simple in C++ is actually more verbose and requires less known features in Haskell...What was the design intent to disallow simple overloading? The simple C++ overloading you want to add to Haskell, is in fact rather semantically complex, and it

Re: [GHC] #5509: quotes pretty-printer not working as comments specify

2011-09-27 Thread Malcolm Wallace
From compiler/utils/Outputable.lhs {{{ -- quotes encloses something in single quotes... -- but it omits them if the thing ends in a single quote -- so that we don't get `foo''. Instead we just have foo'. quotes d = SDoc $ \sty - let pp_d = runSDoc d sty in case show

Re: [Haskell-cafe] mapM is supralinear?

2011-09-27 Thread Malcolm Wallace
On 26 Sep 2011, at 23:14, Arseniy Alekseyev wrote: Garbage collection takes amortized O(1) per allocation, doesn't it? No. For Mark-Sweep GC, the cost is proportional to (H+R) / (H-R) where H is the total heap size R is the reachable (i.e. live) heap This formula amortises the cost of

Re: [Haskell-cafe] mapM is supralinear?

2011-09-27 Thread Malcolm Wallace
On 27 Sep 2011, at 11:23, Arseniy Alekseyev wrote: Malcolm, one should amortize the cost of the collection over the amount of free space allocated rather than recovered They are the same thing. You can only allocate from the space that has been recovered. It is true that generational GC

Re: Please apply the comparison function given to nubBy to elements of the list in the order in which they occur in the list.

2011-09-20 Thread Malcolm Wallace
If this is a _proposal_ to change ghc's non-Report-compatible Data.List implementation to match the behaviour of the Report implementation, then count me as a +1. I think an important convention when it comes to higher order functions on lists is that to the extent which is possible, the

Re: [Haskell-cafe] Categorized Weaknesses from the State of Haskell 2011 Survey

2011-09-13 Thread Malcolm Wallace
On 13 Sep 2011, at 18:59, Michael Orlitzky wrote: Malcolm Wallace and Colin Runciman's ICFP99 paper functioned well as a tutorial for HaXml when I used it - maybe it is a bit out of date now? HaXml is hardly a dire case. The paper is out-of-date, so it's worse than useless: you'll waste

Re: integer-simple

2011-07-31 Thread Malcolm Wallace
I notice that ghci is loading integer-simple before loading base. This at least explains why it cannot find a symbol from the base package - it hasn't been loaded yet. So the question is why does integer-simple use any function from the base package at all? I'm fairly sure that the dependency

Re: [Haskell-cafe] partial inheritance

2011-07-19 Thread Malcolm Wallace
On 19/07/2011, at 0:09, Patrick Browne patrick.bro...@dit.ie wrote: instance Bird Emperor where -- No fly method walk x y = y instance Penguin Emperor where -- How can I override the walk method in the instance Penguin? -- walk x y = x Why would you want to override the walk method

Re: [Haskell-cafe] Inconsistent trailing comma in export list and record syntax

2011-07-11 Thread Malcolm Wallace
That just shifts the problem, I think? Now you can no longer comment out the first line. If you are using to-end-of-line comments with --, then the likelihood of noticing a leading ( or { on the line being commented, is much greater than the likelihood of noticing a trailing comma on the

Re: [Haskell-cafe] Data.Time

2011-07-03 Thread Malcolm Wallace
On 2 Jul 2011, at 22:13, Yitzchak Gale wrote: [1]http://hackage.haskell.org/package/timezone-series [2]http://hackage.haskell.org/package/timezone-olson I'd just like to add that these timezone packages are fantastic. They are extremely useful if you need accurate conversion between

Re: Proposal: fix simple pattern binding and declaration group

2011-07-01 Thread Malcolm Wallace
Once you guys have reached consensus on appropriate revised wording for this issue, I'll happily apply the changes to the Haskell 2012 Report as a bugfix. Regards, Malcolm ___ Haskell-prime mailing list Haskell-prime@haskell.org

Re: [Haskell-cafe] Patterns for processing large but finite streams

2011-07-01 Thread Malcolm Wallace
Sure you can. runningAverage :: Int - [Double] - [Double] runningAverage n xs = let chunk = take n xs in (sum chunk / length chunk) : runningAverage (tail xs) Lazy lists are absolutely ideal for this purpose. Regards, Malcolm On 1 Jul 2011, at 07:33, Eugene Kirpichov

Re: [Haskell-cafe] Alex Lexer Performance Issues

2011-06-26 Thread Malcolm Wallace
On 22 Jun 2011, at 15:53, Tristan Ravitch wrote: On Wed, Jun 22, 2011 at 07:48:40AM +0100, Stephen Tetley wrote: How fast is good old String rather than ByteString? For lexing, String is a good fit (cheap deconstruction at the head / front). For your particular case, maybe it loses due to

Re: [Haskell-cafe] Data.Time

2011-06-26 Thread Malcolm Wallace
On 26 Jun 2011, at 01:53, Tony Morris wrote: Having only had a flirt with Data.Time previously, I assumed it would be robust like many other haskell libraries. If, by lack of robustness, you mean that you get runtime errors, then consider them bugs, and file them with the author/maintainer

Re: [Haskell-cafe] Why aren't there anonymous sum types in Haskell?

2011-06-21 Thread Malcolm Wallace
On 21 Jun 2011, at 20:53, Elliot Stern wrote: A tuple is basically an anonymous product type. It's convenient to not have to spend the time making a named product type, because product types are so obviously useful. Is there any reason why Haskell doesn't have anonymous sum types? If

Re: [Haskell-cafe] Haskell *interpreter* on iPad? (Scheme and Ocaml are there)

2011-06-19 Thread Malcolm Wallace
On 18 Jun 2011, at 20:19, Jack Henahan wrote: but the dev would either be forced into Hugs, or they'd have to implement a more portable GHC. Does such a thing exist already? Just as a point of interest, the original nhc compiler was original written for an ARM architecture machine (Acorn

Re: GHC and Haskell 98

2011-06-18 Thread Malcolm Wallace
As one of the few people who has habitually used Haskell'98 wherever possible, I favour plan A. As I recently discovered, in ghc 7 it is already very fragile to attempt to depend on both the base and haskell98 packages simultaneously. In most cases it simply doesn't work. Removing those few

Re: TypeFamilies vs. FunctionalDependencies type-level recursion

2011-06-16 Thread Malcolm Wallace
| Is there a policy that only a proposal's owner can modify the wiki | page? Or that you have to be a member of the Haskell' committee? I'm not sure. Malcolm Wallace is chair at the moment; I'm ccing him. I have no idea: I neither set up the wiki, nor do I have any interesting admin

Re: How to install GhC on a Mac without registering?

2011-06-12 Thread Malcolm Wallace
On 10 Jun 2011, at 02:15, Manuel M T Chakravarty wrote: Anybody who is halfway serious about developing software on a Mac will have Xcode installed anyway. As the original poster clarified, the motivating use-case is education (specifically a class of 12-13 year olds.) These are not

Re: [Haskell-cafe] location of IEEE Viz code ?

2011-06-12 Thread Malcolm Wallace
http://hackage.haskell.org/trac/PolyFunViz/wiki/IEEEVisCode talks about the code being available through darcs but I can't seem to put my hands on the http address I would need to pull the code. This is all relating to the paper, Huge Data but Small Programs: Visualization Design via

Re: [Haskell-cafe] SIGPLAN Programming Languages Software Award

2011-06-10 Thread Malcolm Wallace
Curious observation: Object languageType language OO (C++)functional functional (Haskell)logical It makes me wonder what comes next... To be more accurate, it was Functional Dependencies that introduced a logic programming language to the type

Re: [Haskell-cafe] SIGPLAN Programming Languages Software Award

2011-06-08 Thread Malcolm Wallace
More seriously, the influence of Haskell over F# (and even Python) is undoubted, but do you really think Haskell influenced Java Generics? (IMHO they were more inspired from C++ templates) (That is a question, not an assertion). Phil Wadler had a hand in designing both Haskell and Java

Re: [Haskell-cafe] Type Constraints on Data Constructors

2011-06-08 Thread Malcolm Wallace
data Bar f a = Foo f = Bar {bar :: f a} The class context on the data constructor buys you nothing extra in terms of expressivity in the language. All it does is force you to repeat the context on every function that uses the datatype. For this reason, the language committee has decided

Re: How to install GhC on a Mac without registering?

2011-06-06 Thread Malcolm Wallace
On 6 Jun 2011, at 13:49, Lyndon Maydwell wrote: I would be fantastic if XCode wasn't a dependency. ... Not to detract at all from the work of the wonderful GHC and Haskell Platform contributors in any way. For me it would just make it that much easier to convince mac-using friends to give

Re: [Haskell-cafe] How to install GhC on a Mac without registering?

2011-06-06 Thread Malcolm Wallace
it won't be a pleasant choice to fork over a good chunk of money to Apple for the use of free software that they didn't develop. Whilst I acknowledge your painful situation, I'd like to rebut the idea that Apple stole someone else's free software and are selling it on. In fact, Apple

Re: [Haskell-cafe] How to install GhC on a Mac without registering?

2011-06-06 Thread Malcolm Wallace
On 6 Jun 2011, at 13:49, Lyndon Maydwell wrote: I would be fantastic if XCode wasn't a dependency. ... Not to detract at all from the work of the wonderful GHC and Haskell Platform contributors in any way. For me it would just make it that much easier to convince mac-using friends to give

Re: [Haskell-cafe] Fwd: Abnormal behaviors when Using ghci

2011-06-05 Thread Malcolm Wallace
On 5/06/2011, at 13:12, 吴兴博 wux...@gmail.com wrote: 1) I'm using Haskell platform 2011.2 on windows (7). Every several days, ghci will crash with no messages. even when I'm just typing with text buffer, without an 'enter'. I got nothing after the crash, not even an exception code, don't even

Re: [Haskell-cafe] Comment Syntax

2011-06-03 Thread Malcolm Wallace
-- followed by a symbol does not start a comment, thus for example, haddock declarations must begin with -- |, and not --|. What might --| mean, if not a comment? It doesn't seem possible to define it as an operator. GHCi, at least, allows it. Prelude let (--|) = (+) Prelude 1 --| 2

Re: [Haskell-cafe] Matplotlib analog for Haskell?

2011-06-03 Thread Malcolm Wallace
I tried gnuplot: Demo.hs:25:18: Could not find module `Paths_gnuplot': Use -v to see a list of the files searched for. Failed, modules loaded: none. Prelude Graphics.Gnuplot.Simple Where to get `Paths_gnuplot': module? $ cd gnuplot-0.4.2 $ cabal install # this generates

Re: [Haskell-cafe] What's the advantage of writing Haskell this way?

2011-05-30 Thread Malcolm Wallace
instance (Monad m, MonadPlus m) = Monoid (Stream m a) where mempty = Chunks mempty mappend (Chunks xs) (Chunks ys) = Chunks (xs `mappend` ys) mappend _ _ = EOF Iteratee.hs:28:25: No instance for (Monoid (m a)) arising from a use of `mempty' There is a clue

Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-23 Thread Malcolm Wallace
On 23 May 2011, at 17:20, michael rice wrote: What's the best way to end up with a list composed of only the Just values, no Nothings? Go to haskell.org/hoogle Type in [Maybe a] - [a] Click on first result. ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-23 Thread Malcolm Wallace
On 23 May 2011, at 17:20, michael rice wrote: What's the best way to end up with a list composed of only the Just values, no Nothings? Alternatively, [ x | Just x - originals ] It also occurs to me that perhaps you still want the Just constructors. [ Just x | Just x -

Re: [Haskell-cafe] cannot install base-4.3.1.0 package

2011-05-15 Thread Malcolm Wallace
On 15 May 2011, at 15:35, Immanuel Normann wrote: Why is it so complicated to install the base package? You cannot upgrade the base package that comes with ghc. It's a bad design, but there we go. Regards, Malcolm ___ Haskell-Cafe mailing list

  1   2   3   4   5   6   7   8   9   10   >