Re: [Haskell-cafe] Basic question concerning the category Hask (was: concerning data constructors)

2008-01-03 Thread Yitzchak Gale
Hi Jonathan,

I wrote:
 So in what way are Set morphisms restricted from being
 Hask morphisms?

Jonathan Cast wrote:
 The normal view taken by Haskellers is that the denotations of
 Haskell types are CPPOs.

CPPO?

  So:

 (1) Must be monotone
 (2) Must be continuous

Could you please define what you mean by those terms
in this context?

 (Needn't be strict, even though that messes up the resulting category
 substantially).

I'm not convinced that the category is all that messed up.

Thanks,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Nicholls, Mark
I was thinking more along type classesand then I was going to throw
some spanners in the works

 



From: Ryan Ingram [mailto:[EMAIL PROTECTED] 
Sent: 02 January 2008 17:41
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Is there anyone out there who can translate
C# generics into Haskell?

 

Of course it depends what's inside the braces, and what you want to do
with it, but I'd be inclined to do something like this:

 

1) data IX a = IX { constructor :: Int - a, ... }

2) data IX a b = IX { constructor :: Int - b, func :: a - b, ... }

3) data IX a b = IX { iy :: IY a, ... }

4) data IX a b = IX { iz :: IZ b, iy :: IY a, ... }

 

Can you specify more clearly what the goal of the conversion is?  If you
want OO style behavior the thing that is most important is existential
quantification.

 

  -- ryan

 

On 1/2/08, Nicholls, Mark [EMAIL PROTECTED] wrote: 

I'm trying to translate some standard C# constucts into Haskell... some
of this seems easy

Specifically

1)

Interface IX
{
}

2)

Interface IXA
{
}

3)

Interface IXA
   Where A : IY
{
}

4)

Interface IXA : IZ
   Where A : IY
{
}


I can take a punt at the first 2but then it all falls apart
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] The Worker/Wrapper Transformation

2008-01-03 Thread Achim Schneider
...is a paper about automatic specialisation of functions by unboxing
arguments, one could say. I'm only on page 6, but already survived the
first formalisms, which is bound to mean that the rest of the paper is
likewise accessible, as hinted on at ltu.

http://www.cs.nott.ac.uk/~gmh/wrapper.pdf

The transformation itself is mindbogglingly easy, which makes this a
good start: You only have to understand the formalisms, not so much what
the formalisms are representing. To quote spj: It usually turns out to
be more interesting and challenging than it seemed at first.

I'm tempted to write that this is a paper for everyone trying to figure
out what the heck Jonathan is talking about.

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Nicholls, Mark

[snip]

-- C#: interface IX1 { String foo1(int); }
class IX1 obj where 
  foo1 :: Int - obj - String

Yep...I think that's what I'd dothough I would have done...

foo1 :: obj - Int - String

Does that matter?


-- C#: interface IX2A { String foo2(A); }
class IX2 obj a where 
  foo2 :: a - obj - String

Ok same here

--C#: interface IX3A where A : IY { String foo3(A); }
class IY a where {- ... -}
class IY a = IX3 obj a where 
  foo3 :: a - obj - String

Yep I think again I would have guessed at that

--C#: interface IX4A : IZ where A : IY
class IZ a where {- ... -}
class (IY a, IZ obj) = IX4 obj a where
  foo4 :: a - obj - String

H...this would have been one of my guessesbut let me have a
go... 

This assumes your objects are immutable, otherwise you would have to
return (obj,String) instead of just String and then you most likely
want to
use the state monad and do notation to make functional programming
look
more like imperative programming.

This is finemy oop is largely immutable.

You really have to drop the OO way of thinking, 
which I find the hardest :)
Haskell's type classes are more powerful in some sense than C#
interfaces;
for example, in C# you can't attach an interface to any class (take for
example the Point struct), it has to be your own class, while in
Haskell,
you can implement an instance of a type class for any datatype!

OK but I was going to go onto 

Interface IXA 
where A : IXA
{
}

And 

Interface IXA,B 
where A : B
{
}

Where I cannot see a way to do the above in Haskell at allas
interfaces effectively operator on type classes not typeswhich seems
inherently more powerful

But if these could be done in Haskell the see what could be made of
stuff likewhich is obviously problematic in C# it obviously doesn't
workbut potentially does make 'sense'.

Interface IXA : A
{
}

Hope this helps a bit. As I'm new myself to Haskell, so take this with
a
grain of salt.

It does...I will have a go with your sample answers.

Once you bite the bullet, I found Haskell a lot more fun than C#,
although
C# of course comes with a gigantic .NET framework and tools...

I'm looking at Haskell because of the formality of it's type
systembut I'm actually not convinced it is as powerful as an OO
onei.e. OO ones operatate principally (in Haskell speak) on type
classes not types

Peter

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Nicholls, Mark
Sent: Wednesday, January 02, 2008 5:41 PM
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Is there anyone out there who can translate C#
generics into Haskell?

I'm trying to translate some standard C# constucts into Haskell... some
of this seems easy

Specifically

1) 

Interface IX
{
}

2)

Interface IXA
{
}

3)

Interface IXA
Where A : IY
{
}

4)

Interface IXA : IZ
Where A : IY
{
}


I can take a punt at the first 2but then it all falls apart
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Nicholls, Mark
Can you give me a summary of why it's meaningless.both would seem to
describe/construct values/objectsthey may not be equivalent, but I
would expect some considerable overlap.

-Original Message-
From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
Sent: 02 January 2008 20:29
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Is there anyone out there who can translate
C# generics into Haskell?

Hello Mark,

Wednesday, January 2, 2008, 7:40:31 PM, you wrote:

 I'm trying to translate some standard C# constucts into Haskell...
some

it's meaningless. read
http://haskell.org/haskellwiki/OOP_vs_type_classes
and especially papers mentioned in the References

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Bulat Ziganshin
Hello Mark,

Thursday, January 3, 2008, 1:22:26 PM, you wrote:

because they have different models. i recommend you to start from
learning this model, otherwise you will don't understand how Haskell
really works and erroneously apply your OOP knowledge to Haskell data
structures.

shortly said, there are 3 ways to polymorphism:

1) C++ templates - type-specific code generated at compile time
2) OOP classes - every object carries VMT which allows to select
type-specific operation
3) type classes - dictionary of type-specific operations is given as
additional hidden argument to each function

Haskell uses t.c. and its abilities are dictated by this
implementation. there is no simple and direct mapping between
features provided by OOP and t.c.


 Can you give me a summary of why it's meaningless.both would seem to
 describe/construct values/objectsthey may not be equivalent, but I
 would expect some considerable overlap.

 -Original Message-
 From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
 Sent: 02 January 2008 20:29
 To: Nicholls, Mark
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] Is there anyone out there who can translate
 C# generics into Haskell?

 Hello Mark,

 Wednesday, January 2, 2008, 7:40:31 PM, you wrote:

 I'm trying to translate some standard C# constucts into Haskell...
 some

 it's meaningless. read
 http://haskell.org/haskellwiki/OOP_vs_type_classes
 and especially papers mentioned in the References




-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: check if program uses haskell 98 only?

2008-01-03 Thread Henning Thielemann

On Thu, 6 Dec 2007, Henning Thielemann wrote:

 On Thu, 6 Dec 2007, Thomas Hartman wrote:

  On a related note... is there some easy way to be sure that a program I am
  compiling uses only haskell 98? (Because any pure haskell 98 should always
  compile on yhc... right?)

 You can for instance use 'haskell98' as dependent package instead of
 'base' in the Cabal description. If you import other modules, I don't know
 how to check that these are Haskell 98. I weakly remember corner cases
 where GHC accepts more than Haskell 98 in Haskell 98 mode. (At least it
 sometimes suggests fixes for errors that are not Haskell 98, e.g.  class
 constraints in signatures. :-)

Now I have an example: GHC-6.4.1 accepts multi parameter type class
constraints without '-fglasgow-exts'.

  I compile this with ghc, no options, and iIt doesn't have any {-#-#}
  options, so according to what I understand, it is using pure haskell 98.
  So I might think this was a candidate for using on yhc.

 I could not always pass a GHC-certified module to Hugs or even Haddock. I
 remember there is some difference with respect to the trailing 'where' in
 the 'instance' head, if the instance declaration is empty.  Haddock expect
 some spaces in infix operators (I believe ( # ) instead of (#)), which are
 not required by Hugs and GHC.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: The Worker/Wrapper Transformation

2008-01-03 Thread Achim Schneider
Achim Schneider [EMAIL PROTECTED] wrote:

 [...]

I'm trying to grok that

[] = id
++ = .

in the context of Hughes lists.

I guess it would stop to slip away if I knew what : corresponds to.

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: announcing darcs 2.0.0pre2

2008-01-03 Thread Simon Marlow

David Roundy wrote:


Anyhow, could you retry this test with the above change in methodology, and
let me know if (a) the pull is still slow the first time and (b) if it's
much faster the second time (after the reverse unpull/pull)?


I think I've done it in both directions now, and it got faster, but still 
much slower than darcs1:


$ time darcs2 unpull --from-tag 2007-09-25 -a
Finished unpulling.
58.68s real   50.64s user   6.36s system   97% darcs2 unpull --from-tag 
2007-09-25 -a

$ time darcs2 pull -a ../ghc-darcs2
Pulling from ../ghc-darcs2...
Finished pulling and applying.
53.28s real   44.62s user   7.10s system   97% darcs2 pull -a ../ghc-darcs2

This is still an order of magnitude slower than darcs1 for the same 
operation.  (these times are now on the local filesystem, BTW)


Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: Re[2]: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Nicholls, Mark
I loosely do understandbut very looselybut I'm not, as yet,
convinced it is completely relevant.

The implementation may differ, but that does not mean that there is no
overlapI am not expecting one model to be a superset of the other,
but I am expecting some sort of overlap between 'interface'
implementation and type class instance declaration.


-Original Message-
From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
Sent: 03 January 2008 10:54
To: Nicholls, Mark
Cc: Bulat Ziganshin; haskell-cafe@haskell.org
Subject: Re[2]: [Haskell-cafe] Is there anyone out there who can
translate C# generics into Haskell?

Hello Mark,

Thursday, January 3, 2008, 1:22:26 PM, you wrote:

because they have different models. i recommend you to start from
learning this model, otherwise you will don't understand how Haskell
really works and erroneously apply your OOP knowledge to Haskell data
structures.

shortly said, there are 3 ways to polymorphism:

1) C++ templates - type-specific code generated at compile time
2) OOP classes - every object carries VMT which allows to select
type-specific operation
3) type classes - dictionary of type-specific operations is given as
additional hidden argument to each function

Haskell uses t.c. and its abilities are dictated by this
implementation. there is no simple and direct mapping between
features provided by OOP and t.c.


 Can you give me a summary of why it's meaningless.both would seem
to
 describe/construct values/objectsthey may not be equivalent, but I
 would expect some considerable overlap.

 -Original Message-
 From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
 Sent: 02 January 2008 20:29
 To: Nicholls, Mark
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] Is there anyone out there who can
translate
 C# generics into Haskell?

 Hello Mark,

 Wednesday, January 2, 2008, 7:40:31 PM, you wrote:

 I'm trying to translate some standard C# constucts into Haskell...
 some

 it's meaningless. read
 http://haskell.org/haskellwiki/OOP_vs_type_classes
 and especially papers mentioned in the References




-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN / CFP - LLVM bindings for Haskell

2008-01-03 Thread Bryan O'Sullivan
This is an early release of Haskell bindings for the popular LLVM
compiler infrastructure project.

If you don't know what LLVM is, it's a wonderful toybox of compiler
components, from a complete toolchain supporting multiple architectures
through a set of well-defined APIs and IR formats that are designed for
building interesting software with.

The official LLVM home page is here:

  http://llvm.org/

The Haskell bindings are based on Gordon Henriksen's C bindings.  The C
bindings are almost untyped, but the Haskell bindings re-add type safety
to prevent runtime crashes and general badness.

Currently, the entire code generation system is implemented, with most
LLVM data types supported (notably absent are structs).  Also plugged in
is JIT support, so you can generate code at runtime from Haskell and run
it immediately.  I've attached an example.

Please join in the hacking fun!

  darcs get http://darcs.serpentine.com/llvm

If you want a source tarball, fetch it from here:

  http://darcs.serpentine.com/llvm/llvm-0.0.2.tar.gz

(Hackage can't host code that uses GHC 6.8.2's language extension names
yet.)

There's very light documentation at present, but it ought to be enough
to get you going.

b
{-# LANGUAGE TypeOperators #-}

module Fibonacci (main) where

import Control.Monad (forM_)
import Data.Int (Int32)
import System.Environment (getArgs)

import qualified LLVM.Core as Core
import qualified LLVM.Core.Builder as B
import qualified LLVM.Core.Constant as C
import qualified LLVM.Core.Instruction as I
import qualified LLVM.Core.Type as T
import qualified LLVM.Core.Value as V
import qualified LLVM.Core.Utils as U
import qualified LLVM.ExecutionEngine as EE

buildFib :: T.Module - IO (V.Function T.Int32 T.Int32)
buildFib m = do
  let one = C.const (1::Int32)
  two = C.const (2::Int32)
  (fib, entry) - U.defineFunction m fib (T.function undefined undefined)
  bld - B.createBuilder
  exit - Core.appendBasicBlock fib return
  recurse - Core.appendBasicBlock fib recurse
  let arg = V.params fib

  B.positionAtEnd bld entry
  test - B.icmp bld  I.IntSLE arg two
  B.condBr bld test exit recurse

  B.positionAtEnd bld exit
  B.ret bld one

  B.positionAtEnd bld recurse
  x1 - B.sub bld  arg one
  fibx1 - B.call bld  fib x1

  x2 - B.sub bld  arg two
  fibx2 - B.call bld  fib x2

  B.add bld  fibx1 fibx2 = B.ret bld
  return fib

main :: IO ()
main = do
  args - getArgs
  let args' = if null args then [10] else args

  m - Core.createModule fib
  fib - buildFib m
  V.dumpValue fib

  prov - Core.createModuleProviderForExistingModule m
  ee - EE.createExecutionEngine prov
  
  forM_ args' $ \num - do
putStr $ fib  ++ num ++  = 
parm - EE.createGeneric (read num :: Int)
gv - EE.runFunction ee fib [parm]
print (EE.fromGeneric gv :: Int)

define i32 @fib(i32) {
entry:
icmp sle i32 %0, 2  ; i1:1 [#uses=1]
br i1 %1, label %return, label %recurse

return: ; preds = %entry
ret i32 1

recurse:; preds = %entry
sub i32 %0, 1   ; i32:2 [#uses=1]
call i32 @fib( i32 %2 ) ; i32:3 [#uses=1]
sub i32 %0, 2   ; i32:4 [#uses=1]
call i32 @fib( i32 %4 ) ; i32:5 [#uses=1]
add i32 %3, %5  ; i32:6 [#uses=1]
ret i32 %6
}

fib 10 = 55
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: The Worker/Wrapper Transformation

2008-01-03 Thread Brent Yorgey
On Jan 3, 2008 6:08 AM, Achim Schneider [EMAIL PROTECTED] wrote:

 Achim Schneider [EMAIL PROTECTED] wrote:

  [...]

 I'm trying to grok that

 [] = id
 ++ = .

 in the context of Hughes lists.

 I guess it would stop to slip away if I knew what : corresponds to.


Well, (:) has type a - [a] - [a], so a function corresponding to (:) for
Hughes lists should have type

foo :: a - H a - H a

that is,

foo :: a - ([a] - [a]) - [a] - [a]

so it can be written

foo x h = (x:) . h

which lambdabot informs me can also be written as (.) . (:).  But in the end
I'm not sure how helpful that is for understanding Hughes lists! I think the
key sentence from the paper is this: by representing a list xs as the
function (xs ++) that appends this list to another list that has still to be
supplied.  If you understand that sentence, then you can understand why []
is id and (++) is (.).

-Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Peter Verswyvelen
Hi Mark,

 foo1 :: Int - obj - String
 Yep...I think that's what I'd dothough I would have done...
 foo1 :: obj - Int - String
 Does that matter?

Well, it's a good habit in Haskell to move the most important parameter to
the end of the argument list. See e.g.
http://www.haskell.org/haskellwiki/Parameter_order. 

 OK but I was going to go onto 
 Interface IXA where A : IXA {}
 and
 Interface IXA,B where A : B {}

No, I would not know how to that in Haskell using type classes. It seems
Haskell does not allow cycles in type class definitions. But as I'm new,
this does not mean it's not possible. It's more important to know *what* you
are trying to do, than to give a solution in a different language, since OO
and FP are kind of orthogonal languages.

 Where I cannot see a way to do the above in Haskell at allas
 interfaces effectively operator on type classes not typeswhich seems
 inherently more powerful

Yeah, kind of makes sense. I liked interfaces in C# a lot, but when I
started doing everything with interfaces, I found the lack of support for
mixins or default implementations problematic. This ended up in a lot of
copy/paste or encapsulating the implementations into a static class with
plain functions, a mess.

 But if these could be done in Haskell the see what could be made of
 stuff likewhich is obviously problematic in C# it obviously doesn't
 workbut potentially does make 'sense'.
 Interface IXA : A {}

Ah! That's one of the bigger restrictions in C# yes! C++ can do that; ATL
uses it a lot, and I also like that approach. You can emulate mixins with
that, and still stay in the single inheritance paradigm. In Haskell you
don't do that at all of course, since you avoid thinking about objects and
inheritance in the first place.

OO is strange. They offer you the nice concept of inheritance, and then the
guidelines tell you: don't use too many levels of inheritance... Although
I've build huge projects using OO, it always felt a bit like unsafe hacking.
I don't really have that feeling with Haskell, but that could also be
because I'm too new to the language ;-)

 I'm looking at Haskell because of the formality of it's type
 systembut I'm actually not convinced it is as powerful as an OO
 onei.e. OO ones operatate principally (in Haskell speak) on type
 classes not types

Maybe you are right, I don't know, my theoritical skills are not high enough
to answer that. Haskell just feels better to me, although the lack of a
friendly productive IDE and large standard framework remains a bit of a
burden.

Good luck,
Peter

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Nicholls, Mark
Sent: Wednesday, January 02, 2008 5:41 PM
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Is there anyone out there who can translate C#
generics into Haskell?

I'm trying to translate some standard C# constucts into Haskell... some
of this seems easy

Specifically

1) 

Interface IX
{
}

2)

Interface IXA
{
}

3)

Interface IXA
Where A : IY
{
}

4)

Interface IXA : IZ
Where A : IY
{
}


I can take a punt at the first 2but then it all falls apart
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: The Worker/Wrapper Transformation

2008-01-03 Thread Achim Schneider
Brent Yorgey [EMAIL PROTECTED] wrote:

 
 Well, (:) has type a - [a] - [a], so a function corresponding to
 (:) for Hughes lists should have type
 
 foo :: a - H a - H a
 
 [...]
 I think the key sentence from the paper is this: by
 representing a list xs as the function (xs ++) that appends this list
 to another list that has still to be supplied.  If you understand
 that sentence, then you can understand why [] is id and (++) is (.).
 
Yes, I did.

They key was not thinking that : has type

(:) :: a - a - [a]

, or, put differently, beat the lisp out of me, thanks.

The problem is merely that Haskell and lisp are too similar in a much
too different way.

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: The Worker/Wrapper Transformation

2008-01-03 Thread Achim Schneider
Achim Schneider [EMAIL PROTECTED] wrote:

 Brent Yorgey [EMAIL PROTECTED] wrote:
 
  
  Well, (:) has type a - [a] - [a], so a function corresponding to
  (:) for Hughes lists should have type
  
  foo :: a - H a - H a
  
  [...]
  I think the key sentence from the paper is this: by
  representing a list xs as the function (xs ++) that appends this
  list to another list that has still to be supplied.  If you
  understand that sentence, then you can understand why [] is id and
  (++) is (.).
  
 Yes, I did.
 
 They key was not thinking that : has type
 
 (:) :: a - a - [a]
 
 , or, put differently, beat the lisp out of me, thanks.
 
What the hell am I talking about?

(define (cons x y)
   (lambda (m) (m x y)))
 
(define (car z)
   (z (lambda (p q) p)))

(define (cdr z)
   (z (lambda (p q) q)))

: is, in a sense, \.

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: The Worker/Wrapper Transformation

2008-01-03 Thread Isaac Dupree

Achim Schneider wrote:

Achim Schneider [EMAIL PROTECTED] wrote:


[...]


I'm trying to grok that

[] = id
++ = .

in the context of Hughes lists.


they are also known as difference lists, and also used at type String 
in the Prelude as ShowS, to help avoid quadratic behavior when making 
complicated Strings.  the [a]-[a] is not an ordinary function -- it's 
expected not to examine its argument, just to use it exactly once (is 
there a formal way to say that?)


~Isaac
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Nicholls, Mark
Ahh ok I see what is meant by the parameter order

-Original Message-
From: Peter Verswyvelen [mailto:[EMAIL PROTECTED] On Behalf Of
Peter Verswyvelen
Sent: 03 January 2008 12:02
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: RE: [Haskell-cafe] Is there anyone out there who can translate
C# generics into Haskell?

Hi Mark,

 foo1 :: Int - obj - String
 Yep...I think that's what I'd dothough I would have done...
 foo1 :: obj - Int - String
 Does that matter?

Well, it's a good habit in Haskell to move the most important
parameter to
the end of the argument list. See e.g.
http://www.haskell.org/haskellwiki/Parameter_order. 

 OK but I was going to go onto 
 Interface IXA where A : IXA {}
 and
 Interface IXA,B where A : B {}

No, I would not know how to that in Haskell using type classes. It seems
Haskell does not allow cycles in type class definitions. But as I'm new,
this does not mean it's not possible. It's more important to know *what*
you
are trying to do, than to give a solution in a different language, since
OO
and FP are kind of orthogonal languages.

 Where I cannot see a way to do the above in Haskell at allas
 interfaces effectively operator on type classes not typeswhich
seems
 inherently more powerful

Yeah, kind of makes sense. I liked interfaces in C# a lot, but when I
started doing everything with interfaces, I found the lack of support
for
mixins or default implementations problematic. This ended up in a
lot of
copy/paste or encapsulating the implementations into a static class with
plain functions, a mess.

 But if these could be done in Haskell the see what could be made of
 stuff likewhich is obviously problematic in C# it obviously
doesn't
 workbut potentially does make 'sense'.
 Interface IXA : A {}

Ah! That's one of the bigger restrictions in C# yes! C++ can do that;
ATL
uses it a lot, and I also like that approach. You can emulate mixins
with
that, and still stay in the single inheritance paradigm. In Haskell you
don't do that at all of course, since you avoid thinking about objects
and
inheritance in the first place.

OO is strange. They offer you the nice concept of inheritance, and then
the
guidelines tell you: don't use too many levels of inheritance...
Although
I've build huge projects using OO, it always felt a bit like unsafe
hacking.
I don't really have that feeling with Haskell, but that could also be
because I'm too new to the language ;-)

 I'm looking at Haskell because of the formality of it's type
 systembut I'm actually not convinced it is as powerful as an OO
 onei.e. OO ones operatate principally (in Haskell speak) on type
 classes not types

Maybe you are right, I don't know, my theoritical skills are not high
enough
to answer that. Haskell just feels better to me, although the lack of
a
friendly productive IDE and large standard framework remains a bit of a
burden.

Good luck,
Peter

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Nicholls, Mark
Sent: Wednesday, January 02, 2008 5:41 PM
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Is there anyone out there who can translate C#
generics into Haskell?

I'm trying to translate some standard C# constucts into Haskell... some
of this seems easy

Specifically

1) 

Interface IX
{
}

2)

Interface IXA
{
}

3)

Interface IXA
Where A : IY
{
}

4)

Interface IXA : IZ
Where A : IY
{
}


I can take a punt at the first 2but then it all falls apart
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The Worker/Wrapper Transformation

2008-01-03 Thread Isaac Dupree

Achim Schneider wrote:

...is a paper about automatic specialisation of functions by unboxing
arguments, one could say. I'm only on page 6, but already survived the
first formalisms, which is bound to mean that the rest of the paper is
likewise accessible, as hinted on at ltu.

http://www.cs.nott.ac.uk/~gmh/wrapper.pdf

The transformation itself is mindbogglingly easy, which makes this a
good start: You only have to understand the formalisms, not so much what
the formalisms are representing. To quote spj: It usually turns out to
be more interesting and challenging than it seemed at first.

I'm tempted to write that this is a paper for everyone trying to figure
out what the heck Jonathan is talking about.



I like it!  Of course the technique itself doesn't provide guidance on 
what type you want to transform a function to.


on page 6, stronger vs weaker seemed backwards to me... isn't (wrap ◦ 
unwrap = idA) a stronger condition than (wrap ◦ unwrap ◦ body = body), 
because it tells you more, and is true in fewer cases? (which is also 
why you want to assume (wrap ◦ unwrap = idA) when you can, because it's 
the most useful one for subsequent program transformation)



and then the inevitable minor copy-editing :-)

p. 22. intentional properties -- intensional (right?)

p. 27. typo 'unwarp' for 'unwrap'

BTW. GHC currently does allow e.g. (I# (1# +# 2#)), not just (case (1# 
+# 2#) of n# - I# n#) -- the strictness implications seem pretty 
straightforwards (it's trivial to transform away).


p. 29. in both these system - systems


~Isaac
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: The Worker/Wrapper Transformation

2008-01-03 Thread Achim Schneider
Achim Schneider [EMAIL PROTECTED] wrote:

 (define (cons x y)
(lambda (m) (m x y)))
  
 (define (car z)
(z (lambda (p q) p)))
 
 (define (cdr z)
(z (lambda (p q) q)))
 
, which, just for completeness, can be of course also be done in
Haskell:

cons :: a - b - (a - b - c) - c
cons x y m = m x y

car :: ((a - b - a) - c) - c 
car z = z $ \p q - p

cdr :: ((a - b - b) - c) - c
cdr z = z $ \p q - q

Prelude car $ cdr $ cdr $ cons 1 $ cons 2 $ cons 3 ()
3


-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Consensus about databases / serialization

2008-01-03 Thread Peter Verswyvelen
Looks good! I liked relational algebra much much more than SQL, so I'll 
certainly have to look into that.


Thanks,
Peter

Justin Bailey wrote:

I can speak to haskelldb a little, see below:

On Jan 2, 2008 3:50 AM, Peter Verswyvelen [EMAIL PROTECTED] wrote:
  

·regarding Haskell and databases, the page
http://haskell.org/haskellwiki/Libraries_and_tools/Database_interfaces
describes a few, but which are the ones that are stable and practical? Any
user experiences?



I started looking at haskell database libraries to generate SQL for
me. Haskelldb does this well - it uses a higher-level representation
of queries based on relational algebra (also the basis of SQL) which
is pretty easy to understand if you know SQL.  It takes care of a lof
the details of generating SQL strings, and does it in a mostly
type-safe way.

It is a bit complicated to install the library and all its
dependencies, because it can work with 3+ (mysql, postgres, odbc)
databases using two different backends (hdbc and hsql). I chose to go
with HDBC because it compiled on Windows and postgres because thats
what we have at my workplace. Once I got it built and installed its
worked well for me.

Until the most recent versions though, it added a distinct operator
to all select statements. I submitted a patch which was accepted and
now that behavior is no longer the default. It is semi-actively
maintained by the original authors and Bjorn, at least, has been very
responsive to my queries on the haskelldb-users mailing list. He also
has made minor updates to keep it compiling with the latest GHC and
Cabal.

Hope that helps!

Justin


  


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Basic question concerning data constructors

2008-01-03 Thread Yitzchak Gale
Hi Benja,

I wrote:
 By the type expression Integer - Integer
 we mean all Haskell functions mapping Integers to Integers.
 There are only countably many of those.
 ...
 But that was not the context in this thread. The category
 Hask that we often mention in discussions about Haskell
 the programming language is most certainly a small category.

Benja Fallenstein wrote:
 I don't know. My understanding has been that at least part of the
 benefit of denotational semantics is that you can define what an
 expression means without referring back to the syntactic construction
 or the operational semantics of that expression -- and thus use the
 denotational semantics to check whether the operational semantics are
 right. But if you start with all Haskell functions, you already
 have to know what a Haskell function *is*.

Denotational semantics maps expressions in a
language - hence, syntax - into something that
represents their semantics. You can choose
different such mappings to represent different
semantics of the same expressions.

The Haskell Report clearly defines what a Haskell
function is in terms of syntax. So my semantics are
well-defined, and they represent what I understand
when I read a Haskell program.

In fact, these semantics do not really depend on
all aspects of the syntax - only the existence of
certain primitive functions, and certain constructions
such as function definition, pattern matching,
ADTs, etc. The same assumptions are made for any
semantics of Haskell.

Benja Fallenstein wrote:
 I think it should be allowed to think of the semantics of Haskell as
 being defined independently of the (relatively operational) notion of
 computable function, and then define computable function to be
 that subset of the functions in the model that you can actually write
 in Haskell.

Computable function is not operational - it just means
functions that are lambdas, if you'd like. It just so happens
that, so far, those are the only functions we know how
to compute operationally. Maybe that quantum stuff...

But yes, sure you can do that. That seems to be the approach
in some papers. In particular, the one by Reynolds in which he proves
that Haskell types cannot be represented by sets.

Sounds like strong evidence that those are the wrong
semantics to choose when studying Haskell as a programming
language. Though it is certainly interesting to do so
in a theoretical setting.

 And the only explicit non-syntactic constructions of
 models for Haskell-like languages that I'm familiar with aren't
 countable (they contain all continuous functions, which in the case of
 (Integer - Integer) comes out to all monotonous functions).

It is not any less syntactic than mine. It only differs in
the semantics assigned to the symbol Integer - Integer.

 So I disagree that the function types of Hask should automatically be
 taken to be countable.

No, I agree with you. It's not automatic. It depends on
your choice of semantics.

 If you want to assume it for some given
 purpose, sure, fine, but IMO that's an additional assumption, not
 something inherent in the Haskell language.

Agreed.

Thanks,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Escape Codes

2008-01-03 Thread H .
Hi,

 It would be nice if you could package this and release it on hackage.
 http://hackage.haskell.org/packages/hackage.html

I packaged it, perhaps you can have a look at it, if it is, what you thought...

When I get a username, I'll put it on hackage :)

--
H.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Basic question concerning the category Hask (was: concerning data constructors)

2008-01-03 Thread Yitzchak Gale
Jonathan Cast wrote:
 The normal view taken by Haskellers is that the denotations of
 Haskell types are CPPOs.

I wrote:
 CPPO?

 (1) Must be monotone
 (2) Must be continuous

 Could you please define what you mean by those terms
 in this context?

Jens Blanck wrote:
 The extra P would stand for pointed (has a least element, bottom), this is
 common in some communities. To me though, a cpo (complete partial order) is
 closed under directed suprema and the empty set is directed so bottom is
 already required. The category of cpos in not cartesian closed. For
 denotational semantics I believe the subcategory of Scott domains are what
 is usually considered.

 Continuous functions on cpos are by definition monotone and they respect
 directed suprema.

Thanks!
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Consensus about databases / serialization

2008-01-03 Thread Yitzchak Gale
Peter Verswyvelen wrote:
  Looks good! I liked relational algebra much much more than SQL, so I'll
 certainly have to look into that.

I agree. I have not tried haskelldb yet, but I would
like to.

My impression from some previous posts is that
because of the high-level approach, it is difficult
to control the precise SQL that is generated. In practice,
you almost always have to do some tweaking that is
at least DB-dependent, and often application dependent.

Is there any way to do that in haskelldb? If not,
is there an obvious way to add it?

Thanks,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Difference lists and ShowS

2008-01-03 Thread Henning Thielemann

On Thu, 3 Jan 2008, Achim Schneider wrote:

 Henning Thielemann [EMAIL PROTECTED] wrote:

  Sometimes I believed that I understand this reason, but then again I
  do not understand. I see that left-associative (++) like in
((a0 ++ a1) ++ a2) ++ a3
   would cause quadratic time. But (++) is right-associative and
  'concat' is 'foldr'. They should not scan the leading lists more than
  once. Also
http://en.wikipedia.org/wiki/Difference_list
   doesn't answer this question. Where exactly is the problem?
 

 | The shows functions return a function that prepends the output String
 | to an existing String. This allows constant-time concatenation of
 | results using function composition.

How is constant-time concatenation meant? If I process all list
elements, it will need linear time. If I do not touch any element, I will
need no time due to lazy evaluation. As far as I know, lazy evaluation is
implemented by returning a union of a routine generating the actual value
and the value, if it was already computed. Thus, calling (++) returns a
function internally.

 I figure it's (constant vs. linear) vs. (linear vs. quadratic), for
 more involved examples.

I can't see it. If I consider (x++y) but I do not evaluate any element of
(x++y) or only the first element, then this will need constant time. If I
evaluate the first n elements I need n computation time units. How is (.)
on difference lists faster than (++) here?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[4]: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Bulat Ziganshin
Hello Mark,

Thursday, January 3, 2008, 2:13:08 PM, you wrote:

of course *some* overlap exists but in order to understand it you
should know exact shape of both methods

when i tried to develop complex library without understanding t.c.
implementation, i constantly goes into the troubles - things that i
(using my OOP experience) considered as possible, was really
impossible in Haskell

so i'm really wonder why you don't want to learn the topic thoroughly


 I loosely do understandbut very looselybut I'm not, as yet,
 convinced it is completely relevant.

 The implementation may differ, but that does not mean that there is no
 overlapI am not expecting one model to be a superset of the other,
 but I am expecting some sort of overlap between 'interface'
 implementation and type class instance declaration.


 -Original Message-
 From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
 Sent: 03 January 2008 10:54
 To: Nicholls, Mark
 Cc: Bulat Ziganshin; haskell-cafe@haskell.org
 Subject: Re[2]: [Haskell-cafe] Is there anyone out there who can
 translate C# generics into Haskell?

 Hello Mark,

 Thursday, January 3, 2008, 1:22:26 PM, you wrote:

 because they have different models. i recommend you to start from
 learning this model, otherwise you will don't understand how Haskell
 really works and erroneously apply your OOP knowledge to Haskell data
 structures.

 shortly said, there are 3 ways to polymorphism:

 1) C++ templates - type-specific code generated at compile time
 2) OOP classes - every object carries VMT which allows to select
 type-specific operation
 3) type classes - dictionary of type-specific operations is given as
 additional hidden argument to each function

 Haskell uses t.c. and its abilities are dictated by this
 implementation. there is no simple and direct mapping between
 features provided by OOP and t.c.


 Can you give me a summary of why it's meaningless.both would seem
 to
 describe/construct values/objectsthey may not be equivalent, but I
 would expect some considerable overlap.

 -Original Message-
 From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
 Sent: 02 January 2008 20:29
 To: Nicholls, Mark
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] Is there anyone out there who can
 translate
 C# generics into Haskell?

 Hello Mark,

 Wednesday, January 2, 2008, 7:40:31 PM, you wrote:

 I'm trying to translate some standard C# constucts into Haskell...
 some

 it's meaningless. read
 http://haskell.org/haskellwiki/OOP_vs_type_classes
 and especially papers mentioned in the References







-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Difference lists and ShowS (Was: The Worker/Wrapper Transformation)

2008-01-03 Thread Daniel Fischer
Am Donnerstag, 3. Januar 2008 14:48 schrieb Henning Thielemann:
 On Thu, 3 Jan 2008, Isaac Dupree wrote:
  Achim Schneider wrote:
   Achim Schneider [EMAIL PROTECTED] wrote:
   [...]
  
   I'm trying to grok that
  
   [] = id
   ++ = .
  
   in the context of Hughes lists.
 
  they are also known as difference lists, and also used at type String
  in the Prelude as ShowS, to help avoid quadratic behavior when making
  complicated Strings.

 Sometimes I believed that I understand this reason, but then again I do
 not understand. I see that left-associative (++) like in
   ((a0 ++ a1) ++ a2) ++ a3
  would cause quadratic time. But (++) is right-associative and 'concat' is
 'foldr'. They should not scan the leading lists more than once.
  Also
   http://en.wikipedia.org/wiki/Difference_list
  doesn't answer this question. Where exactly is the problem?

Show a binary tree inorder? 
L-T-R gives (show L) ++ (show T ++ (show R))
gives ((show LL) ++ (showLT ++ (show LR))) ++ (show T ++ (show R))
gives (((show LLL) ++ (show LLT ++ (show LLR))) ++ (show LT ++ (show LR))) ++ 
(show T ++ (show R))

etc.
If the tree is large, you end up with a pretty large left association for the 
left subtree. True, there's lot of right association, too, but bad enough, I 
think.

Cheers,
Daniel
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Difference lists and ShowS

2008-01-03 Thread Achim Schneider
Henning Thielemann [EMAIL PROTECTED] wrote:

  I figure it's (constant vs. linear) vs. (linear vs. quadratic), for
  more involved examples.
 
 I can't see it. If I consider (x++y) but I do not evaluate any
 element of (x++y) or only the first element, then this will need
 constant time. If I evaluate the first n elements I need n
 computation time units. How is (.) on difference lists faster than
 (++) here?

It's in multiple calls to length if you do ((x++y)++z), the first run
over x can be avoided. It basically gets rewritten to (x++y++z) by
another level of abstraction.


-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Difference lists and ShowS (Was: The Worker/Wrapper Transformation)

2008-01-03 Thread Tillmann Rendel

Henning Thielemann wrote:

Sometimes I believed that I understand this reason, but then again I do
not understand. I see that left-associative (++) like in
  ((a0 ++ a1) ++ a2) ++ a3
 would cause quadratic time. But (++) is right-associative and 'concat' is
'foldr'. They should not scan the leading lists more than once


the point is that the the right-associativity of (++) doesn't prevent 
terms of the form


  ((a0 ++ a1) ++ a2) ++ a3

to arise due to explicit parentheses or (more important) recursive 
processing of data structures. consider showing a tree-like structure of 
the form


  ((a0 `Cons` a1) `Cons` a2) `Cons` a3

A naive Show instance will basically replace every Cons by (++) and 
produce a string concatenation of the offending left-associative form:


  ((show a0 ++ show a1) ++ show a2) ++ show a3

Tillmann
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Difference lists and ShowS (Was: The Worker/Wrapper Transformation)

2008-01-03 Thread Henning Thielemann

On Thu, 3 Jan 2008, Daniel Fischer wrote:

 Am Donnerstag, 3. Januar 2008 14:48 schrieb Henning Thielemann:

  Sometimes I believed that I understand this reason, but then again I do
  not understand. I see that left-associative (++) like in
((a0 ++ a1) ++ a2) ++ a3
   would cause quadratic time. But (++) is right-associative and 'concat' is
  'foldr'. They should not scan the leading lists more than once.
   Also
http://en.wikipedia.org/wiki/Difference_list
   doesn't answer this question. Where exactly is the problem?

 Show a binary tree inorder?
 L-T-R gives (show L) ++ (show T ++ (show R))
 gives ((show LL) ++ (showLT ++ (show LR))) ++ (show T ++ (show R))
 gives (((show LLL) ++ (show LLT ++ (show LLR))) ++ (show LT ++ (show LR))) ++
 (show T ++ (show R))

 etc.
 If the tree is large, you end up with a pretty large left association for the
 left subtree. True, there's lot of right association, too, but bad enough, I
 think.

With difference lists I write

shows L . (shows T . shows R)
(shows LL . (showsLT . shows LR)) . (shows T . shows R)
((shows LLL . (shows LLT . shows LLR)) . (showsLT . shows LR)) . (shows T . 
shows R)

I still need to resolve three (.) until I get to the first character of
the result string, but for the subsequent characters I do not need to
resolve those dots. In the end, resolution of all (.) may need some time
but then concatenation is performed entirely right-associative. Seems to
be that this is the trick ...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: Re[4]: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Nicholls, Mark
I do not necessarily disagree

But if I can identify the overlapthen I have leant the overlap...on
the cheap.
 
-Original Message-
From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
Sent: 03 January 2008 14:39
To: Nicholls, Mark
Cc: Bulat Ziganshin; haskell-cafe@haskell.org
Subject: Re[4]: [Haskell-cafe] Is there anyone out there who can
translate C# generics into Haskell?

Hello Mark,

Thursday, January 3, 2008, 2:13:08 PM, you wrote:

of course *some* overlap exists but in order to understand it you
should know exact shape of both methods

when i tried to develop complex library without understanding t.c.
implementation, i constantly goes into the troubles - things that i
(using my OOP experience) considered as possible, was really
impossible in Haskell

so i'm really wonder why you don't want to learn the topic thoroughly


 I loosely do understandbut very looselybut I'm not, as yet,
 convinced it is completely relevant.

 The implementation may differ, but that does not mean that there is no
 overlapI am not expecting one model to be a superset of the other,
 but I am expecting some sort of overlap between 'interface'
 implementation and type class instance declaration.


 -Original Message-
 From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
 Sent: 03 January 2008 10:54
 To: Nicholls, Mark
 Cc: Bulat Ziganshin; haskell-cafe@haskell.org
 Subject: Re[2]: [Haskell-cafe] Is there anyone out there who can
 translate C# generics into Haskell?

 Hello Mark,

 Thursday, January 3, 2008, 1:22:26 PM, you wrote:

 because they have different models. i recommend you to start from
 learning this model, otherwise you will don't understand how Haskell
 really works and erroneously apply your OOP knowledge to Haskell data
 structures.

 shortly said, there are 3 ways to polymorphism:

 1) C++ templates - type-specific code generated at compile time
 2) OOP classes - every object carries VMT which allows to select
 type-specific operation
 3) type classes - dictionary of type-specific operations is given as
 additional hidden argument to each function

 Haskell uses t.c. and its abilities are dictated by this
 implementation. there is no simple and direct mapping between
 features provided by OOP and t.c.


 Can you give me a summary of why it's meaningless.both would seem
 to
 describe/construct values/objectsthey may not be equivalent, but
I
 would expect some considerable overlap.

 -Original Message-
 From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
 Sent: 02 January 2008 20:29
 To: Nicholls, Mark
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] Is there anyone out there who can
 translate
 C# generics into Haskell?

 Hello Mark,

 Wednesday, January 2, 2008, 7:40:31 PM, you wrote:

 I'm trying to translate some standard C# constucts into Haskell...
 some

 it's meaningless. read
 http://haskell.org/haskellwiki/OOP_vs_type_classes
 and especially papers mentioned in the References







-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Consensus about databases / serialization

2008-01-03 Thread Peter Verswyvelen
Yitz wrote:
 My impression from some previous posts is that
 because of the high-level approach, it is difficult
 to control the precise SQL that is generated. In practice,
 you almost always have to do some tweaking that is
 at least DB-dependent, and often application dependent.

Can't the same be said regarding SQL itself? It sometimes needs tweaking.
That's the problem with any high level abstraction no? Just like in Haskell
you sometimes have to use strictness tweaks. Of course having an extra layer
on top of SQL will make the tweaking more difficult :)

Peter


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: The Worker/Wrapper Transformation

2008-01-03 Thread Jonathan Cast

On 3 Jan 2008, at 4:49 AM, Isaac Dupree wrote:


Achim Schneider wrote:

Achim Schneider [EMAIL PROTECTED] wrote:

[...]

I'm trying to grok that
[] = id
++ = .
in the context of Hughes lists.


they are also known as difference lists, and also used at type  
String in the Prelude as ShowS, to help avoid quadratic behavior  
when making complicated Strings.  the [a]-[a] is not an ordinary  
function -- it's expected not to examine its argument, just to use  
it exactly once (is there a formal way to say that?)


f xn = f [] ++ xn

is the first thing off the top of my head.

OTOH, examining your argument (while, strictly speaking unsafe) is  
pretty darn cool:


f [] = foo
f (c:s) | isAlphaNum c = foo ++c:s
| otherwise= foo++c:s

Token prepend.

jcc

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Jonathan Cast

On 3 Jan 2008, at 7:40 AM, Nicholls, Mark wrote:


I do not necessarily disagree

But if I can identify the overlapthen I have leant the  
overlap...on

the cheap.


Not really.  You still don't have the context which allows you to fit  
the Haskell features into a complete system.  Meaning is derived from  
context, it's not inherent --- and the meaning and use of even those  
features that translate between Haskell and C++ is completely  
different, because the context they need to fit into makes them  
suitable for different sorts of applications.


jcc

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Basic question concerning the category Hask (was: concerning data constructors)

2008-01-03 Thread Jonathan Cast

On 3 Jan 2008, at 3:40 AM, Jens Blanck wrote:


 The normal view taken by Haskellers is that the denotations of
 Haskell types are CPPOs.

CPPO?

  So:

 (1) Must be monotone
 (2) Must be continuous

Could you please define what you mean by those terms
in this context?

 (Needn't be strict, even though that messes up the resulting  
category

 substantially).

I'm not convinced that the category is all that messed up.


Well, no coproducts (Haskell uses a lifted version of the coproduct  
from CPO).  Of course, Haskell makes things even worse by lifting the  
product and exponential objects, as well, which come to think of it  
is unnecessary even in the category of CPPOs and not necessarily  
strict continuous functions.


The extra P would stand for pointed (has a least element, bottom),  
this is common in some communities. To me though, a cpo (complete  
partial order) is closed under directed suprema and the empty set is  
directed so bottom is already required.


Not so.  A set is directed iff every finite subset has an upper bound  
in the set; {} is finite, so it must have an upper bound in the set.   
So directed sets must be non-empty.  (So CPOs needn't be pointed).


jcc

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [darcs-devel] announcing darcs 2.0.0pre2

2008-01-03 Thread David Roundy
On Thu, Jan 03, 2008 at 11:11:40AM +, Simon Marlow wrote:
 David Roundy wrote:
  Anyhow, could you retry this test with the above change in methodology, and
  let me know if (a) the pull is still slow the first time and (b) if it's
  much faster the second time (after the reverse unpull/pull)?
 
 I think I've done it in both directions now, and it got faster, but still 
 much slower than darcs1:
 
 $ time darcs2 unpull --from-tag 2007-09-25 -a
 Finished unpulling.
 58.68s real   50.64s user   6.36s system   97% darcs2 unpull --from-tag 
 2007-09-25 -a
 $ time darcs2 pull -a ../ghc-darcs2
 Pulling from ../ghc-darcs2...
 Finished pulling and applying.
 53.28s real   44.62s user   7.10s system   97% darcs2 pull -a ../ghc-darcs2
 
 This is still an order of magnitude slower than darcs1 for the same 
 operation.  (these times are now on the local filesystem, BTW)

Is this with the latest darcs-unstable? I made some improvements shortly
before Christmas (or was it after Christmas?) that ought to improve the
speed of pulls dramatically.  We were doing O(N^2) operations in our
handling of pending changes, which I fixed (I think).  So I'll wait on
investigating this until you've confirmed which version this was tested
with.  And thanks for the testing!
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Difference lists and ShowS

2008-01-03 Thread apfelmus

Henning Thielemann wrote:

I can't see it. If I consider (x++y) but I do not evaluate any element of
(x++y) or only the first element, then this will need constant time. If I
evaluate the first n elements I need n computation time units. How is (.)
on difference lists faster than (++) here?


That's a very good question. Basically, the problem is: how to specify 
the time complexity of an operation under lazy evaluation?



You argue that (++) is constant time in the sense that evaluating (x ++ 
y) to WHNF is O(1) when x and y are already in WHNF. Same for (.). This 
is indeed correct but apparently fails to explain why (.) is any better 
than (++). Help!



Of course, this very paradox shows that just looking at WHNF is not 
enough. The next best description is to pretend that our language is 
strict and to consider full normal form


  x in NF, y in NF -- (x++y) evaluates to NF in O(length x) time

Even when x and y are not in normal form, we know that evaluating the 
expression (x ++ y) takes


  O(x ++ y) ~ O(length x) + O(x) + O(y)

time to evaluate to NF. Here, O(e) is the time needed to bring the 
expression e into NF first. This approach now explains that (++) takes 
quadratic time when used left-associatively


  O((x ++ y) ++ z) ~   O(length x + length y) + O(length x)
 + O(x) + O(y) + O(z)

instead of the expected

  O((x ++ y) ++ z) ~ O(x) + O(y) + O(z)

or something (only up to constant factors and stuff, but you get the 
idea). Note that considering NFs is still only an approximation since


  O(head (qsort xs)) ~ O(n) + O(xs)  where n = length xs

instead of the expected

  O(head (qsort xs)) ~ O(qsort xs)
 ~ O(n log n) + O(xs) where n = length xs

thanks to lazy evaluation. Also note that despite considering full 
normal forms, we can express some laziness with this by giving timings 
for an expression in different contexts like


  O(take n ys)
  O(head ys)

instead of only O(ys). Same for parameters with something like

  O(const x) ~ O(1)

instead of the anticipated O(const x) ~ O(x). (For lazy data structures, 
there are better ways to take laziness into account.)




With difference lists I write

shows L . (shows T . shows R)
(shows LL . (showsLT . shows LR)) . (shows T . shows R)
((shows LLL . (shows LLT . shows LLR)) . (showsLT . shows LR)) . (shows T . 
shows R)

I still need to resolve three (.) until I get to the first character of
the result string, but for the subsequent characters I do not need to
resolve those dots. In the end, resolution of all (.) may need some time
but then concatenation is performed entirely right-associative. Seems to
be that this is the trick ...


So far so good, but the problem now is that analyzing (.) with full 
normal forms is doomed since this would mean to evaluate things under 
the lambda which may take less time than doing call-by-need reductions. 
Still, we somehow have


  O(x . y) ~ O(x) + O(y)

which is better than O(x ++ y) but I'm not quite sure how to make this 
exact yet.



In the end, the above O(e)s are just random doodles conjured out of the 
hat, I don't know a formalism for easy reasoning about time in a lazy 
language. Anyone any pointers? Note that the problem is already present 
for difference lists in strict languages.




Regards,
apfelmus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Difference lists and ShowS

2008-01-03 Thread Achim Schneider
apfelmus [EMAIL PROTECTED] wrote:

O((x ++ y) ++ z) ~   O(length x + length y) + O(length x)
   + O(x) + O(y) + O(z)

I would say that it's ~ O(length x) + O(length $ x ++ y) + O(2 * list
mangling)

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] HsColour version confusion

2008-01-03 Thread Adrian Hey

Hello,

I'm confused about which HsColour version I should be using with
Haddock/Cabal (on Windows).

According to this page..

 http://www.cs.york.ac.uk/fp/darcs/hscolour/

..the latest version is 1.9. But the latest version in Hackage is 1.6,
the latest version in the ftp downloads dir is 1.8, unless you want a
pre-compiled windows version in which case you're stuck with 1.3 :-)

Anyone know what's going on?

Thanks
--
Adrian Hey

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Refactoring status

2008-01-03 Thread Peter Verswyvelen
Hi all,

 

Is any work being done on Haskell refactoring support, like HaRe or others? 

 

Is anyone actively using refactoring? When using C#, I used Resharper a lot,
and ever since, I'm really hooked to refactoring, so I miss it a lot when
doing Haskelling. (I never seem to get a function name or signature right
the first time. is it just me? J)

 

I'm currently using Emacs with Haskell Mode (which does not offer
refactoring support) but I think many of you use VIM (which does support
it?)

 

Can one use refactoring outside of an editor? This does not really sound
practical,  but maybe it works?

 

Thank you,

Peter

 

PS: IMHO I don't think text should be the source format of our files. I
think we should use a standarized decorated AST as the source, from which we
can derive a textual (but also graphical) view and editor. Any comments on
that? J

 

 

 

 





 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Importing Data.Char speeds up ghc around 70%

2008-01-03 Thread Richard Kelsall

Simon Marlow wrote:
...
I have seen strange artifacts like this before that turned out to be 
caused by one of two things:


 - bad cache interactions, e.g. we just happen to have laid out the code in
   such a way that frequently accessed code sequences push each other out
   of the cache, or the relative position of the heap and stack have a bad
   interaction.  This happens less frequently these days with 4-way and
   8-way associative caches on most CPUs.

 - alignment issues, such as storing or loading a lot of misaligned Doubles

in the second case, I've seen the same program run +/- 50% in 
performance from run to run, just based on random alignment of the 
stack.  But it's not likely to be the issue here, I'm guessing.  If it 
is code misalignment, that's something we can easily fix (but I don't 
*think* we're doing anything wrong in that respect).


I have an Opteron box here that regularly gives +/- 20% from run to run 
of the same program with no other load on the machine.  I have no idea 
why...



...
This got me wondering how I could test for code misalignment problems.
I expect there's a cleverer way, but how about a single executable
containing several copies of the same code to be tested and a loop
that runs and times the different copies. A consistently higher or
lower runtime from one copy would indicate a misalignment problem.
(I'm assuming the different copies of the code would probably load
at fairly random alignments, random padding could be added.) It might
have to run the copies in a different order each time round the loop
to avoid the possibility of external periodic events affecting a
particular copy.


Richard.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Consensus about databases / serialization

2008-01-03 Thread Lihn, Steve
 
For small queries, it does not matter much which approach you choose.
But for large, complex queries, such 3-table join (especial Star
Transformation) and/or large data set (millions of rows involved in
large data warehouses), the performance will differ by order of
magnitude, depending on how things are optimized.  

Steve 

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Peter Verswyvelen
Subject: RE: [Haskell-cafe] Consensus about databases / serialization

Yitz wrote:
 My impression from some previous posts is that
 because of the high-level approach, it is difficult
 to control the precise SQL that is generated. In practice,
 you almost always have to do some tweaking that is
 at least DB-dependent, and often application dependent.

Can't the same be said regarding SQL itself? It sometimes needs
tweaking.
That's the problem with any high level abstraction no? Just like in
Haskell
you sometimes have to use strictness tweaks. Of course having an extra
layer
on top of SQL will make the tweaking more difficult :)

Peter




--
Notice:  This e-mail message, together with any attachments, contains
information of Merck  Co., Inc. (One Merck Drive, Whitehouse Station,
New Jersey, USA 08889), and/or its affiliates (which may be known
outside the United States as Merck Frosst, Merck Sharp  Dohme or MSD
and in Japan, as Banyu - direct contact information for affiliates is 
available at http://www.merck.com/contact/contacts.html) that may be 
confidential, proprietary copyrighted and/or legally privileged. It is 
intended solely for the use of the individual or entity named on this 
message. If you are not the intended recipient, and have received this 
message in error, please notify us immediately by reply e-mail and then 
delete it from your system.

--
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Refactoring status

2008-01-03 Thread C.M.Brown
Hi Peter,

 Is any work being done on Haskell refactoring support, like HaRe or others?

HaRe is still very active and is due for a new release very soon.
There are probably in excess of 40 refactorings for HaRe in total now, and
I intend to add more! Sadly, I am currently the only maintainer left
on the project, so I am busy trying to implement new refactorings and
finish off my thesis.

 Is anyone actively using refactoring? When using C#, I used Resharper a lot,
 and ever since, I'm really hooked to refactoring, so I miss it a lot when
 doing Haskelling. (I never seem to get a function name or signature right
 the first time. is it just me? J)

The greatest problem that the HaRe group have experienced is that HaRe
supports Haskell 98. While this is the perfect model for academic
investigation and Haskell tool design, most of the real world use the de
facto standard of GHC haskell. We would really like HaRe to be ported over to 
GHC at some point
in the near future.

 I'm currently using Emacs with Haskell Mode (which does not offer
 refactoring support) but I think many of you use VIM (which does support
 it?)
 Can one use refactoring outside of an editor? This does not really sound
 practical,  but maybe it works?

HaRe works with both Emacs and VIM; you can also use it from a command
prompt meaning that it can be integrated into any tool that you require.
Indeed, there was even some investigation of porting it to Sub Etha Edit
with great success!

 PS: IMHO I don't think text should be the source format of our files. I
 think we should use a standarized decorated AST as the source, from which we
 can derive a textual (but also graphical) view and editor. Any comments on
 that? J

You mean a syntax-directed editor, right?

Kind regards,
Chris.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN / CFP - LLVM bindings for Haskell

2008-01-03 Thread Bryan O'Sullivan
Don Stewart wrote:

 (Hackage can't host code that uses GHC 6.8.2's language extension names
 yet.)
 
 {-# LANGUAGE XYZ #-} pragmas? If so, I'm pretty sure they're 
 supported, since xmonad uses them, and is on hackage.

Language pragmas in general are fine, but I believe I'm using a few that
are new to Cabal 1.2.3.0, which isn't being used to power Hackage yet.
Or thus quoth Duncan.

b
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Refactoring status

2008-01-03 Thread Neil Mitchell
Hi

 PS: IMHO I don't think text should be the source format of our files… I
 think we should use a standarized decorated AST as the source, from which we
 can derive a textual (but also graphical) view and editor… Any comments on
 that? J

Yes - I think you're wrong. I've seen non-textual editors for
programming languages, and they are severely unpleasant for all but
the most new beginners and restricted tasks.

There is a good chance that you can derive graphical views of source
code (call flow graphs, module dependencies etc) which perhaps could
be used to modify one particular sort of information in the code.
Other than that, I'd say text is going to remain the way forward.

Thanks

Neil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN / CFP - LLVM bindings for Haskell

2008-01-03 Thread Don Stewart
bos:
 Don Stewart wrote:
 
  (Hackage can't host code that uses GHC 6.8.2's language extension names
  yet.)
  
  {-# LANGUAGE XYZ #-} pragmas? If so, I'm pretty sure they're 
  supported, since xmonad uses them, and is on hackage.
 
 Language pragmas in general are fine, but I believe I'm using a few that
 are new to Cabal 1.2.3.0, which isn't being used to power Hackage yet.
 Or thus quoth Duncan.
 
Ah yes, good point! 

There are some that can't be placed in the .cabal file -- though they
can go in the .hs file (with -fglasgow-exts in the .cabal as needed).

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN / CFP - LLVM bindings for Haskell

2008-01-03 Thread Don Stewart
bos:
 This is an early release of Haskell bindings for the popular LLVM
 compiler infrastructure project.
 
 If you don't know what LLVM is, it's a wonderful toybox of compiler
 components, from a complete toolchain supporting multiple architectures
 through a set of well-defined APIs and IR formats that are designed for
 building interesting software with.
 
 The official LLVM home page is here:
 
   http://llvm.org/
 
 The Haskell bindings are based on Gordon Henriksen's C bindings.  The C
 bindings are almost untyped, but the Haskell bindings re-add type safety
 to prevent runtime crashes and general badness.
 
 Currently, the entire code generation system is implemented, with most
 LLVM data types supported (notably absent are structs).  Also plugged in
 is JIT support, so you can generate code at runtime from Haskell and run
 it immediately.  I've attached an example.
 
 Please join in the hacking fun!
 
   darcs get http://darcs.serpentine.com/llvm
 
 If you want a source tarball, fetch it from here:
 
   http://darcs.serpentine.com/llvm/llvm-0.0.2.tar.gz

Woot. More codegen fun!

 (Hackage can't host code that uses GHC 6.8.2's language extension names
 yet.)

{-# LANGUAGE XYZ #-} pragmas? If so, I'm pretty sure they're 
supported, since xmonad uses them, and is on hackage.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[6]: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Bulat Ziganshin
Hello Mark,

Thursday, January 3, 2008, 6:40:13 PM, you wrote:

it would be hard to understand overlap without knowing both systems.
you will believe that you understand it, but things will go strange
ways :)

 I do not necessarily disagree

 But if I can identify the overlapthen I have leant the overlap...on
 the cheap.
  
 -Original Message-
 From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
 Sent: 03 January 2008 14:39
 To: Nicholls, Mark
 Cc: Bulat Ziganshin; haskell-cafe@haskell.org
 Subject: Re[4]: [Haskell-cafe] Is there anyone out there who can
 translate C# generics into Haskell?

 Hello Mark,

 Thursday, January 3, 2008, 2:13:08 PM, you wrote:

 of course *some* overlap exists but in order to understand it you
 should know exact shape of both methods

 when i tried to develop complex library without understanding t.c.
 implementation, i constantly goes into the troubles - things that i
 (using my OOP experience) considered as possible, was really
 impossible in Haskell

 so i'm really wonder why you don't want to learn the topic thoroughly


 I loosely do understandbut very looselybut I'm not, as yet,
 convinced it is completely relevant.

 The implementation may differ, but that does not mean that there is no
 overlapI am not expecting one model to be a superset of the other,
 but I am expecting some sort of overlap between 'interface'
 implementation and type class instance declaration.


 -Original Message-
 From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
 Sent: 03 January 2008 10:54
 To: Nicholls, Mark
 Cc: Bulat Ziganshin; haskell-cafe@haskell.org
 Subject: Re[2]: [Haskell-cafe] Is there anyone out there who can
 translate C# generics into Haskell?

 Hello Mark,

 Thursday, January 3, 2008, 1:22:26 PM, you wrote:

 because they have different models. i recommend you to start from
 learning this model, otherwise you will don't understand how Haskell
 really works and erroneously apply your OOP knowledge to Haskell data
 structures.

 shortly said, there are 3 ways to polymorphism:

 1) C++ templates - type-specific code generated at compile time
 2) OOP classes - every object carries VMT which allows to select
 type-specific operation
 3) type classes - dictionary of type-specific operations is given as
 additional hidden argument to each function

 Haskell uses t.c. and its abilities are dictated by this
 implementation. there is no simple and direct mapping between
 features provided by OOP and t.c.


 Can you give me a summary of why it's meaningless.both would seem
 to
 describe/construct values/objectsthey may not be equivalent, but
 I
 would expect some considerable overlap.

 -Original Message-
 From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
 Sent: 02 January 2008 20:29
 To: Nicholls, Mark
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] Is there anyone out there who can
 translate
 C# generics into Haskell?

 Hello Mark,

 Wednesday, January 2, 2008, 7:40:31 PM, you wrote:

 I'm trying to translate some standard C# constucts into Haskell...
 some

 it's meaningless. read
 http://haskell.org/haskellwiki/OOP_vs_type_classes
 and especially papers mentioned in the References










-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread Peter Verswyvelen
 HaRe works with both Emacs and VIM; you can also use it from a command
 prompt meaning that it can be integrated into any tool that you require.
 Indeed, there was even some investigation of porting it to Sub Etha Edit
 with great success!

Cool! I'll check it out. However, I'm using some GHC extensions, so that is
indeed a show stopper :)

 You mean a syntax-directed editor, right?

Yes, but also that a compiler should directly read the syntax tree; the
frontend part of the compiler should really be the editor, providing
round-trip editing between text - AST. Nothing new really, I used to work
with a 6502 assembler on the Commodore 64 that did exactly that :)

Cheers,
Peter

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread C.M.Brown
 Cool! I'll check it out. However, I'm using some GHC extensions, so that
is
 indeed a show stopper :)

Which extensions are you using that are not Haskell 98? I would be very
interested to know what users would generally require from a refactorer.

  You mean a syntax-directed editor, right?

 Yes, but also that a compiler should directly read the syntax tree; the
 frontend part of the compiler should really be the editor, providing
 round-trip editing between text - AST. Nothing new really, I used to
work
 with a 6502 assembler on the Commodore 64 that did exactly that :)

I agree with Neil, AST editors are generally ugly and hard to use. There
is also the problem of laying out Haskell code. Everyone uses their own
layout style and pretty printing ASTs is generally a bad thing to do in
this context.

Cheers,
Chris.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Refactoring status

2008-01-03 Thread Bulat Ziganshin
Hello Neil,

Thursday, January 3, 2008, 9:57:10 PM, you wrote:

 Yes - I think you're wrong. I've seen non-textual editors for
 programming languages, and they are severely unpleasant for all but
 the most new beginners and restricted tasks.

what sort of code you are tried to develop? visual designers are
successfully used for GUI design (not surprising) and SQL

pure parts of my haskell program is just functions which takes some
input (as arguments) and produce some output (as result). these
functions are built from other functions and i don't see why it should
be bad to represent this graphically instead of textually. moreover,
Haskell is known as hard-to-read language (at least for beginners)
due to its great power of function composition, and graphical
representation of complex expressions may make easier their understanding


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread Peter Verswyvelen
 Yes - I think you're wrong. I've seen non-textual editors for
 programming languages, and they are severely unpleasant for all but
 the most new beginners and restricted tasks.

For programmers and mathematicians, you are absolutely right. For beginners
and people who have highly developed visual skills (like computer graphic
artists), I'm afraid you are wrong. Most of the latter would never even try
to look at something like Haskell, while many of them are actually using a
(subset of) a dataflow or functional language (Apple's Shake, SideFX
Houdini, Digital Fusion, the Unreal 3 Game Engine, the Spirops AI system,
just to name a few). Most of these application also provide a textual
interface, but artists mostly prefer the graphical view.

 There is a good chance that you can derive graphical views of source
 code (call flow graphs, module dependencies etc) which perhaps could
 be used to modify one particular sort of information in the code.
 Other than that, I'd say text is going to remain the way forward.

But now everybody is developing their own parsers and structured data
representation for Haskell tools no, because text is the standard? 

Cheers,
Peter



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread Peter Verswyvelen
 I agree with Neil, AST editors are generally ugly and hard to use. There
 is also the problem of laying out Haskell code. Everyone uses their own
 layout style and pretty printing ASTs is generally a bad thing to do in
 this context.

I actually meant something more like
http://en.wikipedia.org/wiki/Intentional_programming

Cheers,
Peter


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Refactoring status

2008-01-03 Thread Bulat Ziganshin
Hello Peter,

Thursday, January 3, 2008, 9:13:27 PM, you wrote:

well, i use refactoring without help of any tool. according to my
own experience, it's much easier in Haskell than in other languages i
know - basically, you just cut-n-paste your code around. i don't use
type signatures at all - this creates some problems when i wrote large
portion of code and try to make it compile, but nothing more

 
   
   
 Hi all,
   
  
   
 Is any work being done on Haskell refactoring support, like HaRe or others?
   
  
   
 Is anyone actively using refactoring? When using C#, I used
 Resharper a lot, and ever since, I▓m really hooked to refactoring,
 so I miss it a lot when doing Haskelling. (I never seem to get a
 function name or signature right the first time┘ is it just me? J)
   
  
   
 I▓m currently using Emacs with Haskell Mode (which does not offer
 refactoring support) but I think many of you use VIM (which does support it?)
   
  
   
 Can one use refactoring outside of an editor? This does not really
 sound practical,  but maybe it works?
   
  
   
 Thank you,
   
 Peter
   
  
   
 PS: IMHO I don▓t think text should be the source format of our
 files┘ I think we should use a standarized decorated AST as the
 source, from which we can derive a textual (but also graphical) view
 and editor┘ Any comments on that? J
   
  
   
  
   
  
   
  
   

  
  
   
  
   
   
 


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Refactoring status

2008-01-03 Thread C.M.Brown
Hi Bulat,

 i don't use
 type signatures at all - this creates some problems when i wrote large
 portion of code and try to make it compile, but nothing more

I believe type signatures are the very essence of Haskell documentation!
I'd much rather see a program with type signatures for functions and
little (or no) comments over programs with no type signatures and
ambigious comments (if any comments at all!).

Type signatures really does make dealing with someone elses code that
much easier.

Regards,
Chris.


 
 
 
  Hi all,
 
   
 
  Is any work being done on Haskell refactoring support, like HaRe or others?
 
   
 
  Is anyone actively using refactoring? When using C#, I used
  Resharper a lot, and ever since, I▓m really hooked to refactoring,
  so I miss it a lot when doing Haskelling. (I never seem to get a
  function name or signature right the first time┘ is it just me? J)
 
   
 
  I▓m currently using Emacs with Haskell Mode (which does not offer
  refactoring support) but I think many of you use VIM (which does support 
  it?)
 
   
 
  Can one use refactoring outside of an editor? This does not really
  sound practical,  but maybe it works?
 
   
 
  Thank you,
 
  Peter
 
   
 
  PS: IMHO I don▓t think text should be the source format of our
  files┘ I think we should use a standarized decorated AST as the
  source, from which we can derive a textual (but also graphical) view
  and editor┘ Any comments on that? J
 
   
 
   
 
   
 
   
 

 
 
 
   
 
 
 



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] haskell package installation problem

2008-01-03 Thread Brian Park
Hi,

I was installing various haskell packages from hackage.

When I was installing HaXml, I think it was complaining about
Text.PrettyPrint.HughesPJ not installed or something. (can't remember the
specific message and I can't reproduce now...)

So I installed pretty-1.0.0.0 package as well.

Ever since then, when I try to install other haskell packages, I get the
following error message:
[EMAIL PROTECTED]:~/Download/mtl-1.1.0.0$ runghc Setup.hs configure
interactive: /usr/local/lib/ghc-6.8.2/lib/Cabal-1.2.3.0/HSCabal-1.2.3.0.o:
unknown symbol
`prettyzm1zi0zi0zi0_TextziPrettyPrintziHughesPJ_lvl18_closure'
ghc-6.8.2: unable to load package `Cabal-1.2.3.0'

Does anyone know what the problem is?

Currently installed packages are:
=
/usr/local/lib/ghc-6.8.2/package.conf:
Cabal-1.2.3.0, HTTP-3001.0.4, HUnit-1.2.0.0, X11-1.4.1,
array-0.1.0.0, base-3.0.1.0, bytestring-0.9.0.1,
containers-0.1.0.1, directory-1.0.0.0, filepath-1.1.0.0,
(ghc-6.8.2), haskell98-1.0.1.0, hpc-0.5.0.0, hxt-7.4, mtl-1.1.0.0,
network-2.1.0.0, old-locale-1.0.0.0, old-time-1.0.0.0,
packedstring-0.1.0.0, parsec-2.1.0.0, polyparse-1.1,
pretty-1.0.0.0, process-1.0.0.0, random-1.0.0.0, readline-1.0.1.0,
rts-1.0, template-haskell-2.2.0.0, unix-2.3.0.0, xmonad-0.5,
xmonad-contrib-0.5
=


Thank you,

- Brian
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fusion of lists and chunky sequences

2008-01-03 Thread Don Stewart
lemming:
 
 On the one hand I like to use lists in my code because element types can
 be freely chosen and maximum laziness allows feedback and other tricks. On
 the other hand there are ByteString.Lazy and one could build chunky
 sequences from other fast array implementations. They have constraints on
 the element types like Storable in
   http://code.haskell.org/~sjanssen/storablevector
  and IArray multi-parameter type class for UArray.
 
  I like to continue writing code for lists, and let the optimizer replace
 it by operations on chunky sequences whereever possible. E.g.
   Chunky.fromList (List.map f (List.unfoldr g x))
  might be transformed to
   Chunky.unfoldr (f ... g) x
 
 Chunky.fromList serves two purposes:
  1. I obtain the result in a data structure that can be quickly accessed
 by further operations.
  2. It tells the optimizer that element granularity for laziness is not
 needed and that the element type fulfills the constraint of the fast array
 type, and thus fusion can go on safely. (As far as I can see.)
 
  Is there some framework which fuses lists and chunky sequences? When
 writing fusion rules like the above one by myself, then they interfer with
 Prelude's fusion rules (and they would probably also interfer with those
 of an alternative list fusion framework). The 'map' and 'unfoldr' is
 certainly already fused to the internal 'build' or to another auxiliary
 function. As far as I know, I cannot disable the Prelude rules and give
 the List-Chunk rules priority higher than Prelude's ones.

You can, with some caveats, use a single fusion system across data
structures, and avoid the built in build/foldr system.

I'd start by installing the stream-fusion list library, from hackage,
which gives you the list api, and a fusion mechanism.

To avoid the build in fusion system, you need to:

* avoid list comprehensions
* avoid .. (use Stream.enumFromTo instead)

then you can write fusion rules for your structure in terms of streams,
and they'll fuse with list operations as well.

Duncan, Roman and I plan to have strict and lazy bytestrings fusing
on top of the stream-fusion package in Q1 this year, but you can start
now looking at other data structures.

  I hoped to be able to apply application specific fusion rules by defining
 a newtype wrapper around the chunky sequence type, while keeping the rest
 of the list code unchanged. You might argue, that code cannot be
 application specific if it still relies on the generic list type. Maybe
 it's the best to wrap the list type in a newtype and lift all of the
 application relevant list functions to this type and then define fusion
 rules on the lifted functions.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread C.M.Brown
 Currently, I'm trying to learn arrows and Yampa (mainly to see how well it
 compares to my own dataflow/reactive stuff that was written in C#, C++ and
 assembler)

Arrows won't work with HaRe at the moment, therefore Yampa won't either;
which is a shame.

 First of all, let's see if I get the concept of a syntax directed editor
 right. The idea is, that I (or my company), has a specific indentation rule,
 naming convention rule, etc... When I get code from someone else (in a
 syntax tree form ala XML), it will immediately show the text using my
 conventions.

Yep, this was what I was thinking to some extent.

Furthermore, when I need to perform refactoring, a rename is
 just *one* change to the entire system, no matter how many other files use
 the name; no more merging for stupid renames.

I'm a little confused as to what you mean here. A renaming renames all
(and only those) uses of an identifier within a particular definition, and
not every use of a particular name. The binding structure of the program
must not be affected; and there must be no introduction of ambiguity in
the namespace. You can do this with HaRe, but HaRe currently refactors
Programatica data types. If you can
somehow convert your AST into what HaRe expects then the refactoring will
work, but you will need to tweak our pretty printer (and turn off layout
preservation).

When diffing, whitespace,
 indentation, etc does not matter; the structure of the files is compared
 instead.

There is also (preliminary at the moment) duplicate code detection built
into HaRe. This is based on the principle of looking at the shape of functions 
and
expressions, concentrating on where variables are bound and whether one
term is an intance of another. Duplicate expressions can be converted into
a more general abstraction, transforming the duplicate expressions into
function calls (parameterised by their differences).

Cheers,
Chris.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread C.M.Brown
 Furthermore, IMHO, type signatures alone are not enough, a good parameter
 name says at least as much as the type.

Yes! A very good point! :)


 E.g. what does a function Int - Int - Bool do? I have no idea. A good
 function name helps, e.g. isDivisible:: Int - Int - Bool. But then I still
 don't know which parameter is the numerator and denominator. So good names
 for the parameters are at least as important, e.g. isDivisible ::
 numerator:Int - denonimator:Int - Bool


I agree. But I was generally thinking of more complex functions than this,
especially if they use some kind of user-defined monad and have implicit
parameters, say.

Cheers,
Chris.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread Peter Verswyvelen
 I believe type signatures are the very essence of Haskell documentation!
 I'd much rather see a program with type signatures for functions and
 little (or no) comments over programs with no type signatures and
 ambigious comments (if any comments at all!).

Okay, but when using a syntax directed editor, type signatures can be
automatically provided because the types are known. 

Furthermore, IMHO, type signatures alone are not enough, a good parameter
name says at least as much as the type. 

E.g. what does a function Int - Int - Bool do? I have no idea. A good
function name helps, e.g. isDivisible:: Int - Int - Bool. But then I still
don't know which parameter is the numerator and denominator. So good names
for the parameters are at least as important, e.g. isDivisible ::
numerator:Int - denonimator:Int - Bool

 Type signatures really does make dealing with someone elses code that
 much easier.

Yes, as is good documentation, which unfortunately is still limited to
ASCII. I would prefer to have rich documentation right inside my source
code, with math symbols, drawings, pictures, animations, whatever... 

Cheers,
Peter


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is there anyone out there who can translate C# generics into Haskell?

2008-01-03 Thread Ketil Malde
Peter Verswyvelen [EMAIL PROTECTED] writes:

 Well, it's a good habit in Haskell to move the most important parameter to
 the end of the argument list. See e.g.
 http://www.haskell.org/haskellwiki/Parameter_order. 

I must say I like these recommendations.  As for the Data.Map examples,
the parameter order was changed compared to the old FiniteMap, and I
was sure there was some rationale given?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread Peter Verswyvelen
 Furthermore, when I need to perform refactoring, a rename is
  just *one* change to the entire system, no matter how many other files
use
  the name; no more merging for stupid renames.
 I'm a little confused as to what you mean here. A renaming renames all
 (and only those) uses of an identifier within a particular definition, and
 not every use of a particular name. The binding structure of the program

Suppose we have a file Foo.hs, with the content:

foo ::Int
foo = 42

Translated into a syntax tree, this might look like (majorly simplified)

Definition id=68684 name=foo
Constant value=42 type=Int/
/Definition

and a file Bar.hs, with

bar :: Int
bar = foo + 27

or translated

Definition id=577647 name=bar
Add
 Reference id=68684/
   Constant value=27 type=Int/
/Add
/Definition

If you rename foo, using textual representation, both Foo.hs and Bar.hs will
be touched / checked-out.

However, if you work directly on the structure, then only the Foo XML file
is changed, Bar is not changed at all.

Of course this might only be the case with renames, more complex
refactorings usually require modifying other files :) 

Anyway, I hate merges caused by renames by others. And many developers tend
to leave names as they are, because you get used to strange names anyway...
A good example is Microsoft's Windows Presentation Foundation code: what do
you think the method FindName on an element tree does? It searches for an
element with a particular name, and returns that element ;)

 There is also (preliminary at the moment) duplicate code detection built
 into HaRe. This is based on the principle of looking at the shape of
functions and
 expressions, concentrating on where variables are bound and whether one
 term is an intance of another. Duplicate expressions can be converted into
 a more general abstraction, transforming the duplicate expressions into
 function calls (parameterised by their differences).

Impressive!

Cheers,
Peter


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Consensus about databases / serialization

2008-01-03 Thread Yitzchak Gale
I wrote:
... to control the precise SQL that is generated. In practice,
 you almost always have to do some tweaking that is
 at least DB-dependent, and often application dependent.

Peter Verswyvelen wrote:
 Can't the same be said regarding SQL itself? It sometimes needs tweaking.
 That's the problem with any high level abstraction no?

Certainly. In an ideal world, you could just write your queries
in straightforward SQL and the DB would figure out what to
do. But in real life, that is not how it works.

So that complexity then gets passed up to the Haskell
interface layers. Again, in an ideal world you would like to
imagine that a high-level interface like haskelldb would
be smart enough to compile any relational algebraic
expression into SQL that will do the Right Thing for the
given backend.

But that would be very difficult. For example - there may
be things you need to tweak that are both
application-dependent and DB dependent.

So to be usable in a serious DB project, there
would have to be some kind of hooks that would allow
you to tweak the SQL. After doing that - what have we
gained by taking the high-level approach to begin with?
I'm not sure.

I would like to hear about people's thoughts and experiences
on this.

-Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Consensus about databases / serialization

2008-01-03 Thread Yitzchak Gale
Lihn, Steve wrote:
 For small queries, it does not matter much which approach you choose.
 But for large, complex queries, such 3-table join (especial Star
 Transformation) and/or large data set (millions of rows involved in
 large data warehouses), the performance will differ by order of
 magnitude, depending on how things are optimized.

Ah, yes. and that brings up another issue - how do the various
backends scale for:

- large SQL passed in
- results with many records
- records with many fields
- records/fields with many bytes
- several cursors

What laziness options are available?

-Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Supporting both cabals?

2008-01-03 Thread Judah Jacobson
On Jan 3, 2008 4:26 PM, Magnus Therning [EMAIL PROTECTED] wrote:
 GHC 6.8 has just made it into Debian in a usable form.  (w00t!)

 Due to the library split my old cabal files don't work any longer.
 updating them isn't the problem, the problem is keeping them compatible
 with both versions of Cabal.  I searched the wiki (quickly) but didn't
 find anything on this topic.  Is there a cookbook out there for it?

The standard fix is to use Cabal configurations:
http://www.haskell.org/haskellwiki/Upgrading_packages

Best,
-Judah
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] US Homeland Security program language security risks

2008-01-03 Thread Galchin Vasili
Hello,

https://buildsecurityin.us-cert.gov/daisy/bsi/articles/knowledge/coding/295.html

I stumbled across this page. It seems that Haskell and other strongly typed
functional languages like Ml/OCaml will fare much, much better, e.g. buffer
overrun. Thoughts .  comments.

Vasili
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] An interesting monad: Prompt

2008-01-03 Thread Felipe Lessa
On Nov 18, 2007 10:22 PM, Ryan Ingram [EMAIL PROTECTED] wrote:
[snip]
  data Prompt (p :: * - *) :: (* - *) where
  PromptDone :: result - Prompt p result
  -- a is the type needed to continue the computation
  Prompt :: p a - (a - Prompt p result) - Prompt p result
[snip]
  runPromptM :: Monad m = (forall a. p a - m a) - Prompt p r - m r
  runPromptM _ (PromptDone r) = return r
  runPromptM f (Prompt pa c)  = f pa = runPromptM f . c
[snip]

How can we prove that (runPromptM prompt === id)? I was trying to go with

runPromptM prompt (PromptDone r)
 = return r
 = PromptDone r

runPromptM prompt (Prompt pa c)
 = prompt pa = runPromptM prompt . c
 = Prompt pa return = runPromptM prompt . c
 = Prompt pa ((= (runPromptM prompt . c) . return)
 = Prompt pa (runPromptM prompt . c)

... and I got stuck here. It seems obvious that we can strip out the
'runPromptM prompt' down there to finish the proof, but that doesn't
sound very nice, as I'd need to suppose what I'm trying to prove. Am I
missing something here?

Thank you,

-- 
Felipe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Difference lists and ShowS

2008-01-03 Thread Albert Y. C. Lai

apfelmus wrote:
I don't know a formalism for easy reasoning about time in a lazy 
language. Anyone any pointers? Note that the problem is already present 
for difference lists in strict languages.


http://homepages.inf.ed.ac.uk/wadler/topics/strictness-analysis.html

especially strictness analysis aids time analysis.

Much CPO math is involved, but I view it as: a function gives you 
output; if you know how much of the output you use, you can deduce how 
much work the function goes through.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Instance classes and error (also, related to Data.Binary.GET)

2008-01-03 Thread bbrown
I am using the Data.Binary module and having some issues reading big endian
files (actually, just reading the file).  I can read the header but not the
rest of the data which contains a set of row information.  Also, go ahead and
make fun my style of coding.

Anyway, This is the my code and the error at the bottom.


The issue stems from here, it says I didn't define an instance, but I did:

instance Binary URLSet where
put _ = do BinaryPut.putWord8 0
get = do
  remainingByteData - BinaryGet.getRemainingLazyByteString
  i :: URLInfo - decode remainingByteData
  j :: TitleInfo - decode remainingByteData
  k :: DescrInfo - decode remainingByteData
  x :: KeywordsInfo - decode remainingByteData
  return (URLSet {urlinfo=i, titleinfo=j, 
  descrinfo=k, keywordsinfo=x})

-

module Main where

import Data.Word
import Data.Binary
import qualified Data.ByteString.Lazy.Char8 as BSLC8
import Data.ByteString.Lazy (ByteString)
import Data.Binary.Get as BinaryGet
import Data.Binary.Put as BinaryPut
import IO
import Text.Printf
import System.Environment
import Control.Monad (replicateM, liftM)

{- *
 Define the Database Data Types
 SpiderDatabase represents a singleton wrapper for an
 entire database.
   * -}
data SpiderDatabase =  SpiderDatabase { 
  magicNumberA :: Word16,
  magicNumberB :: Word16,
  majorVers :: Word16,
  minorVers :: Word16,
  headerTag :: Word16,
  poolLen :: Word16,
  spiderpool :: [URLSet]
}
data URLSet = URLSet {
  urlinfo :: URLInfo,
  titleinfo :: TitleInfo,
  descrinfo :: DescrInfo,
  keywordsinfo :: KeywordsInfo
}
data URLInfo = URLInfo {
  tag :: Word8,
  urlid :: Word16,
  urllen :: Word16,
  url :: ByteString
}
data TitleInfo = TitleInfo {
  titletag :: Word8,  
  titlelen :: Word16,
  title :: ByteString
}
data DescrInfo = DescrInfo {
  descrtag :: Word8,  
  descrlen :: Word16,
  descr :: ByteString
}
data KeywordsInfo = KeywordsInfo {
  keywordstag :: Word8,  
  keywordslen :: Word16,
  keywords :: ByteString
}
{- *
 Class instances
   * -}
instance Show SpiderDatabase where
show db = let magicb = (magicNumberB db)
  header = (headerTag db)
  poolct = (poolLen db)
  in Database Content\n ++
 (((printf Magic: %X %X\n) (magicNumberA db)) (magicNumberB
db)) ++
 printf URL Pool Count: %d\n poolct ++
 End

instance Binary URLInfo where
put _ = do BinaryPut.putWord8 0
get = do
  urltag - getWord8
  idx - getWord16be
  len - getWord16be
  strdata - BinaryGet.getLazyByteString (fromIntegral len)
  return (URLInfo {tag=urltag, urlid=idx, 
   urllen=len, url=strdata})
instance Binary DescrInfo where
put _ = do BinaryPut.putWord8 0
get = do
  tag - getWord8
  len - getWord16be
  strdata - BinaryGet.getLazyByteString (fromIntegral len)
  return (DescrInfo {descrtag=tag,
 descrlen=len, 
 descr=strdata})
instance Binary TitleInfo where
put _ = do BinaryPut.putWord8 0
get = do
  tag - getWord8
  len - getWord16be
  strdata - BinaryGet.getLazyByteString (fromIntegral len)
  return (TitleInfo {titletag=tag,
 titlelen=len, 
 title=strdata})
instance Binary KeywordsInfo where
put _ = do BinaryPut.putWord8 0
get = do
  tag - getWord8
  len - getWord16be
  strdata - BinaryGet.getLazyByteString (fromIntegral len)
  return (KeywordsInfo {keywordstag=tag,
keywordslen=len, 
keywords=strdata})
instance Binary URLSet where
put _ = do BinaryPut.putWord8 0
get = do
  remainingByteData - BinaryGet.getRemainingLazyByteString
  i :: URLInfo - decode remainingByteData
  j :: TitleInfo - decode remainingByteData
  k :: DescrInfo - decode remainingByteData
  x :: KeywordsInfo - decode remainingByteData
  return (URLSet {urlinfo=i, titleinfo=j, 
  descrinfo=k, keywordsinfo=x})
  
instance Binary SpiderDatabase where
put _ = do BinaryPut.putWord8 0
get = do 
  magicnumbera - BinaryGet.getWord16be
  magicnumberb - BinaryGet.getWord16be
  major - BinaryGet.getWord16be
  minor - BinaryGet.getWord16be
  header - BinaryGet.getWord16be
  poolct - BinaryGet.getWord16be
  -- ***
  -- Get the remaining byte string data,
  -- So that we can use lazy bytestring to load to load the
  -- the data types.
  -- ***

Re[2]: [Haskell-cafe] Refactoring status

2008-01-03 Thread Bulat Ziganshin
Hello C.M.Brown,

Thursday, January 3, 2008, 10:46:54 PM, you wrote:

 i don't use
 type signatures at all - this creates some problems when i wrote large
 portion of code and try to make it compile, but nothing more

 I believe type signatures are the very essence of Haskell documentation!
 I'd much rather see a program with type signatures for functions and
 little (or no) comments over programs with no type signatures and
 ambigious comments (if any comments at all!).

 Type signatures really does make dealing with someone elses code that
 much easier.

well, i don't worry about types of things with which i work. i know
that it is a file, for example. its actual type depends on the
information i need inside this function. it may start as FileInfo type,
then after refactoring it will become CompressedFile or
(fileInfo,FileSize) type. while it's great to know types of every
variable to better understand how program works, adding type
signatures means more work when writing program and when changing it.
i want to express only data processing algorithm leaving all the
details to compiler. for me, ghc just reads thoughts

types and type signatures was required in classic languages to fight
with errors. but in haskell omitting type signatures doesn't make
program less reliable, so i don't need to write this extra code in
addition to the essential - algorithm itself. for the same reason, i
like pointless notation

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Instance classes and error (also, related to Data.Binary.GET)

2008-01-03 Thread Daniel Fischer
I've no experience with Data.Binary, but I noticed you declared

instance Binary YourType where...

and the compiler says

instance Binary (Get YourType)

is missing. That might be worth looking into.
Cheers,
Daniel

Am Freitag, 4. Januar 2008 00:13 schrieb bbrown:
 I am using the Data.Binary module and having some issues reading big endian
 files (actually, just reading the file).  I can read the header but not the
 rest of the data which contains a set of row information.  Also, go ahead
 and make fun my style of coding.

 Anyway, This is the my code and the error at the bottom.


 The issue stems from here, it says I didn't define an instance, but I did:

 instance Binary URLSet where
 put _ = do BinaryPut.putWord8 0
 get = do
   remainingByteData - BinaryGet.getRemainingLazyByteString
   i :: URLInfo - decode remainingByteData
   j :: TitleInfo - decode remainingByteData
   k :: DescrInfo - decode remainingByteData
   x :: KeywordsInfo - decode remainingByteData
   return (URLSet {urlinfo=i, titleinfo=j,
   descrinfo=k, keywordsinfo=x})

 -

 module Main where

 import Data.Word
 import Data.Binary
 import qualified Data.ByteString.Lazy.Char8 as BSLC8
 import Data.ByteString.Lazy (ByteString)
 import Data.Binary.Get as BinaryGet
 import Data.Binary.Put as BinaryPut
 import IO
 import Text.Printf
 import System.Environment
 import Control.Monad (replicateM, liftM)

 {- *
  Define the Database Data Types
  SpiderDatabase represents a singleton wrapper for an
  entire database.
* -}
 data SpiderDatabase =  SpiderDatabase {
   magicNumberA :: Word16,
   magicNumberB :: Word16,
   majorVers :: Word16,
   minorVers :: Word16,
   headerTag :: Word16,
   poolLen :: Word16,
   spiderpool :: [URLSet]
 }
 data URLSet = URLSet {
   urlinfo :: URLInfo,
   titleinfo :: TitleInfo,
   descrinfo :: DescrInfo,
   keywordsinfo :: KeywordsInfo
 }
 data URLInfo = URLInfo {
   tag :: Word8,
   urlid :: Word16,
   urllen :: Word16,
   url :: ByteString
 }
 data TitleInfo = TitleInfo {
   titletag :: Word8,
   titlelen :: Word16,
   title :: ByteString
 }
 data DescrInfo = DescrInfo {
   descrtag :: Word8,
   descrlen :: Word16,
   descr :: ByteString
 }
 data KeywordsInfo = KeywordsInfo {
   keywordstag :: Word8,
   keywordslen :: Word16,
   keywords :: ByteString
 }
 {- *
  Class instances
* -}
 instance Show SpiderDatabase where
 show db = let magicb = (magicNumberB db)
   header = (headerTag db)
   poolct = (poolLen db)
   in Database Content\n ++
  (((printf Magic: %X %X\n) (magicNumberA db))
 (magicNumberB db)) ++
  printf URL Pool Count: %d\n poolct ++
  End

 instance Binary URLInfo where
 put _ = do BinaryPut.putWord8 0
 get = do
   urltag - getWord8
   idx - getWord16be
   len - getWord16be
   strdata - BinaryGet.getLazyByteString (fromIntegral len)
   return (URLInfo {tag=urltag, urlid=idx,
urllen=len, url=strdata})
 instance Binary DescrInfo where
 put _ = do BinaryPut.putWord8 0
 get = do
   tag - getWord8
   len - getWord16be
   strdata - BinaryGet.getLazyByteString (fromIntegral len)
   return (DescrInfo {descrtag=tag,
  descrlen=len,
  descr=strdata})
 instance Binary TitleInfo where
 put _ = do BinaryPut.putWord8 0
 get = do
   tag - getWord8
   len - getWord16be
   strdata - BinaryGet.getLazyByteString (fromIntegral len)
   return (TitleInfo {titletag=tag,
  titlelen=len,
  title=strdata})
 instance Binary KeywordsInfo where
 put _ = do BinaryPut.putWord8 0
 get = do
   tag - getWord8
   len - getWord16be
   strdata - BinaryGet.getLazyByteString (fromIntegral len)
   return (KeywordsInfo {keywordstag=tag,
 keywordslen=len,
 keywords=strdata})
 instance Binary URLSet where
 put _ = do BinaryPut.putWord8 0
 get = do
   remainingByteData - BinaryGet.getRemainingLazyByteString
   i :: URLInfo - decode remainingByteData
   j :: TitleInfo - decode remainingByteData
   k :: DescrInfo - decode remainingByteData
   x :: KeywordsInfo - decode remainingByteData
   return (URLSet {urlinfo=i, titleinfo=j,
   descrinfo=k, keywordsinfo=x})

 instance Binary SpiderDatabase where
 put _ = do BinaryPut.putWord8 0
 get = do
   magicnumbera - BinaryGet.getWord16be
   magicnumberb - 

Re: [Haskell-cafe] Refactoring status

2008-01-03 Thread hjgtuyl

On Thu, 03 Jan 2008 19:48:05 +0100, C.M.Brown [EMAIL PROTECTED] wrote:

HaRe is still very active and is due for a new release very soon.
There are probably in excess of 40 refactorings for HaRe in total now,  
and

I intend to add more! Sadly, I am currently the only maintainer left
on the project, so I am busy trying to implement new refactorings and
finish off my thesis.



A possible first goal would be, to add extensions that are definitely in  
Haskell prime, see:

  
http://hackage.haskell.org/trac/haskell-prime/wiki/Status'#definitely-inProposalStatus



HaRe works with both Emacs and VIM; you can also use it from a command
prompt meaning that it can be integrated into any tool that you require.
Indeed, there was even some investigation of porting it to Sub Etha Edit
with great success!



It would be nice to have it built in to the functional programming  
extensions of Eclipse

( http://eclipsefp.sourceforge.net/ )

--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread ajb

G'day all.

Quoting Peter Verswyvelen [EMAIL PROTECTED]:


I actually meant something more like
http://en.wikipedia.org/wiki/Intentional_programming


I'm pretty sure that Intentional programming is Hungarian for I want
to sell you another IDE.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Refactoring status

2008-01-03 Thread C.M.Brown
Hi,

 A possible first goal would be, to add extensions that are definitely in
 Haskell prime, see:

 http://hackage.haskell.org/trac/haskell-prime/wiki/Status'#definitely-inProposalStatus

Oh great! Thanks for the link, I think the main issue is moving over to a
platform that is heavily maintained (such as GHC) and then working
towards, say, haskell prime coverage as a first goal.

 It would be nice to have it built in to the functional programming
 extensions of Eclipse
 ( http://eclipsefp.sourceforge.net/ )

Yes, I actually did some work on this but due to time restrictions it was
never finished. However, it wouldn't be difficult to add HaRe to any type
of interactive environment. HaRe is called from the command prompt and
requires positional and region information from the editor together with
the facility to display a prompt and read answers.

I would love to be able to work with people who may be interested in
porting HaRe to editors such as Eclipse... :)

Cheers,
Chris.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Refactoring status

2008-01-03 Thread C.M.Brown
On Fri, 4 Jan 2008, Bulat Ziganshin wrote:

 Hello Peter,

 Thursday, January 3, 2008, 11:03:58 PM, you wrote:

  Okay, but when using a syntax directed editor, type signatures can be
  automatically provided because the types are known.

 the same is possible for Haskell - it's possible to add to code type
 signatures deduced by the compiler

Ha! Yes, HaRe also has the facility to do this have I plugged it
enough yet? :-)

Cheers,
Chris.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN / CFP - LLVM bindings for Haskell

2008-01-03 Thread Ross Paterson
On Thu, 03 Jan 2008 03:43:49 -0800, Bryan O'Sullivan wrote:
 (Hackage can't host code that uses GHC 6.8.2's language extension names
 yet.)

It should be able to now.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Instance classes and error (also, related to Data.Binary.GET)

2008-01-03 Thread Brandon S. Allbery KF8NH


On Jan 3, 2008, at 18:13 , bbrown wrote:


DbReader.hs:119:22:
No instance for (Binary (Get URLInfo))
  arising from a use of `decode' at DbReader.hs:119:22-45


Without looking more closely, this suggests to me that you have  
mismatched or incorrectly encapsulated monads (for example, treating  
a value in the Get monad as if it were pure).  This might be related  
to the way you specify the types of the values obtained from decode.


(I haven't used Data.Binary.)

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Consensus about databases / serialization

2008-01-03 Thread Brandon S. Allbery KF8NH


On Jan 3, 2008, at 16:32 , Peter Verswyvelen wrote:


I see. But ouch, exactly the same could be said for Haskell no? :)


Optimization by quasirandom insertion of bangs / seq?  Already there :)

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN / CFP - LLVM bindings for Haskell

2008-01-03 Thread Duncan Coutts
In message [EMAIL PROTECTED] Ross Paterson
[EMAIL PROTECTED] writes:
 On Thu, 03 Jan 2008 03:43:49 -0800, Bryan O'Sullivan wrote:
  (Hackage can't host code that uses GHC 6.8.2's language extension names
  yet.)
 
 It should be able to now.

Thanks very much Ross.

BTW, I think we should put some HackageDB hacking and admin instructions on the
hackage wiki so we don't have to pester you so much for this kind of routine
admin stuff.

Duncan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN / CFP - LLVM bindings for Haskell

2008-01-03 Thread Bryan O'Sullivan
Ross Paterson wrote:

 It should be able to now.

Thank you!

b
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Instance classes and error (also, related to Data.Binary.GET)

2008-01-03 Thread Clive Brettingham-Moore

Like the previous no experience with Data.Binary, but my (rusty) monad
experience is enough to see the source of the problem:
bbrown wrote:

The issue stems from here, it says I didn't define an instance, but I did:

instance Binary URLSet where
put _ = do BinaryPut.putWord8 0
get = do
  remainingByteData - BinaryGet.getRemainingLazyByteString
  i :: URLInfo - decode remainingByteData
  j :: TitleInfo - decode remainingByteData
  k :: DescrInfo - decode remainingByteData
  x :: KeywordsInfo - decode remainingByteData
  return (URLSet {urlinfo=i, titleinfo=j, 
  descrinfo=k, keywordsinfo=x})


  

Data.Binary seems to use the Get monad which looks to be a garden
variety parsing monad.

For  line in the do block:

 i :: URLInfo - decode remainingByteData


Because of the way do notation works x::a - is expecting a value of M a
for a monad M, above Get URLInfo, inplying a type of ByteString - (Get
URLInfo) for decode and therefore the comiler is looking for the
corresponding Binary instance (and of course, not finding it since,
quite properly, your binary instance is URLInfo not Get URLInfo). If you
can't follow this, find a monad tutorial and look at how do notation
expands to = and .

The code you have almost certainly isn't doing what you want/expect
(even if you fix the bad monad nesting you are trying to repeatedly
decode the same data as different types). Not knowing exactly how your
data is encoded it is hard to be certain of the correct code but
something like this seems more likely (untried):

instance Binary URLSet where
   put _ = do BinaryPut.putWord8 0
   get = do
 i :: URLInfo - get
 j :: TitleInfo - get
 k :: DescrInfo - get
 x :: KeywordsInfo - get
 return (URLSet {urlinfo=i, titleinfo=j,
 descrinfo=k, keywordsinfo=x})

This assumes that the data contains the structures serialized in order.
In this case for i the type of get is inferred to Get URLInfo - which
will work since URLInfo has a Binary instance.

You also have a similar issue in the SpiderDatabase instance.

Clive





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN / CFP - LLVM bindings for Haskell

2008-01-03 Thread Ryan Dickie
On Jan 3, 2008 3:43 AM, Bryan O'Sullivan [EMAIL PROTECTED] wrote:

 This is an early release of Haskell bindings for the popular LLVM
 compiler infrastructure project.

 If you don't know what LLVM is, it's a wonderful toybox of compiler
 components, from a complete toolchain supporting multiple architectures
 through a set of well-defined APIs and IR formats that are designed for
 building interesting software with.

 The official LLVM home page is here:

  http://llvm.org/

 The Haskell bindings are based on Gordon Henriksen's C bindings.  The C
 bindings are almost untyped, but the Haskell bindings re-add type safety
 to prevent runtime crashes and general badness.

 Currently, the entire code generation system is implemented, with most
 LLVM data types supported (notably absent are structs).  Also plugged in
 is JIT support, so you can generate code at runtime from Haskell and run
 it immediately.  I've attached an example.

 Please join in the hacking fun!

  darcs get http://darcs.serpentine.com/llvm

 If you want a source tarball, fetch it from here:

  http://darcs.serpentine.com/llvm/llvm-0.0.2.tar.gz

 (Hackage can't host code that uses GHC 6.8.2's language extension names
 yet.)

 There's very light documentation at present, but it ought to be enough
 to get you going.

b

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


Maybe I am asking an uninformed n00b question but how come GHC has fvia-C
and are also working on an asm backend. Is there any reason why they could
not build off the work of LLVM (which supports various architectures) then
ditch those two backends and call it a day?

--ryan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe