[Haskell-cafe] Typeclass vs. Prolog programming

2006-09-27 Thread oleg
This message is intended as a long answer to Michael Shulman's question (Re: variadic functions and typeCast) and Jason Dagit's question (Re: Duplicate Instance problem). Incidentally, the short answer to Jason Dagit's question is `constraints are disregarded during instance selection'. The answer

Re: [Haskell-cafe] flip dot

2006-09-27 Thread Brian Hulley
On Thursday, September 28, 2006 1:33 AM, Greg Fitzgerald wrote: Since there's talk of removal of the composition operator in Haskell-prime, how about this: Instead of: foo = f . g you write: foo = .g.f A leading dot would mean, "apply all unnamed parameters to the function on the right". A

Re: [Haskell-cafe] A better syntax for qualified operators?

2006-09-27 Thread Brian Hulley
Bas van Dijk wrote: On Wednesday 27 September 2006 22:20, Brian Hulley wrote: (The other change needed for LL(1) is to give contexts a marker before they appear eg: foo :: {MonadIO m} a -> m a ) Or move contexts to the end of a type and separate it with a | like Clean does: (See 6.2 of http:/

Re: [Haskell-cafe] flip dot

2006-09-27 Thread Greg Fitzgerald
> You mean "apply the function on the right to the result of the left"?Yes.(.) :: a -> (a -> b) -> bx.f == f xPrefix usage:given: (f :: Integer -> Char) and (g :: Double -> Double -> Integer) (foo = .f) == \x -> f x(bar = .g) == \x y = g x yfoo :: Double -> Double -> Charfoo = .g.f  > How about mak

Re: [Haskell-cafe] A better syntax for qualified operators?

2006-09-27 Thread Brian Hulley
Brandon Moore wrote: Brian Hulley wrote: I would *like* to be able to use the syntax: ith = Data.Array.IArray.(!) Why does the nice argument not apply equally well to infixifying things? Shouldn't I be able to write myArr Data.Arr.`get` ix Good point. This would also remove the need

[Haskell-cafe] Re: variadic functions and typeCast

2006-09-27 Thread Michael Shulman
On 9/27/06, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote: First of all, there is a version of TypeCast that works within the same module, please see any code described in http://pobox.com/~oleg/ftp/Haskell/typecast.html Yes, I was aware of that; I gave the shorter version just because it

Re: [Haskell-cafe] Creating DLLs with GHC

2006-09-27 Thread SevenThunders
SevenThunders wrote: > > > > SevenThunders wrote: >> >> I am having some difficulty with creating a dynamic link library using >> GHC on windows XP. >> >> > > > I need to report some additional strange DLL behavior with ghc.exe > unfortunately. > > Although I solved my linking problems

[Haskell-cafe] Re: Curious Functor Class

2006-09-27 Thread Ashley Yakeley
I wrote: Perhaps the key is that there exist types P and Q s.t. there's an isomorphism F a <=> (P -> a,Q) This seems to be intuitively Napierian: ln (P -> a,Q) = (P,ln a) | ln Q I can believe that Hoistables are in fact Idioms, though I know there are Idioms that are not Hoistables (May

Re: [Haskell-cafe] Creating DLLs with GHC

2006-09-27 Thread SevenThunders
SevenThunders wrote: > > I am having some difficulty with creating a dynamic link library using > GHC on windows XP. > > I need to report some additional strange DLL behavior with ghc.exe unfortunately. Although I solved my linking problems and was able to create a .dll and a MS VC .lib f

Re: [Haskell-cafe] flip dot

2006-09-27 Thread Brandon Moore
Brandon Moore wrote: Greg Fitzgerald wrote: Since there's talk of removal of the composition operator in Haskell-prime , how about this: Instead of: foo = f . g you write: foo = .g.f A leading dot would mean, "apply all u

Re: [Haskell-cafe] flip dot

2006-09-27 Thread Brandon Moore
Greg Fitzgerald wrote: Since there's talk of removal of the composition operator in Haskell-prime , how about this: Instead of: foo = f . g you write: foo = .g.f A leading dot would mean, "apply all unnamed parameters to t

[Haskell-cafe] Re: variadic functions and typeCast

2006-09-27 Thread oleg
Michael Shulman wrote: > class TypeCast x y | x -> y, y -> x where > typeCast :: x -> y > > instance TypeCast x x where > typeCast = id > > Anyway, my main question about typeCast is this: why is it needed here > at all? First of all, there is a version of TypeCast that works within the s

[Haskell-cafe] flip dot

2006-09-27 Thread Greg Fitzgerald
Since there's talk of removal of the composition operator in Haskell-prime, how about this: Instead of:foo = f . gyou write:foo = .g.fA leading dot would mean, "apply all unnamed parameters to the function on the right".  A trailing dot would mean, "apply the result of the left to the function on t

Re: [Haskell-cafe] Re: [Haskell] Re: compiler-independent core libraries infrastructure

2006-09-27 Thread John Meacham
On Fri, Sep 15, 2006 at 05:12:34PM +0100, Neil Mitchell wrote: > So, just to confirm in my mind what you are proposing: > > Compiler/Version specific Core: > > Yhc.Core, Hugs.Core, GHC.Core > > With a different version for each compiler version. Tied intimately to > the compiler. A large i

[Haskell-cafe] Re: Curious Functor Class

2006-09-27 Thread Ashley Yakeley
Jeremy Gibbons wrote: I haven't assimilated the forall here, but datatypes with only one shape of data have been called "Naperian" by Peter Hancock (because they support a notion of logarithm), and they're instances of McBride and Paterson's "idioms" or "applicative functors". http://sneezy

Re: [Haskell-cafe] A better syntax for qualified operators?

2006-09-27 Thread Bas van Dijk
On Wednesday 27 September 2006 22:20, Brian Hulley wrote: > (The other change needed for LL(1) is to give contexts a marker before they > appear eg: > >         foo :: {MonadIO m} a -> m a > ) Or move contexts to the end of a type and separate it with a | like Clean does: (See 6.2 of http://clean

Re: [Haskell-cafe] Creating DLLs with GHC

2006-09-27 Thread SevenThunders
SevenThunders wrote: > > I am having some difficulty with creating a dynamic link library using > GHC on windows XP. > > I am attempting to follow the example in > http://www.haskell.org/ghc/docs/6.4/html/users_guide/win32-dlls.html > > though I have a binary build of ghc 6.5 > > My problem

Re: [Haskell-cafe] Expressing seq

2006-09-27 Thread Bertram Felgenhauer
Chad Scherrer wrote: > Prelude> let sq x y = if x == x then y else y > Prelude> 1 `sq` 2 > 2 > Prelude> (length [1..]) `sq` 2 > Interrupted. > There must be a subtlety I'm missing, right? Two, at least: First, your sq has a different type, as it requires an Eq instance: Prelude> :t sq sq :: (Eq

Re: [Haskell-cafe] Creating DLLs with GHC

2006-09-27 Thread SevenThunders
Jason Dagit wrote: > > On 9/27/06, SevenThunders <[EMAIL PROTECTED]> wrote: > >> Does cabal really work on windows? > > I've never had a problem with cabal on windows. I use it instead of > makefiles and I'm reasonably happy with it. > >> Although it's installed I notice that >> when I try

Re: [Haskell-cafe] Expressing seq

2006-09-27 Thread Chris Kuklewicz
Chad Scherrer wrote: > I was reading on p. 29 of "A History of Haskell" (a great read, by the > way) about the controversy of adding seq to the language. But other > than for efficiency reasons, is there really any new primitive that > needs to be added to support this? > > As long as the compiler

Re: [Haskell-cafe] Expressing seq

2006-09-27 Thread Chad Scherrer
> > There must be a subtlety I'm missing, right? What if the types are not instances of Eq? Jason Thanks, I figured it was something simple. Now I just to convince myself there's no way around that. Is there a proof around somewhere? -- Chad Scherrer "Time flies like an arrow; fruit flies l

Re: [Haskell-cafe] A better syntax for qualified operators?

2006-09-27 Thread Brandon Moore
Brian Hulley wrote: Hi - Consider the scenario when you want to find a function that returns the i'th element of an array but all you know is that there is a module called Data.Array.IArray that will probably have such a function in it. So you start typing in your program: let ith

Re: [Haskell-cafe] Expressing seq

2006-09-27 Thread Jason Dagit
On 9/27/06, Chad Scherrer <[EMAIL PROTECTED]> wrote: I was reading on p. 29 of "A History of Haskell" (a great read, by the way) about the controversy of adding seq to the language. But other than for efficiency reasons, is there really any new primitive that needs to be added to support this? A

[Haskell-cafe] Duplicate Instance problem

2006-09-27 Thread Jason Dagit
Hello, I tried to create a type class for making instances of Show display a custom way. After using my class for a while I found that sometimes RealFloats would display as 'NaN' and this is unacceptable. So at this point I had something like: {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable

[Haskell-cafe] Expressing seq

2006-09-27 Thread Chad Scherrer
I was reading on p. 29 of "A History of Haskell" (a great read, by the way) about the controversy of adding seq to the language. But other than for efficiency reasons, is there really any new primitive that needs to be added to support this? As long as the compiler doesn't optimize it away, why n

[Haskell-cafe] Creating DLLs with GHC

2006-09-27 Thread Jason Dagit
On 9/27/06, SevenThunders <[EMAIL PROTECTED]> wrote: Does cabal really work on windows? I've never had a problem with cabal on windows. I use it instead of makefiles and I'm reasonably happy with it. Although it's installed I notice that when I try to build my library using it, it dies on t

Re: [Haskell-cafe] Creating DLLs with GHC

2006-09-27 Thread SevenThunders
Jason Dagit wrote: > > On 9/26/06, Matthew Bromberg <[EMAIL PROTECTED]> wrote: >> I am having some difficulty with creating a dynamic link library using >> GHC on windows XP. >> >> I am attempting to follow the example in >> http://www.haskell.org/ghc/docs/6.4/html/users_guide/win32-dlls.html >

[Haskell-cafe] A better syntax for qualified operators?

2006-09-27 Thread Brian Hulley
Hi - Consider the scenario when you want to find a function that returns the i'th element of an array but all you know is that there is a module called Data.Array.IArray that will probably have such a function in it. So you start typing in your program: let ith = Data.Array.IArray.

Re: [Haskell-cafe] Re: Getting the latest

2006-09-27 Thread Lyle Kopnicky
Max Vasin wrote: Lyle> I have no idea how it decides where to go. Right now ghc Lyle> 6.4.1 is in /usr/local/bin/ghc. After I 'make install', will it Lyle> be ghc 6.5? I don't want to screw up the installed package so it Lyle> can't be updated later. It should be :-) It should be screwed up?

Re: [Haskell-cafe] Optimizing a title matcher

2006-09-27 Thread Brandon Moore
Ketil Malde wrote: Lyle Kopnicky <[EMAIL PROTECTED]> writes: If you have some other metric other than prefix in mind for partial matches, then things probably get a lot more complicated. You're probably looking at calculating minimum distances in some feature-space, which calls for pretty s

Re: [Haskell-cafe] Creating DLLs with GHC

2006-09-27 Thread Jason Dagit
On 9/26/06, Matthew Bromberg <[EMAIL PROTECTED]> wrote: I am having some difficulty with creating a dynamic link library using GHC on windows XP. I am attempting to follow the example in http://www.haskell.org/ghc/docs/6.4/html/users_guide/win32-dlls.html though I have a binary build of ghc 6.5

[Haskell-cafe] Re: Getting the latest

2006-09-27 Thread Max Vasin
> "Lyle" == Lyle Kopnicky <[EMAIL PROTECTED]> writes: Lyle> My question is, when I do 'make install', will it just overwrite Lyle> the version (6.4.1) I already have? Or will they go in separate Lyle> places? This depends on the prefix you configured sources with (/usr/local by default). Lyl

Re: [Haskell-cafe] Optimizing a title matcher

2006-09-27 Thread Lyle Kopnicky
Ketil Malde wrote: Do you really need that to search for movie titles? At any rate, an exact-match finite-map implementation is a good start - to get good performance, you probably will need to use some kind of index to reduce the amount of data to search exhaustively (all-against-all). For tex

Re: [Haskell-cafe] Computing lazy and strict list operations at the same time

2006-09-27 Thread Brandon Moore
Andrew Pimlott wrote: This is a follow-up to a thread from June-July[1]. The question was how to write the function initlast :: [a] -> ([a], a) initlast xs = (init xs, last xs) so that it can be consumed in fixed space: main = print $ case initlast [0..10] of

Re: [Haskell-cafe] Creating DLLs with GHC

2006-09-27 Thread SevenThunders
Well I tried this statement ghc --mk-dll -fglasgow-exts -fffi -I. --make ExternLib.hs It only compiled the object file, creating ExternLib.o, but it did not create the stub file or attempt to link in the dependent packages. I then went back to this, ghc --mk-dll -fglasgow-exts -fffi -o netsim.

Re: [Haskell-cafe] Re: Is Haskell a 5GL?

2006-09-27 Thread Ch. A. Herrmann
Hi, an experienced person at our lab told me that the classification into generations has become unfashioned in the last decade; thus I think I will stay away from using it but argue with concrete abstraction features. Concerning the point someone made about the features of Haskell: * pattern ma

Re: [Haskell-cafe] Computing lazy and strict list operations at thesame time

2006-09-27 Thread Claus Reinke
This is a follow-up to a thread from June-July[1]. The question was how to write the function initlast :: [a] -> ([a], a) initlast xs = (init xs, last xs) so that it can be consumed in fixed space: main = print $ case initlast [0..10] of (init, last) -> (le

RE: [Haskell-cafe] source code for haskell web server?

2006-09-27 Thread Pasqualino 'Titto' Assini
There is also the HAppS application server and the HaskellNet library. Would not be possible to merge the protocol-handling parts of all these libraries into a generic Internet Haskell server that could then be expanded to support CGIs, transactions, etc.? Regards, titto > -Original

Re: [Haskell-cafe] source code for haskell web server?

2006-09-27 Thread Bjorn Bringert
On 4 sep 2006, at 20.24, Tim Newsham wrote: Since there are a lot of modifications of HWS around now, it seems to be worthwhile to combine the efforts. E.g. I adapted the HWS adaption provided by WASH http://www.informatik.uni-freiburg.de/~thiemann/WASH/#wsp for my needs. For instance in R

Re[2]: [Haskell-cafe] Re: Is Haskell a 5GL?

2006-09-27 Thread Bulat Ziganshin
Hello Bill, Tuesday, September 26, 2006, 1:03:02 AM, you wrote: > I spent some time working on a large Prolog application where > performance was critical, ... > I think you're right that Haskell should > be in the same bag as Prolog. and Haskell is the same as C++ when performance is critical,

Re: [Haskell-cafe] Re: Is Haskell a 5GL?

2006-09-27 Thread Bulat Ziganshin
Hello Max, Monday, September 25, 2006, 10:41:20 PM, you wrote: Ch>> That's a religious statement. I was looking for some strong Ch>> arguments for the nonbelievers that Haskell is a 5GL. > But what about nonbelievers in language classification by generation? i was not on the market when 1..3 GL

Re: [Haskell-cafe] Optimizing a title matcher

2006-09-27 Thread Johan Tibell
On 9/27/06, Johan Tibell <[EMAIL PROTECTED]> wrote: On 9/27/06, Lyle Kopnicky <[EMAIL PROTECTED]> wrote: > Hi folks, > > It turns out Haskell is vindicated. It's my algorithm that was slow. As > Robert Dockins pointed out, the double nested loop is just going to take > a long time. > > As evidenc

Re: [Haskell-cafe] Optimizing a title matcher

2006-09-27 Thread Ketil Malde
Lyle Kopnicky <[EMAIL PROTECTED]> writes: >> If you have some other metric other than prefix in mind for partial >> matches, then things probably get a lot more complicated. You're >> probably looking at calculating minimum distances in some >> feature-space, which calls for pretty sophisticated

Re: [Haskell-cafe] Optimizing a title matcher

2006-09-27 Thread Johan Tibell
On 9/27/06, Lyle Kopnicky <[EMAIL PROTECTED]> wrote: Hi folks, It turns out Haskell is vindicated. It's my algorithm that was slow. As Robert Dockins pointed out, the double nested loop is just going to take a long time. As evidence, it turns out my C++ version is just as slow as the Haskell ve

Re: [Haskell-cafe] Unable to profile program using Data.ByteString.Lazy

2006-09-27 Thread Ketil Malde
Ketil Malde <[EMAIL PROTECTED]> writes: > I filed a request to backport [ghc 6.4.2 to Ubuntu Dapper], but for > some reason, I am unable to find it again. Hah! Found it (with some IRC assistance): https://launchpad.net/distros/ubuntu/+source/ghc6/+bug/56516 -k -- If I haven't seen further,

[Haskell-cafe] Re: Creating DLLs with GHC

2006-09-27 Thread Cyril Schmidt
Matthew, As regards the symbols that end with _closure, I believe you can resolve them by adding -package parsec to the ghc command line (as far as I can see, all the symbols you list come from the parsec package). I don't know, though, what to do with the undefined symbols from matrixstack. You

Re: [Haskell-cafe] Creating DLLs with GHC

2006-09-27 Thread Esa Ilari Vuokko
Hi On 9/27/06, Matthew Bromberg <[EMAIL PROTECTED]> wrote: though I have a binary build of ghc 6.5 If you have new ghc 6.5, you can use --mk-dll with --make, in case that helps. ghc --mk-dll -o netsim.dll ExternLib.o ExternLib_stub.o dllNet.o src1.o src1_stub.o src2.o -optl-lmatrixstack -op

Re: [Haskell-cafe] Unable to profile program using Data.ByteString.Lazy

2006-09-27 Thread Ketil Malde
"Jason Dagit" <[EMAIL PROTECTED]> writes: > Ubuntu seems to be a bit behind then. The current official release of > the 6.4 branch is at 6.4.2. Debian seems to provide this version, > maybe you can use the debian package? But, if I were you I wouldn't > worry so much about upgrading ghc but ins