Re: [Haskell-cafe] JavaScript (SpiderMonkey, V8, etc) embedded in GHC?

2012-11-10 Thread Claus Reinke
I've looked around with no success… this surprises me actually. Has anyone embedded SpiderMonkey, V8, or any other relatively decent JavaScript interpreters in GHC (using the FFI)? I just started something [1]. Cheers, Simon [1] https://github.com/sol/v8 Out of curiosity: wouldn't it make

Re: [Haskell-cafe] Reddy on Referential Transparency

2012-07-27 Thread Claus Reinke
Have we become a bit complacent about RT? We're not complacent, we just know things without having to check references. Just kidding, of course, functional programmers tend to enjoy improving their understanding!-) The Strachey reference is worth reading - great that it is online these days,

Re: [Haskell-cafe] Need inputs for a Haskell awareness presentation

2012-06-01 Thread Claus Reinke
I have the opportunity to make a presentation to folks (developers and managers) in my organization about Haskell - and why it's important - and why it's the only way forward. Haskell is important, but not the only way forward. Also, there have been other great languages, with limited impact -

Re: [Haskell-cafe] Hierarchical tracing for debugging laziness

2012-01-25 Thread Claus Reinke
Look how one can watch the evaluation tree of a computation, to debug laziness-related problems. You might like the old Hood/GHood: http://hackage.haskell.org/package/hood http://hackage.haskell.org/package/GHood Background info/papers: http://www.ittc.ku.edu/csdl/fpg/Tools/Hood

Re: [Haskell-cafe] How to speedup generically parsing sum types?

2011-11-03 Thread Claus Reinke
* syb: toJSON and fromJSON from the Data.Aeson.Generic module. Uses the Data type class. .. As can be seen, in most cases the GHC Generics implementation is much faster than SYB and just as fast as TH. I'm impressed by how well GHC optimizes the code! Not that it matters much if you're going

Re: [Haskell-cafe] What library package fulfills these requirements?

2011-10-28 Thread Claus Reinke
I am planning to give a workshop on FP using Haskell. The audience will be programmers with quite a bit of experience with conventional languages like Java and .net . I want to give them some feeling about FP. And hopefully, they will become interested so they want more... My

Re: [Haskell-cafe] Message

2011-10-22 Thread Claus Reinke
The world needs programmers to accept and take seriously Greg Wilson's extensible programming, and stop laughing it off as lolwut wysiwyg msword for programming, and start implementing it. http://third-bit.com/blog/archives/4302.html Who is the world? For starters, I don't think it is Greg

Re: [Haskell-cafe] which tags program should I use?

2011-09-26 Thread Claus Reinke
suggests using :etags in GHCI or hasktags, or gasbag. Of the three, hasktags comes closest to working but it has (for me) a major inconvenience, namely it finds both function definitions and type signatures, resulting in two TAGS entries such as: Some customization required? Tweaking the

Re: [Haskell-cafe] Deciding equality of functions.

2011-04-10 Thread Claus Reinke
It is a common situation when one has two implementations of the same function, one being straightforward but slow, and the other being fast but complex. It would be nice to be able to check if these two versions are equal to catch bugs in the more complex implementation. This common

Re: [Haskell-cafe] why are trading/banking industries seriouslyadopting FPLs???

2011-03-25 Thread Claus Reinke
I am very curious about the readiness of trading and banking industries to adopt FPLs like Haskell: .. Why are are trading/banking diving into FPLs? Some possible reasons have been given, but to keep things in perspective, you might want to consider that it isn't just FPLs. Smalltalk, for

Re: [Haskell-cafe] Byte Histogram

2011-02-05 Thread Claus Reinke
Lately I've been trying to go the other direction: make a large section of formerly strict code lazy. There used to be a couple of tools trying to make suggestions when a function could be made less strict (Olaf Chitil's StrictCheck and another that escapes memory at the moment). Often, it

Re: [Haskell-cafe] Denotational semantics for the lay man.

2011-01-17 Thread Claus Reinke
I've recently had the opportunity to explain in prose what denotational semantics are to a person unfamiliar with it. I was trying to get across the concept of distilling the essence out of some problem domain. I wasn't able to get the idea across so I'm looking for some simple ways to explain

Re: [Haskell-cafe] Needed: A repeatable process for installing GHC on Windows

2011-01-15 Thread Claus Reinke
Earlier today I was trying to set up a Windows build bot for the 'network' package. That turned out to be quite difficult. Too much playing with PATHs, different gcc versions, etc. Does anyone have a repeatable, step-by-step process to install GHC and get a build environment (where I could build

Re: [Haskell-cafe] dot-ghci files

2010-12-09 Thread Claus Reinke
Perhaps ghc should also ignore all group-writable *.hs, *.lhs, *.c, *.o, *.hi files. dot-ghci files are *run* if you just start ghci (or ghc -e) in that directory (even if you don't intend to compile, load, or run any Haskell code). Claus ___

Re: [Haskell-cafe] OverloadedStrings mixed with type classes leads toboilerplate type signatures

2010-12-05 Thread Claus Reinke
ghci :set -XOverloadedStrings ghci $name ate a banana. % [(name, Johan)] Johan ate a banana. class Context a where lookup :: a - T.Text - T.Text instance Context [(T.Text, T.Text)] where lookup xs k = fromMaybe (error $ KeyError: ++ show k) (P.lookup k xs)

Re: [Haskell-cafe] Conditional compilation for different versionsof GHC?

2010-12-01 Thread Claus Reinke
This is obviously a personal preference issue, but I try to avoid the Cabal macros since they don't let my code run outside the context of Cabal. I often times like to have a test suite that I can just use with runhaskell, and (unless you can tell me otherwise) I can't run it anymore. Also, I

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Claus Reinke
but if improved records are never going to happen Just to inject the usual comment: improved records have been here for quite some time now. In Hugs, there is TREX; in GHC, you can define your own. No need to wait for them. Using one particular random variation of extensible records and

Re: [Haskell-cafe] Re: change in overlapping instance behavior between GHC 6.12 and GHC 7 causes compilation failure

2010-11-09 Thread Claus Reinke
instance (EmbedAsChild m c, m1 ~ m) = EmbedAsChild m (XMLGenT m1 c) That looked to me like a long-winded way of saying: instance (EmbedAsChild m c) = EmbedAsChild m (XMLGenT m c) Unless I'm missing something? These two instances are not equivalent: - the first matches even if m and m1

Re: [Haskell-cafe] http://functionalley.eu

2010-11-06 Thread Claus Reinke
I opted to host them there rather than uploading them to Hackage, because they're part of a wider project. Note that this means they won't be cabal installable or searchable. Was that your intention? I am curious about this: wasn't cabal designed with the option of having several package

Re: [Haskell-cafe] Reference for technique wanted

2010-11-05 Thread Claus Reinke
I haven't the faintest idea what SML is doing with the third version, but clearly it shouldn't. Those numbers are worrying, not just because of the third version - should doubling the tree size have such a large effect? I find your report that GHC doesn't do as well with the third version

Re: [Haskell-cafe] Reference for technique wanted

2010-11-04 Thread Claus Reinke
The bottom line is that - in logic programming languages, building a list by working on a pair of arguments representing a segment of the list is the NORMAL way to build a list; it's as fast as it gets, and the list is inspectable during construction. modulo usage patterns: e.g., mostly

Re: [Haskell-cafe] Non-hackage cabal source

2010-11-04 Thread Claus Reinke
remote-repo: myhackage:http://myhackage/packages However, when I try to unpack my package with cabal: $ cabal unpack MyPackage Downloading MyPackage-0.0.1... cabal: Failed to download http://myhackage/packages/package/MyPackage-0.0.1.tar.gz : ErrorMisc Unsucessful HTTP code: 404 Why is cabal

Re: [Haskell-cafe] Reference for technique wanted

2010-11-03 Thread Claus Reinke
The characteristics of the logical variable are as follows. An incomplete data structure (ie. containing free variables) may be returned as a procedure's output. The free variables can later be filled in by other procedures, giving the effect of implicit assignments to a data structure

Re: [Haskell-cafe] Reference for technique wanted

2010-11-02 Thread Claus Reinke
Interesting discussion. I still think it is the same idea, namely to represent not-yet-known list tails by variables, embedded into two different kinds of languages. \rest-start++rest [start|rest]\rest-- '\' is an infix constructor Savvy Prolog programmers wouldn't *DREAM* of using

[Haskell-cafe] non-hackage cabal repos? unpacking non-repo package tarballs?

2010-11-02 Thread Claus Reinke
I often find myself writing example code that I'd like to distribute via cabal, but without further burdening hackage with not generally useful packages. 1. The simplest approach would be if cabal could expose its internal 'unpackPackage' as a command, so that author: cabal sdist user:

Re: [Haskell-cafe] Reference for technique wanted

2010-11-01 Thread Claus Reinke
To simplify, the difference in persistence between the two representations is enough to consider them very different as it makes a dramatic difference in interface. Interesting discussion. I still think it is the same idea, namely to represent not-yet-known list tails by variables, embedded

Re: [Haskell-cafe] Edit Hackage

2010-11-01 Thread Claus Reinke
Stack Overflow and Reddit are at least improvements over the traditional web forums, starting to acquire some of the features Usenet had twenty years ago. Much like Planet-style meta-blogs and RSS syndication makes it liveable to follow blogs. Very much this. I mourn Usenet's potential as

Re: [Haskell-cafe] who's in charge?

2010-10-29 Thread Claus Reinke
2) If there is a problem, here's what you could do about it, in descending order of attractiveness: y) specify the requirements (a sample application of what needs to be supported would be a start) z) review the existing options wrt to those requirements (which ones are you aware about,

Re: [Haskell-cafe] Need programming advice for Network ProtocolParsing

2010-10-27 Thread Claus Reinke
I'm occasionally working on making a friendly yet performant library that simultaneously builds parsers and generators, but it's non-trivial. If you I'm probably missing something in the friendly yet performant requirements, but I never quite understood the difficulty: A typical translation of

[Haskell-cafe] Haddock API and .haddock interface files questions

2010-10-26 Thread Claus Reinke
Some questions about Haddock usage: 1. Haddock executable and library are a single hackage package, but GHC seems to include only the former (haddock does not even appear as a hidden package anymore). Is that intended? 2. Naively, I'd expect Haddock processing to involve three stages:

Re: [Haskell-cafe] Bug in HTTP (bad internal error handling)

2010-10-16 Thread Claus Reinke
After it catches this error, the function returns (line 376): return (fail (show e)) The fail is running in the Either monad (The Result type = Either). This calls the default Monad implementation of fail, which is just a call to plain old error. This basically causes the entire program to

Re: [Haskell-cafe] A new cabal odissey: cabal-1.8 breaking its ownneck by updating its dependencies

2010-09-17 Thread Claus Reinke
On the topic of cabal odisseys: I think it would help to document (prominently) what Cabal fundamentally doesn't (try to) do, to avoid optimistic expectations (and hence the surprises when Cabal doesn't meet those expectations), and to point out the design choices behind many bug tickets

Re: Réf. : [Haskell-cafe] Re: circular imports

2010-09-07 Thread Claus Reinke
That sort of code (stripped out): In Game.hs: data Game = Game { ... activeRules :: [Rule]} applyTo :: Rule - Game - Game applyTo r gs = ... Often, it helps to parameterize the types/functions (instead of using recursive modules to hardcode the parameters). Would

Re: [Haskell-cafe] what's the best environment for haskell work?

2010-08-06 Thread Claus Reinke
For another programs (that compile fine with ghc --make), I didn't bother making the package. But I had to find out the package dependencies by building, checking where it fails, and trying to add a package to the dependency list. Maybe there's a better way, didn't find it. We do plan to fix

Re: [Haskell-cafe] Haddock anchors

2010-07-15 Thread Claus Reinke
One of the problems is that the anchors that Haddock currently generate aren't always legal in HTML, XHTML, or XML. I'd like to fix the anchor generation so that they are. If I do, then links between old and new generated Haddock pages will land on the right page, but won't always get to the

Re: [Haskell-cafe] Debugging cause of indefinite thread blocking

2010-07-07 Thread Claus Reinke
I am making use of the Data.Array.Repa module to achieve data-parallelism. On running my program I get the error: thread blocked indefinitely on an MVar operation Haven't seen any responses yet, so here are some suggestions: Two questions: 1. What could be some of the potential causes for

Re: [Haskell-cafe] Re: checking types with type families

2010-07-03 Thread Claus Reinke
Prelude :t id :: Eq b = b - b id :: Eq b = b - b :: (Eq b) = b - b Prelude id :: Eq b = b - b interactive:1:0: No instance for (Show (b - b)) arising from a use of `print' at interactive:1:0-19 Possible fix: add an instance declaration for (Show (b - b)) In a stmt of a

Re: [Haskell-cafe] Is my code too complicated?

2010-07-03 Thread Claus Reinke
Most languages today provide a certain glue to bring everything together. Most languages today provide several kinds of glue and, while some of those kinds are not recommended, Haskell unfortunately doesn't provide all useful kinds of glue. Especially the module system is a weak point: in SML,

Re: [Haskell-cafe] Re: checking types with type families

2010-07-02 Thread Claus Reinke
class C a b | a-b where op :: a - b instance C Int Bool where op n = n0 data T a where T1 :: T a T2 :: T Int -- Does this typecheck? f :: C a b = T a - Bool f T1 = True f T2 = op 3 The function f should typecheck because inside the T2 branch we know that

Re: [Haskell-cafe] Re: checking types with type families

2010-07-02 Thread Claus Reinke
f :: forall a b. C a b = T a - Bool f T1 = True f T2 = (op :: a - b) 3 as that results in the counter-intuitive Couldn't match expected type `Bool' against inferred type `b' `b' is a rigid type variable bound by the type signature for `f' at

Re: [Haskell-cafe] Re: Mining Twitter data in Haskell and Clojure

2010-06-28 Thread Claus Reinke
Claus -- cafe5 is pretty much where it's at. You're right, the proggy was used as the bug finder, actually at cafe3, still using ByteString. It would be useful to have a really tiny data source - no more than 100 entries per Map should be sufficient to confirm or reject hunches about

Re: [Haskell-cafe] Re: Mining Twitter data in Haskell and Clojure

2010-06-24 Thread Claus Reinke
I'll work with Simon to investigate the runtime, but would welcome any ideas on further speeding up cafe4. An update on this: with the help of Alex I tracked down the problem (an integer overflow bug in GHC's memory allocator), and his program now runs to completion. So this was about

Re: [Haskell-cafe] checking types with type families

2010-06-23 Thread Claus Reinke
I'm interested in situations where you think fundeps work and type families don't. Reason: no one knows how to make fundeps work cleanly with local type constraints (such as GADTs). If you think you have such as case, do send me a test case. Do you have a wiki page somewhere collecting

Re: [Haskell-cafe] Huffman Codes in Haskell

2010-06-23 Thread Claus Reinke
This seems like an example of list-chauvinism -- what Chris Okasaki calls a communal blind spot of the FP community in Breadth-First Numbering: Lessons from a Small Exercise in Algorithm Design -- http://www.eecs.usma.edu/webs/people/okasaki/icfp00.ps Thanks for sharing; this was an

Re: [Haskell-cafe] TH instance code.

2010-06-22 Thread Claus Reinke
I have below duplicate code, but i don't know how to use TH instance code. -- duplicate code start -- instance Variable PageType where toVariant = toVariant . show fromVariant x = fmap (\v - read v :: PageType) $ fromVariant x If

Re: [Haskell-cafe] Re: How to browse code written by others

2010-06-20 Thread Claus Reinke
If you go this route, I will shamelessly promote hothasktags instead of ghci. It generates proper tags for qualified imports. What do you mean by proper here? I think Luke means that if you use qualified names then hothasktags can give you better location information than current ghci ctags.

Re: [Haskell-cafe] What is Haskell unsuitable for?

2010-06-18 Thread Claus Reinke
If you want to use cool languages, you may have to get a cool job. I know: it's easy to say and harder to accomplish. Most functional languages (e.g. Lisp, Haskell, ...) have a challenging time in industry since they require some savvy with multiple levels of higher abstractions and some

Re: [Haskell-cafe] Re: Mining Twitter data in Haskell and Clojure

2010-06-17 Thread Claus Reinke
I'll work with Simon to investigate the runtime, but would welcome any ideas on further speeding up cafe4. Just a wild guess, but those foldWithKeys make me nervous. The result is strict, the step function tries to be strict, but if you look at the code for Data.IntMap.foldr, it doesn't really

Re: [Haskell-cafe] How to browse code written by others

2010-06-15 Thread Claus Reinke
..ghci is able to generate the tagsfiles for you. This allows you to jump to definitions of identifiers. If you go this route, I will shamelessly promote hothasktags instead of ghci. It generates proper tags for qualified imports. What do you mean by proper here? GHCi has the information

Re: [Haskell-cafe] How to Show an Operation?

2010-06-14 Thread Claus Reinke
As others have pointed out, you can't go from operation to representation, but you can pair operations and expressions with their representations. This idea is also implemented in my little 'repr' package: http://hackage.haskell.org/package/repr And probably more completely/comfortably!-)

Re: [Haskell-cafe] HP/Cygwin and Curl

2010-06-08 Thread Claus Reinke
Thanks Stephen--that was related to my original question, about using HP with Cygwin. The answer seems to be No!--you must use MSYS (for real work). The short version: - Cygwin provides commandline tools, compilers and libraries - MSYS provides commandline tools for the MinGW compilers and

Re: [Haskell-cafe] HP/Cygwin and Curl

2010-06-08 Thread Claus Reinke
of the Haskell tools won't work when launched from Cygwin Bash. Chris -Original Message- From: haskell-cafe-boun...@haskell.org [mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Claus Reinke Sent: 08 June 2010 09:02 To: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] HP/Cygwin and Curl

Re: [Haskell-cafe] How to Show an Operation?

2010-06-07 Thread Claus Reinke
If I have a problem where I have to select from a set of operations, how would I print the result? Example: If I can chose from (x+y), (x*y), (x^2+y)... and I feed them all into my problem solver and it finds that (x*y) is right, how can I print that string? As others have pointed out,

Re: [Haskell-cafe] Chuch encoding of data structures in Haskell

2010-05-27 Thread Claus Reinke
The approach is so simple and trivial that it must have occurred to people a hundred times over. Yet I do not find any other examples of this. Whenever I google for church encoding the examples don't go beyond church numerals. Am I googling for the wrong keywords? You might find Typing

Re: [Haskell-cafe] Re: How do you rewrite your code?

2010-03-04 Thread Claus Reinke
All my code, whether neat or not so neat is still way too concrete, too direct. I think the correct answer is one should try to find abstractions and not code straight down to the point. Which to me is still a really tough one, I have to admit. Taking this cue, since you've raised it before,

Re: [Haskell-cafe] Questions about haskell CPP macros

2009-07-13 Thread Claus Reinke
I am trying to improve the error reporting in my sendfile library, and I know I can find out the current file name and line number with something like this: {-# LANGUAGE CPP #-} main = putStrLn (__FILE__ ++ : ++ show __LINE__) This outputs: test.hs:2 Unfortunately, if your file is in a

Re: [Haskell-cafe] Haskell on JVM

2009-06-26 Thread Claus Reinke
For example, Clojure lacks proper tail recrusion optimization due to some missing functionality in the JVM. But does anybody know the details? |Basically, the JVM lacks a native ability to do tail calls. It does |not have an instruction to remove/replace a stack frame without |executing

Re: [Haskell-cafe] Haskell on JVM

2009-06-26 Thread Claus Reinke
JVM 7 has tail calls, Source, please? JSR-292 seems the most likely candidate so far, and its draft doesn't seem to mention tail calls yet. As of March this year, the people working on tail calls for mlvm [1], which seems to be the experimentation ground for this, did not seem to expect any

Re: [Haskell-cafe] Error in array index.

2009-06-25 Thread Claus Reinke
It's too bad that indexes are `Int` instead of `Word` under the hood. Why is `Int` used in so many places where it is semantically wrong? Not just here but also in list indexing... Indices/offsets can only be positive and I can't see any good reason to waste half the address space -- yet we

[Haskell-cafe] HaRe (the Haskell Refactorer) in action - short screencast

2009-06-22 Thread Claus Reinke
I've heard that many Haskellers know HaRe only as a rumour. It has been many years since the original project finished, and HaRe hasn't been maintained for quite some time, so just pointing to the sources isn't quite the right answer. The sources are still available, and build with GHC 6.8.3

Re: [Haskell-cafe] Code walking off the right edge of the screen

2009-06-21 Thread Claus Reinke
I (too) often find myself writing code such as this: if something then putStrLn howdy there! else if somethingElse then putStrLn howdy ho! else ... 1. recognize something odd. done. 2. look for improvements. good. 3. define suitable abstractions for your special case 4.

Re: [Haskell-cafe] IORef memory leak

2009-06-19 Thread Claus Reinke
It is not possible to write a modifyIORef that *doesn't* leak memory! Why? Or can one read about it somewhere? Possibly, Don meant that 'modifyIORef' is defined in a way that does not allow to enforce evaluation of the result of the modification function (a typical problem with fmap-style

Re: [Haskell-cafe] Runtime strictness analysis for polymorphic HOFs?

2009-06-15 Thread Claus Reinke
I was recently trying to figure out if there was a way, at runtime, to do better strictness analysis for polymorphic HOFs, for which the strictness of some arguments might depend on the strictness of the strictness of function types that are passed as arguments [1]. As an example, consider foldl.

Re: [Haskell-cafe] Re: Documentation on hackage

2009-06-15 Thread Claus Reinke
who needs this kind of documentation? http://hackage.haskell.org/packages/archive/tfp/0.2/doc/html/Types-Data-Num-Decimal-Literals.html The code below is shown under 'Source' links in that documentation. I don't understand it, but it seems everything is generated automatically. What should the

Re: [Haskell-cafe] How to know the build dependencies?

2009-06-14 Thread Claus Reinke
I am learning to use cabal for my code. Just when I start, I met a question, is there an easy way to find out what packages my code depends? If you've managed to get your code to compile, ghc --show-iface Main.hi is perhaps the easiest way (ghc --make and ghci will also report package

Re: [Haskell-cafe] curious about sum

2009-06-14 Thread Claus Reinke
A much better idea than making sum strict, would simply be to add a sum'. Even better to abstract over strictness, to keep a lid on code duplication? {-# LANGUAGE TypeOperators #-} sum = foldlS ($) (+) 0 sum' = foldlS ($!) (+) 0 -- identity on constructors of t (from a),

Re: [Haskell-cafe] Debugging misbehaving multi-threaded programs

2009-06-11 Thread Claus Reinke
I've written a multi-threaded Haskell program that I'm trying to debug. Basically what's happening is the program runs for a while, and then at some point one of the threads goes crazy and spins the CPU while allocating memory; this proceeds until the system runs out of available memory. I can't

Re: [Haskell-cafe] Monad transformer responsibilities

2009-06-05 Thread Claus Reinke
From what I understand, the current best practices are to build your package dependencies like so: ParsecMyMonadT MyMonadT_Parsec -- orphan instances go here ProjectPackage This does mean splitting up your project into three packages, but decouples the orphan instance into its own package

Re: [Haskell-cafe] Monad transformer responsibilities

2009-06-05 Thread Claus Reinke
| bar :: (C T) = T | *Main :t bar | | interactive:1:0: | No instance for (C T) | arising from a use of `bar' at interactive:1:0-2 | Possible fix: add an instance declaration for (C T) | In the expression: bar I'm not sure where that comes from, but it does seem to be an

Re: [Haskell-cafe] Bool as type class to serve EDSLs.

2009-06-01 Thread Claus Reinke
Do you argue that overloading logical operations like this in Haskell sacrifices type safety? Could programs go wrong [1] that use such abstractions? If I understand your point correctly, you are suggesting that such programs are still type safe. I agree with the claim that such features are

Re: [Haskell-cafe] Re: Error message reform (was: Strange type errorwith associated type synonyms)

2009-06-01 Thread Claus Reinke
I once thought, that error messages must be configurable by libraries, too. This would be perfect for EDSLs that shall be used by non-Haskellers. Yes, that is a problem. But I have no idea how to design that. There was some work in that direction in the context of the Helium project. See

Re: [Haskell-cafe] Question on kind inference

2009-05-31 Thread Claus Reinke
--- class A a where foo :: a b class B a class (A a, B a) = C a --- GHC compiles it without errors, but Hugs rejects it: Illegal type in class constraint. The error message is horribly uninformative.

Re: [Haskell-cafe] Which type variables are allowed in a context?

2009-05-31 Thread Claus Reinke
-- class A a where foo :: A (b d) = a (c b) -- GHC compiles it successfully, but Hugs rejects it: Ambiguous type signature in class declaration *** ambiguous type : (A a, A (b c)) = a (d b) *** assigned to: foo 'd'

Re: [Haskell-cafe] (no subject)

2009-05-31 Thread Claus Reinke
-- type F a = Int class A a where foo :: A b = a (F b) -- GHC - OK Hugs - Illegal type F b in constructor application This time, I'd say Hugs is wrong (though eliminating that initial complaint leads back to an

Re: [Haskell-cafe] GHCi vs. Hugs (record syntax)

2009-05-31 Thread Claus Reinke
head[[]{}] GHCi: [] Hugs: ERROR - Empty field list in update What is the correct behavior? Seems as if GHC interprets []{} as labelled construction instead of labelled update - 3 Expressions (the grammar productions): | qcon { fbind1 , ... , fbindn } (labeled construction, n=0) |

Re: [Haskell-cafe] (no subject)

2009-05-31 Thread Claus Reinke
-- type F a = Int class A a where foo :: A b = a (F b) -- GHC - OK Hugs - Illegal type F b in constructor application This time, I'd say Hugs is wrong (though eliminating that initial complaint leads back to an

Re: [Haskell-cafe] Re: Error message reform

2009-05-30 Thread Claus Reinke
I find this slightly more complicated case quite confusing with the current wording: Prelude :t (\x - x) :: (a - b) - (a - a) interactive:1:7: Couldn't match expected type `a' against inferred type `b' `a' is a rigid type variable bound by an expression type

Re: [Haskell-cafe] Re: Error message reform (was: Strange type error with associated type synonyms)

2009-05-28 Thread Claus Reinke
One user's view of error message history, perhaps helpful to reformers:-) Once upon a time, Hugs tended to have better error messages than GHC. They still weren't perfect, mostly when begginners where confronted with messages referring to advanced concepts - eg, Simon Thompson had a list of

Re: [Haskell-cafe] Bool as type class to serve EDSLs.

2009-05-28 Thread Claus Reinke
Of course once you've got ifthenelse you find yourself wanting explicit desugaring of pattern matching (could view patterns help here?), Could you be more specific about what you want there, perhaps with a small example? I recognize the other problems from my own forays into EDSLs, but I'm not

Re: [Haskell-cafe] How to implement this? A case for scoped record labels?

2009-05-26 Thread Claus Reinke
I wonder if I am completely off here, but I am surprised that there is no progress on the scoped labels front. The Haskell wiki mentioned that the status quo is due to a missing optimum in the design space, but the same can be said about generic programming in Haskell and yet, GHC ships with

Re: [Haskell-cafe] fast Eucl. dist. - Haskell vs C

2009-05-19 Thread Claus Reinke
I understand from your later post that is was in fact specialized, but how do I make sure it _is_ specialized? -ddump-tc seems to give the generalized type, so it seems you'd need to look at the -ddump-simpl output if you want to know whether a local function is specialized.

Re: [Haskell-cafe] tips on using monads

2009-05-18 Thread Claus Reinke
I've got one of those algorithms which threatens to march off the right edge (in the words of Goerzen et al). I need something like a State or Maybe monad, but this is inside the IO monad. So I presume I need StateT or MaybeT. However, I'm still (slowly) learning about monads from first

Re: [Haskell-cafe] fast Eucl. dist. - Haskell vs C

2009-05-18 Thread Claus Reinke
My current best try uses the uvector package, has two 'vectors' of type (UArr Double) as input, and relies on the sumU and zipWithU functions which use streaming to compute the result: dist_fast :: UArr Double - UArr Double - Double dist_fast p1 p2 = sumDs `seq` sqrt sumDs where

Re: [Haskell-cafe] fast Eucl. dist. - Haskell vs C

2009-05-18 Thread Claus Reinke
dist_fast :: UArr Double - UArr Double - Double dist_fast p1 p2 = sumDs `seq` sqrt sumDs where sumDs = sumU ds ds= zipWithU euclidean p1 p2 euclidean x y = d*d where

Re: [Haskell-cafe] tips on using monads

2009-05-18 Thread Claus Reinke
I've got one of those algorithms which threatens to march off the right edge (in the words of Goerzen et al). I need something like a State or Maybe monad, but this is inside the IO monad. So I presume I need StateT or MaybeT. However, I'm still (sdlowly) learning about monads from first

Re: [Haskell-cafe] fast Eucl. dist. - Haskell vs C

2009-05-18 Thread Claus Reinke
Once I actually add a 'dist_fast_inline_caller', that indirection disappears in the inlined code, just as it does for dist_fast itself. dist_fast_inlined_caller :: UArr Double - UArr Double - Bool dist_fast_inlined_caller p1 p2 = dist_fast_inlined p1 p2 2 However, in the simpl output

Re: [Haskell-cafe] fast Eucl. dist. - Haskell vs C

2009-05-18 Thread Claus Reinke
As I said, I don't get the fusion if I just add the function above to the original Dist.hs, export it and compile the module with '-c -O2 -ddump-simpl': I can't reproduce this. Interesting. I'm using ghc 6.11.20090320 (windows), uvector-0.1.0.3. I attach the modified Dist.hs and its simpl

Re: [Haskell-cafe] conflicting variable definitions in pattern

2009-05-15 Thread Claus Reinke
I miss lots of stuff from when I was a kid. I used to write elem x (_ ++ x : _) = True elem _ _ = False and think that was cool. How dumb was I? Yeah, the Kiel Reduction Language had similarly expressive and fun pattern matching, with subsequence matching and backtracking if

Re: [Haskell-cafe] Functional Reactive Web Application Framework?

2009-05-13 Thread Claus Reinke
I assume you want to write FRP in a Haskell-embedded DSL and generate FRP'd JavaScript. If you wish to use Flapjax as a supporting library I'd be glad to help. I'm curious: how difficult is it nowadays for in-page JavaScript to control the evolution of its surrouding page, FRP-style? I used to

Re: [Haskell-cafe] Functional Reactive Web Application Framework?

2009-05-13 Thread Claus Reinke
oops, sorry, keyboard accident I assume you want to write FRP in a Haskell-embedded DSL and generate FRP'd JavaScript. If you wish to use Flapjax as a supporting library I'd be glad to help. I'm curious: how difficult is it nowadays for in-page JavaScript to control the evolution of its

Re: [Haskell-cafe] Data.Map and strictness (was: Is Haskell aGoodChoice for WebApplications?(ANN: Vocabulink))

2009-05-07 Thread Claus Reinke
seq something like size map that will force a traversal of the entire tree, and ensure that the result is actually demanded, .. (Not tested) and not recommended, either, I'm afraid!-) | Actually, I'm unsure how to fix this. For an expression like this: | |Data.Map.delete key map | | how

Re: [Haskell-cafe] Re: Visualizing Typed Functions

2009-05-07 Thread Claus Reinke
With these functions visualized, one could make a kind of drag and drop interface for Haskell programming, although that isn't really my intention. I admit this is a little convoluted even for the purpose of visualization, but at least it's a starting place. Does anyone know of another

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Claus Reinke
mplus' :: MonadPlus m = Maybe a - m a - m a mplus' m l = maybeToMonad m `mplus` l maybeToMonad :: Monad m = Maybe a - m a maybeToMonad = maybe (fail Nothing) return In general, however, this operation can't be done. For example, how would you write: mplus' :: IO a - [a] - [a] Perhaps

Re: [Haskell-cafe] Array Binary IO molecular simulation

2009-05-01 Thread Claus Reinke
So I wonder of existing projects of such type, both Molecular dynamics and Monte Carlo methods. The fastest Haskell Monte Carlo code I've seen in action is Simon's port of a Monte Carlo Go engine: http://www.haskell.org/pipermail/haskell-cafe/2009-March/057982.html

Re: [Haskell-cafe] How to install HOpenGL to Windows?

2009-04-30 Thread Claus Reinke
The thing is, it doesn't really matter if autoconf macros work fine for every Unix ever invented. The Windows users simply cannot use packages with configure scripts. They complain about it a lot. We can call them foolish for not installing cygwin/mingw, but they will not do it and instead will

Re: [Haskell-cafe] Google SoC: Space profiling reloaded

2009-04-30 Thread Claus Reinke
http://socghop.appspot.com/student_project/show/google/gsoc2009/haskell/t124022468245 There's less than a month left before I'm supposed to jump into coding, and I'd love to hear about any little idea you think would make this project even better! I created a project page with a rough draft of

Re: [Haskell-cafe] How to install HOpenGL to Windows?

2009-04-30 Thread Claus Reinke
If someone wants to use a unix shell on an unknown platform, they should at least check that one exists there or -even better- provide one, not just assume that there'll always be one (and then be surprised about getting complaints from those windows users). Same for autoconf, make co. You

Re: [Haskell-cafe] Non-atomic atoms for type-level programming

2009-04-29 Thread Claus Reinke
z :: client - Label client z client = undefined ok :: (B.Label client ~ A.Label client) = client - [A.Label client]. ok client = [ A.z client, B.z client] This technique relies on the explicit management of the identities of modules both at compile-time (type annotation

Re: [Haskell-cafe] Non-atomic atoms for type-level programming

2009-04-28 Thread Claus Reinke
Standard ML's answer to that kind of issue is type sharing. Does type sharing help with making modules retroactively compatible? It would be as if one could write modules parameterised by types, instead of declaring them locally, and being able to share a type parameter over several imports:

Re: [Haskell-cafe] Can subclass override its super-class' defaultimplementation of a function?

2009-04-27 Thread Claus Reinke
Basically, I have a bunch of instances that have a common functionality but I'd like to be able to group those instances and give each group a different default implementation of that functionality. It's so easy to do this in Java, for example, but I have no idea how to do it in Haskell. The

  1   2   3   4   5   6   >