[Haskell-cafe] Re: Red-black trees as a nested datatype

2006-12-28 Thread Jim Apple

Correction:

type RedBlackTree a =
   Tree a
   -- A red tree with two levels of black nodes is just a red node on
   -- top of two two-level black nodes.
   (Node a (Black2 a)) (Black2 a) a ()


type RedBlackTree a =
Tree a
-- A red tree with two levels of black nodes is just a red node on
-- top of two black nodes.
(Node (Black2 a) a) (Black2 a) a ()

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


Re: [Haskell-cafe] Is there a printable copy of the (GHC) library references anywhere?

2006-12-28 Thread Paul Moore

On 12/27/06, Neil Mitchell [EMAIL PROTECTED] wrote:

Only a few of the standard libraries are useful unless you are doing
something specific. i.e. Data.Maybe is generally useful, but
Control.Monad.State is only useful if you are using a state monad.


Hmm, I'm not sure I agree with you here. Yes, a lot of the libraries
are fairly specialised, but the problem is when you find you need a
specialised library, how do you know it exists in the standard
library? That's where something like the Haddock documentation is less
useful, as it's library-oriented rather than task-oriented.

For example (not a wonderful example, as I know the answer :-)) if I'm
writing a program and I need to build a parser, what's to tell me
(apart from asking around, or stumbling on it) that Parsec is the
library I want - or if I know that, that it's included in the standard
library and I don't need to go and install it?

(Other broad areas occasionally relevant to me - XML serialisation,
sending emails, SSH, implementing a Windows service...).

I'm not so much asking can I do X? as how do I reach a level where
I stand a chance of knowing the answer to can I do X? without
asking? :-) Ultimately, though, I agree that the basic answer is just
experience...


If someone wrote a tour of Data.List/Data.Maybe as well as a few
common functions out of Control.Monad that would probably make a nice
companion to a tour of the prelude.


David House pointed me at Wikibooks entries for these two, which look
quite nice.

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


Re: [Haskell-cafe] Is there [...] Where to find most haskell libraries I know of

2006-12-28 Thread Marc Weber
 For example (not a wonderful example, as I know the answer :-)) if I'm
 writing a program and I need to build a parser, what's to tell me
 (apart from asking around, or stumbling on it) that Parsec is the
 library I want - or if I know that, that it's included in the standard
 library and I don't need to go and install it?

Thus you need a list of availible libraries to get to know wether they
will fit your needs...

The only index I know of is www.haskell.org - link Applications and
libraries ...

Another way would be goto darcs.haskell.org and browse the folders. Many
libs are located there (of course not all)

Another list of libraries can be found in gentoo portage overlay
http://haskell.org/~gentoo/gentoo-haskell

Some standard packages can be found in one source file eg
Some additional libraries can be found here
http://www.haskell.org/ghc/dist/current/dist/  - *extra-libs*

If this and google didn't help you I would ask ;)

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


Re[2]: [Haskell-cafe] Is there [...] Where to find most haskell libraries I know of

2006-12-28 Thread Bulat Ziganshin
Hello Marc,

Thursday, December 28, 2006, 6:25:46 PM, you wrote:

 The only index I know of is www.haskell.org - link Applications and
 libraries ...

you forget about HCAR

 Another way would be goto darcs.haskell.org and browse the folders. Many
 libs are located there (of course not all)

main libraries - yes, but no more than 10% of overall count


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Strange type behavior in GHCi 6.4.2

2006-12-28 Thread Grady Lemoine

I understand the distinction, and I find both techniques interesting,
but your AD code is a lot more convenient.  All I have to do is make
sure that my functions are sufficiently polymorphic, and I can get
derivatives *automatically* with very little programmer effort.  It
seems like a good way to inject worry-free calculus wherever it's
needed -- for instance, if I want gradient information about a
function, I can use AD and avoid having to choose a length scale,
consider accuracy issues, etc. like I would if I used a finite
difference approximation.

(Of course, this assumes that the function I'm differentiating
consists only of building blocks that I have AD definitions of.  In
particular, I'm not really sure how I want to define the Ord
operations for Dual, so that a function with an if statement based on
a comparison (e.g. Gaussian elimination with pivoting) can be
differentiated.  On the one hand, I'm not sure I want to include the
infinitesimal part in the definition, because it is in some sense how
fast the number is changing, not how big it is; on the other hand, if
I don't include the infinitesimal part, my definition of Ord won't be
consistent with equality...)

One question I have, though, for anyone on the list who knows the
answer -- if I give a function a polymorphic type signature, can it
affect performance?  That is, if I write two functions with the same
definitions but different user-specified type signatures,

foo1 :: (Floating a) = a - a
foo1 = ...

and

foo2 :: Double - Double
foo2 = ...

when I apply foo1 to a Double, will the compiler (GHC, specifically)
generate code that is just as efficient as if I used foo2?

Regards,

--Grady Lemoine

On 12/19/06, Dan Piponi [EMAIL PROTECTED] wrote:

On 12/2/06, Chris Kuklewicz [EMAIL PROTECTED] wrote:
 Grady Lemoine wrote:
  I've been playing around with Dan Piponi's work on automatic
  differentiation...
 I played with such things, as seen on the old wiki:
 http://haskell.org/hawiki/ShortExamples_2fSymbolDifferentiation

I missed this while I was away on vacation so apologies for responding
to something two weeks old. I just want to point out that the method
I've been promoting is very distinct from symbolic differentiation. I
wouldn't make a big deal about this except that besides playing well
with Haskell, AD can help with many real world numerical problems, but
people often dismiss it because it they confuse it with symbolic
differentiation which they have already determined doesn't solve their
problems.
--
Dan
___
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] Strange type behavior in GHCi 6.4.2

2006-12-28 Thread Kirsten Chevalier

On 12/28/06, Grady Lemoine [EMAIL PROTECTED] wrote:


One question I have, though, for anyone on the list who knows the
answer -- if I give a function a polymorphic type signature, can it
affect performance?  That is, if I write two functions with the same
definitions but different user-specified type signatures,

foo1 :: (Floating a) = a - a
foo1 = ...

and

foo2 :: Double - Double
foo2 = ...

when I apply foo1 to a Double, will the compiler (GHC, specifically)
generate code that is just as efficient as if I used foo2?



As with so many things, the answer is it depends. The simple answer
to if I give a function a polymorphic type signature, can it affect
performance? is no, because type information is erased before code
generation. However, if by polymorphic type signatures you mean
ones involving class-based overloading, like the ones you wrote, then
the answer is maybe -- functions that have classes involved in their
types are desugared by the compiler into functions that take extra
dictionary arguments, which can make performance worse. GHC does
specialization to try to negate some of the performance impact of
this, but it doesn't always do what you want it to. The best thing to
do is to make sure you compile your code with -O2 and if profiling
seems to imply that overloaded functions are causing you bottlenecks,
seek help on this list or on Haskell IRC (and there should be a pretty
good body of previous discussion on the subject in the list archives).

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
I eat too much / I laugh too long / I like too much of you when I'm
gone. -- Ani DiFranco
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] SYB and/or HList for XML, deserialization and collections

2006-12-28 Thread Alex Jacobson
I'd really rather factor our the template haskell.  It does not leave me 
feeling good.


At the specific level, TemplateHaskell doesn't solve the problem of 
getting good XML element names.  For example with HList lets me annotate 
labels with information about whether they are attributes or elements.


At the usage level, it does not traverse other modules easily and forces 
you to do weird things with code order in order to compile.


At the concept level, I find it way too hard to think in terms of the 
abstract syntax of Haskell.  I'd rather be thinking in terms of 
application semantics.


At the implementation level, it forces the generation of standard 
accessor names e.g. withFoo for every foo, rather than supporting a 
general syntax for access or update.


-Alex-



Bulat Ziganshin wrote:

Hello S.,

Wednesday, December 27, 2006, 2:24:00 AM, you wrote:

  
Having just done a major refactor of the HAppS HTTP API to make it 
much much easier to use, I am now thinking about simplifying the 
current boilerplate associated with XML serialization and state 
deserialization.



are you considered using Template Haskell to do it? at least it is used for
automatic generation of class instances for binary serialization


  


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


Statistics on library imports (was: Re: [Haskell-cafe] Is there a printable copy of the (GHC) library references anywhere?)

2006-12-28 Thread Henk-Jan van Tuyl


About the usefulness of libraries: I just made some statistics
on imports in Haskell code; I have a lot of Haskell source code
on my disk (mostly downloaded).
In the following table, the number on the left indicates the
number of imports found for each library.

Top twenty of imports:

 418 Data.List
 417 System.IO
 288 Data.Char
 274 Control.Monad
 157 Data.Maybe
 150 Graphics.UI.WX
 144 Control.Exception
 118 Test.HUnit
 105 System.Directory
 103 Data.Word
 101 Prelude
  95 Text.ParserCombinators.Parsec
  84 System.IO.Error
  83 System.IO.Unsafe
  80 System.Exit
  79 Data.Array
  76 Graphics.UI.WXCore
  75 Data.Bits
  73 System.Time
  73 MissingH.Str

Total number of imports: 8691
Total number of files:   1918

Regards,
Henk-Jan van Tuyl


On Wed, 27 Dec 2006 22:00:24 +0100, Neil Mitchell [EMAIL PROTECTED]  
wrote:




Only a few of the standard libraries are useful unless you are doing
something specific. i.e. Data.Maybe is generally useful, but
Control.Monad.State is only useful if you are using a state monad.

If someone wrote a tour of Data.List/Data.Maybe as well as a few
common functions out of Control.Monad that would probably make a nice
companion to a tour of the prelude.

Thanks




--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
--

Using Opera's revolutionary e-mail client:
https://secure.bmtmicro.com/opera/buy-opera.html?AID=789433

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


Re: [Haskell-cafe] Is there a printable copy of the (GHC) library references anywhere?

2006-12-28 Thread Henk-Jan van Tuyl


I wrote A tour of the Haskell monad functions last year, see
  http://members.chello.nl/hjgtuyl/tourdemonad.html

Regards,
Henk-Jan van Tuyl


On Wed, 27 Dec 2006 22:00:24 +0100, Neil Mitchell [EMAIL PROTECTED]  
wrote:



If someone wrote a tour of Data.List/Data.Maybe as well as a few
common functions out of Control.Monad that would probably make a nice
companion to a tour of the prelude.


--
http://Van.Tuyl.eu/
--

Using Opera's revolutionary e-mail client:
https://secure.bmtmicro.com/opera/buy-opera.html?AID=789433

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


Re: Statistics on library imports (was: Re: [Haskell-cafe] Is there a printable copy of the (GHC) library references anywhere?)

2006-12-28 Thread Henk-Jan van Tuyl


Here are the scripts; they are written in Rexx, because I have bad  
experience with reading through a lot of files, with Haskell (memory  
leaks). You can download the Rexx interpreter Regina from SourceForge to  
run the scripts. If you rewrite them in Haskell, I would like to see the  
result.


Regards,
Henk-Jan

On Thu, 28 Dec 2006 23:08:38 +0100, David House [EMAIL PROTECTED] wrote:


On 28/12/06, Henk-Jan van Tuyl [EMAIL PROTECTED] wrote:

In the following table, the number on the left indicates the
number of imports found for each library.


Care to share your script you used to produce these numbers?





--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
--

Using Opera's revolutionary e-mail client:
https://secure.bmtmicro.com/opera/buy-opera.html?AID=789433


stat.rexx
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Statistics on library imports (was: Re: [Haskell-cafe] Is there a printable copy of the (GHC) library references anywhere?)

2006-12-28 Thread Henk-Jan van Tuyl


I pushed the Send button too fast, you need the attached script as well.

On Thu, 28 Dec 2006 23:08:38 +0100, David House [EMAIL PROTECTED] wrote:


On 28/12/06, Henk-Jan van Tuyl [EMAIL PROTECTED] wrote:

In the following table, the number on the left indicates the
number of imports found for each library.


Care to share your script you used to produce these numbers?





--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
--

Using Opera's revolutionary e-mail client:
https://secure.bmtmicro.com/opera/buy-opera.html?AID=789433


exists.rexx
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-28 Thread Steve Schafer
On Tue, 26 Dec 2006 20:21:45 -0800, you wrote:

How would this example look if you named only multiply-used expressions?
I'd like to see it in a more conventional pointful style with nested
expressions.  I'm still wondering whether the awkwardness results from your
writing style or is more inherent.  Showing the real variable names may also
help also.

This is what it looks like for real:

 process :: Item - MediaKind - MediaSize - Language - SFO
 process item mediaKind mediaSize language =
   let pagemaster = loadPagemaster item mediaKind mediaSize;
   questions = stripUndisplayedQuestions mediaKind $
   appendEndQuestions item pagemaster $
   coalesceParentedQuestions $
   validateQuestionContent $
   loadQuestions item;
  (numberedQuestions,questionCategories) = numberQuestions pagemaster 
 questions;
  numberedQuestions' = coalesceNAQuestions numberedQuestions;
  (bands,sequenceLayouts) = buildLayout mediaKind language 
 numberedQuestions';
  bands' = resolveCrossReferences bands;
  groupedBands = groupBands bands';
  pages = paginate item mediaKind mediaSize pagemaster groupedBands;
  pages' = combineRows pages;
  sfo = pages' sequenceLayouts;
  in sfo

These are the function signatures:

 loadPagemaster :: Item - MediaKind - MediaSize - Pagemaster
 loadQuestions :: Item - [Question]
 validateQuestionContent :: [Question] - [Question]
 coalesceParentedQuestions :: [Question] - [Question]
 appendEndQuestions :: Item - Pagemaster - [Question] - [Question]
 stripUndisplayedQuestions :: MediaKind - [Question] - [Question]
 numberQuestions :: Pagemaster - [Question] - 
 ([NumberedQuestion],[QuestionCategory])
 coalesceNAQuestions :: [NumberedQuestion] - [NumberedQuestion]
 buildLayout :: MediaKind - Language - [NumberedQuestion] - 
 ([Band],[SequenceLayout])
 resolveCrossReferences :: [Band] - [Band]
 groupBands :: [Band] - [[Band]]
 paginate :: Item - MediaKind - MediaSize - Pagemaster - [[Band]] - [Page]
 combineRows :: [Page] - [Page]
 createSFO :: [Page] - [SequenceLayout] - SFO

MediaKind, MediaSize and Language are simple enumerations; everything
else is a complex structure.

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Seeking advice on a style question

2006-12-28 Thread Steve Schafer
On Wed, 27 Dec 2006 17:06:24 +0100, you wrote:

But in general, it's futile trying to simplify things without knowing
their meaning: names are *important*. I assume that your proper goal is
not to structure pipeline processes in full generality, but to simplify
the current one at hand.

No, I'm looking for full generality. ;)

I have dozens of these kinds of quasi-pipelines, all similar in
overall appearance, but different in detail.

Even if you wanted to simplify the general structure, I think you'd have
to make the types of the different yk explicit. Otherwise, the problem
is underspecified and/or one has to assume that they're all different
(modulo some equalities implied by type correctness).

Most of them are, in fact, different types (see my reply to Conal).



Here's the essence of the problem. If I have this:

 process1 x y =
   let u = foo x y;
   v = bar u;
   w = baz v
   in  w

I can easily rewrite it in point-free style:

 process1 = baz . bar . foo

But if I have this:

 process2 x y =
   let u = foo x y;
   v = bar u;
   w = baz v u
   in  w

then I can't avoid naming and using an intermediate variable. And that
annoys me. The u in process2 is of no more value to me (pardon the
pun) as the one in process1, but I am forced to use it simply because
the data flow is no longer strictly linear.

The reason I brought up monads as a possible means of managing this
problem is that the State, Reader and Writer monads already handle
certain specific shapes of nonlinear data flow, which suggested to
me that maybe there was a monadic approach to managing nonlinear data
flow in a more general way. Of course, if there is a non-monadic,
purely functional way to do it, that would be even better, but I've
never seen such a thing (short of doing lots of tupling and
un-tupling).

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange type behavior in GHCi 6.4.2

2006-12-28 Thread Grady Lemoine

That's interesting.  I suppose it makes sense -- for polymorphism that
doesn't involve typeclasses, nothing is assumed about what kind of
data you have, so there's nothing you can do with it that isn't
generic to all data types.  I was wondering if the compiler would
automatically generate specialized code for certain concrete instances
of a typeclass (Double) in addition to generic code for an arbitrary
member of the typeclass (Floating a), and it sounds like I may or may
not get that in the way I want.  I suppose there may have to be some
slowdown -- if the compiler specializes every piece of code for every
instance of a typeclass it might encounter, it could bloat the
executable beyond all reason.  I'll have to do some tests to see if I
notice an effect in practice.

Thank you,

--Grady Lemoine

On 12/28/06, Kirsten Chevalier [EMAIL PROTECTED] wrote:

On 12/28/06, Grady Lemoine [EMAIL PROTECTED] wrote:

 One question I have, though, for anyone on the list who knows the
 answer -- if I give a function a polymorphic type signature, can it
 affect performance?  That is, if I write two functions with the same
 definitions but different user-specified type signatures,

 foo1 :: (Floating a) = a - a
 foo1 = ...

 and

 foo2 :: Double - Double
 foo2 = ...

 when I apply foo1 to a Double, will the compiler (GHC, specifically)
 generate code that is just as efficient as if I used foo2?


As with so many things, the answer is it depends. The simple answer
to if I give a function a polymorphic type signature, can it affect
performance? is no, because type information is erased before code
generation. However, if by polymorphic type signatures you mean
ones involving class-based overloading, like the ones you wrote, then
the answer is maybe -- functions that have classes involved in their
types are desugared by the compiler into functions that take extra
dictionary arguments, which can make performance worse. GHC does
specialization to try to negate some of the performance impact of
this, but it doesn't always do what you want it to. The best thing to
do is to make sure you compile your code with -O2 and if profiling
seems to imply that overloaded functions are causing you bottlenecks,
seek help on this list or on Haskell IRC (and there should be a pretty
good body of previous discussion on the subject in the list archives).

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
I eat too much / I laugh too long / I like too much of you when I'm
gone. -- Ani DiFranco


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


[Haskell-cafe] Combine list of sorted lists

2006-12-28 Thread Quan Ta

Hi all,

I have this function which combines (zip) list of sorted lists into a sorted
list (sorted by sum).  The function works with infinite list and seems to
give correct result.  But after I see the code for the Hamming sequence from
the Wiki, I wonder if it can be written better, or more clearly, or succint?

import Data.List

comb [] = []
comb (a:as) = foldl f2 (f1 a) as
   where
 f1 :: [Int] - [[Int]]
 f1 [] = []
 f1 (a:as) = [a] : f1 as

 f2 :: [[Int]] - [Int] - [[Int]]
 f2 la[]= []
 f2 []lb= []
 f2 la@(a:as) lb@(b:bs) = (a ++ [b]) : (f3 (f2 [a] bs) (f2 as lb))

 f3 :: [[Int]] - [[Int]] - [[Int]]
 f3 [] lb = lb
 f3 la [] = la
 f3 la lb = let a = head la
b = head lb
in if sum a = sum b then
   a : f3 (tail la) lb
   else
   b : f3 la (tail lb)

t1 = take 500 (comb [[1,2..],[1,23..],[1,5..],[1,9..]])

t2 = take 500 (sortBy (\x y - compare (sum x) (sum y))
 [[a,b,c,d] | a-[1,2..80],b-[1,23..80],
  c-[1,5..80],d-[1,9..80]])

--t3 = take 500 (sortBy (\x y - compare (sum x) (sum y))
--  [[a,b,c,d] | a-[1,2..],b-[1,23..],
--   c-[1,5..],d-[1,9..]])

main = print (show ((map sum t1) == (map sum t2)))

-- thanks for looking,
-- Quan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] flatten a nested list

2006-12-28 Thread pphetra

I would like to write a program that can do something like this.
 
;; lisp syntax
* (my-flatten '(1 (2 (3 4) 5)))
(1 2 3 4 5)

I end up like this.

data Store a = E a | S [Store a]
 deriving (Show)

flat :: [Store a] - [a]
flat [] = []
flat ((E x):xs) = [x] ++ flat xs
flat ((S x):xs) = flat x ++ flat xs

so
*Main flat [E 1, S[E 2, S[E 3, E 4], E 5]]
[1,2,3,4,5]

Compare to a Lisp solution, It 's not looking good.
Any suggestion.

Thanks,
PPhetra
-- 
View this message in context: 
http://www.nabble.com/flatten-a-nested-list-tf2893713.html#a8084726
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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