Re: [Haskell-cafe] class default method proposal

2007-12-12 Thread Luke Palmer
On Dec 11, 2007 3:19 PM, David Menendez <[EMAIL PROTECTED]> wrote:
> On Dec 11, 2007 9:20 AM, Duncan Coutts <[EMAIL PROTECTED]> wrote:
>
> > So my suggestion is that we let classes declare default implementations
> > of methods from super-classes.
> 
> > Does this proposal have any unintended consequences? I'm not sure.
> > Please discuss :-)
>
> It creates ambiguity if two classes declare defaults for a common
> superclass.
>
> My standard example involves Functor, Monad, and Comonad. Both Monad and
> Comonad could provide a default implementation for fmap. But let's say I
> have a type which is both a Monad and a Comonad: which default
> implementation gets used?

Isn't a type which is both a Monad and a Comonad just Identity?

(I'm actually not sure, I'm just conjecting)

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


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Benja Fallenstein
On Dec 13, 2007 2:28 AM, Benja Fallenstein <[EMAIL PROTECTED]> wrote:
> Although on reflection, I think I might like the following compromise
> with Tillmann's version best:
>
> main = interact $ perLine $ detab 0 where
> detab tab ('\t':cs) = replicate (4-tab) ' ' ++ detab 0 cs
> detab tab (char:cs) = char  :  detab ((tab+1) `mod` 4) cs
> detab tab ""= ""

On more reflection, I wonder whether it would be worthwhile to have a
library function for folds that work from both left *and* right:

foldlr :: (a -> b -> c -> (a,c)) -> a -> c -> [b] -> (a,c)
foldlr f l r [] = (l,r)
foldlr f l r (x:xs) = let (l',r') = f l x r''; (l'',r'') = foldlr f l' r xs
   in (l'',r')

main = interact $ perLine $ snd . foldlr detab 0 "" where
detab tab '\t' cs = (0, replicate (4-tab) ' ' ++ cs)
detab tab char cs = ((tab+1) `mod` 4, char : cs)

It's a fun function, anyway :-)

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


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Benja Fallenstein
On Dec 13, 2007 2:20 AM, Benja Fallenstein <[EMAIL PROTECTED]> wrote:
> Another version of detab:
>
> main = interact $ perLine $ concat . snd. mapAccumL f 0 where
> f tab '\t' = (0, replicate (4-tab) ' ')
> f tab char = ((tab+1) `mod` 4, [char])

Although on reflection, I think I might like the following compromise
with Tillmann's version best:

main = interact $ perLine $ detab 0 where
detab tab ('\t':cs) = replicate (4-tab) ' ' ++ detab 0 cs
detab tab (char:cs) = char  :  detab ((tab+1) `mod` 4) cs
detab tab ""= ""

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


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Benja Fallenstein
Another version of detab:

main = interact $ perLine $ concat . snd. mapAccumL f 0 where
f tab '\t' = (0, replicate (4-tab) ' ')
f tab char = ((tab+1) `mod` 4, [char])

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


Re: [Haskell-cafe] Re: Software Tools in Haskell

2007-12-12 Thread Conal Elliott
Since there are many useful per-line functions, do a little refactoring,
placing the following into a library:

  perLine :: (String -> String) -> (String -> String)
  perLine f = unlines . map f . lines


On Dec 12, 2007 12:43 PM, apfelmus <[EMAIL PROTECTED]> wrote:

> Tommy M McGuire wrote:
> > (Plus, interact is scary. :-D )
>
> You have a scary feeling for a moment, then it passes. ;)
>
> > Gwern Branwen wrote:
> >> I... I want to provide a one-liner for 'detab', but it looks
> >> impressively monstrous and I'm not sure I understand it.
> >
> > On the other hand, I'm not looking for one-liners; I really want clarity
> > as opposed to cleverness.
>
>   tabwidth = 4
>
>  -- tabstop !! (col-1) == there is a tabstop at column  col
>  -- This is an infinite list, so no need to limit the line width
>   tabstops  = map (\col -> col `mod` tabwidth == 1) [1..]
>
>  -- calculate spaces needed to fill to the next tabstop in advance
>   tabspaces = snd $ mapAccumR addspace [] tabstops
>   addspace cs isstop = let cs'=' ':cs in (if isstop then [] else cs',cs')
>
>
>   main = interact $ unlines . map detabLine . lines
>  where
>  detabLine = concat $ zipWith replace tabspaces
>  replace cs '\t' = cs -- replace with adequate number of spaces
>  replace _  char = [char] -- pass through
>
>
> How about that?
>
>
> Regards,
> apfelmus
>
> ___
> 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] GUI

2007-12-12 Thread Miguel Mitrofanov

I've seen an Objective C binding for Haskell; haven't used it yet.

13.12.2007, в 2:58, Marc A. Ziegert писал(а):


Am Mittwoch, 12. Dezember 2007 schrieb Miguel Mitrofanov:

Gtk2Hs is good (I suppose), but it requires X. OK, I have X, but it's
not "native" on my Mac; some Mac users don't install it and almost
all Mac users don't always run it.


the problem is Apple. if you want to have a native gui on OSX then  
you are either nearly stuck to Objective-C or to obsolete gui  
libraries.

i'm not a mac user, but i know one who is; he told me.
on osx there are two main gui apis: carbon and cocoa.

carbon is obsolete, but it partially runs on osx -- it is not 64bit  
compatible.



cocoa is the newer one, which every mac user likes.
AFAIK there is no C backend to that api, so you will have to  
develop a C backend first and then the haskell (or gtk2) wrapper.

there are some bindings for other languages, i.e. C#, but no C.


if you are able to code objective-c and know how to access cocoa  
using c, please help those gtk developers to port gtk2 to native OSX.

it will then automagically work with gtk2hs.

- marc
___
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] GUI

2007-12-12 Thread Marc A. Ziegert
Am Mittwoch, 12. Dezember 2007 schrieb Miguel Mitrofanov:
> Gtk2Hs is good (I suppose), but it requires X. OK, I have X, but it's  
> not "native" on my Mac; some Mac users don't install it and almost  
> all Mac users don't always run it.

the problem is Apple. if you want to have a native gui on OSX then you are 
either nearly stuck to Objective-C or to obsolete gui libraries.
i'm not a mac user, but i know one who is; he told me.
on osx there are two main gui apis: carbon and cocoa.

carbon is obsolete, but it partially runs on osx -- it is not 64bit compatible.


cocoa is the newer one, which every mac user likes.
AFAIK there is no C backend to that api, so you will have to develop a C 
backend first and then the haskell (or gtk2) wrapper.
there are some bindings for other languages, i.e. C#, but no C.


if you are able to code objective-c and know how to access cocoa using c, 
please help those gtk developers to port gtk2 to native OSX.
it will then automagically work with gtk2hs.

- marc


signature.asc
Description: This is a digitally signed message part.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Tommy M McGuire

Don Stewart wrote:


My thoughts too when reading the initial post was that it was all very
low level imperative programming. Not of the Haskell flavour.

-- Don


Oh, heck yeah.  As I was thinking when I was translating it, "I can't 
even say I'm writing Pascal code using Haskell; I wouldn't write Pascal 
code this way."


(IIRC, the xindex in translit that I mentioned uses several flag values 
in-band and I couldn't detangle the mess to figure them out, so I copied 
it as-is.  Ick.)



--
Tommy M. McGuire
[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Tillmann Rendel

Hi Tommy,

detab is one of the programs I do not like.  I kept the "direct 
translation" approach up through that, but I think it really hides the 
simplicity there; detab copies its input to its output replacing tabs 
with 1-8 spaces, based on where the tab occurs in a line.  The only 
interesting state dealt with is the count of characters on each line, 
but that gets hidden, not emphasized.


On the other hand, I'm not looking for one-liners; I really want clarity 
as opposed to cleverness.


I would do a simple, imperative feeling detab using a recursive [Char] 
processing function:


detab :: Int -> String -> String
detab width text = detab' width text where
  detab' tab [] = []
  detab' tab ('\n' : text) = '\n'  :  detab' width   text
  detab' tab ('\t' : text) = replicate tab ' ' ++ detab' width   text
  detab' 1   (char : text) = char  :  detab' width   text
  detab' tab (char : text) = char  :  detab' (tab-1) text

main = interact (detab 4)

In Haskell, using IO all over the place is the opposite of clarity, even 
in imperative feeling code wich basically encodes a main loop.


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


Re: [Haskell-cafe] Re: Software Tools in Haskell

2007-12-12 Thread Tommy M McGuire

apfelmus wrote:

Tommy M McGuire wrote:

(Plus, interact is scary. :-D )


You have a scary feeling for a moment, then it passes. ;)


  tabwidth = 4

 -- tabstop !! (col-1) == there is a tabstop at column  col
 -- This is an infinite list, so no need to limit the line width
  tabstops  = map (\col -> col `mod` tabwidth == 1) [1..]

 -- calculate spaces needed to fill to the next tabstop in advance
  tabspaces = snd $ mapAccumR addspace [] tabstops
  addspace cs isstop = let cs'=' ':cs in (if isstop then [] else cs',cs')


Are you using mapAccumR (mapAccumR? (!)) to share space among the space 
strings?  If so, wouldn't this be better:


tabstops = map (\col -> col `mod` tabwidth == 1) [1..tabwidth]
tabspaces = cycle $ snd $ mapAccumR addspace [] tabstops

On the other hand, wouldn't this make for less head scratching:

tabspaces = map (\col -> replicate (spacesFor col) ' ') [1..]
  where
  spacesFor col = tabwidth - ((col - 1) `mod` tabwidth)


  main = interact $ unlines . map detabLine . lines
 where
 detabLine = concat $ zipWith replace tabspaces


I think you mean "concat . zipWith...".   (You're doing this from 
memory, aren't you?)



 replace cs '\t' = cs -- replace with adequate number of spaces
 replace _  char = [char] -- pass through


How about that?


It doesn't produce the same output, although I almost like it enough not 
to care:


$ od -a test
000  ht   c   o   l  sp   1  ht   2  ht   3   4  ht   r   e   s   t
020  nl
021
$ runhaskell detab.hs http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: dataenc-0.10.1

2007-12-12 Thread Duncan Coutts

On Wed, 2007-12-12 at 13:30 +, Magnus Therning wrote:

> The visible change is the addition of a function, decode', that allows
> lazier decoding  by shifting some responisility to the user.

That's interesting. It's in the same spirit as the lazy variant provided
in the iconv lib. It'll be interesting to see if this is the best
general interface for allowing people to lazily convert and handle
conversion errors.

The slight difference is that the iconv lib works over bytestring chunks
rather than individual Word8 and provides a bit more detail about
errors. It's otherwise pretty similar.

convertLazily
:: EncodingName
  -- ^ Name of input string encoding
-> EncodingName
  -- ^ Name of output string
encoding
-> ByteString
  -- ^ Input text
-> [Span]
  -- ^ Output text spans

When nothing goes wrong we expect just a bunch of Spans. If there are
conversion errors we get other span types.

data Span = Span ByteString | ConversionError ConversionError

data ConversionError =
   UnsuportedConversion EncodingName EncodingName
 | InvalidChar Offset
 | IncompleteChar Offset
 | UnexpectedError Errno

http://hackage.haskell.org/packages/archive/iconv/0.4/doc/html/Codec-Text-IConv.html#v%3AconvertLazily

Duncan

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


Re[2]: [Haskell-cafe] New slogan for haskell.org

2007-12-12 Thread Bulat Ziganshin
Hello Andrew,

Thursday, December 13, 2007, 12:40:59 AM, you wrote:

>> Knuth[1] pp. 417-419 discusses Fibonacci trees and Fibonacci search.
>> According to Knuth (and who am I to argue with him) Fibonacci search has
>> better average case running time than binary search, although worst case
>> can be slightly slower.

afair, it's only because binary shift operation is rather slow on MIX
machine while Fib. search use just subtraction to compute next index
to try

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] class default method proposal

2007-12-12 Thread Lennart Augustsson
I had it pretty well worked out for single parameter type classes, but I
couldn't see any nice extension to multiple parameters.

On Dec 11, 2007 5:30 PM, Simon Peyton-Jones <[EMAIL PROTECTED]> wrote:

> | If it really would work ok we should get it fully specified and
> | implemented so we can fix the most obvious class hierarchy problems in a
> | nice backwards compatible way. Things are only supposed to be candidates
> | for Haskell' if they're already implemented.
>
> Getting it fully specified is the first thing.
>
> Personally I am not keen about
>
> a) coupling it to explicit import/export (independently-desirable though
> such a change might be)
>
> b) having instance declarations silently spring into existence
>
>
> Concerning (b) here's a suggestion.  As now, require that every instance
> requires an instance declaration.  So, in the main example of
> http://haskell.org/haskellwiki/Class_system_extension_proposal, for a new
> data type T you'd write
>instance Monad T where
>  return = ...
>  (>>=)  = ...
>
>instance Functor T
>instance Applicative T
>
> The instance declaration for (Functor T) works just as usual (no explicit
> method, so use the default method) except for one thing: how the default
> method is found.  The change is this:
>Given "instance C T where ...", for any method 'm' not
>defined by "...":
>for every class D of which C is a superclass
>where there is an instance for (D T)
>see if the instance gives a binding for 'm'
>If this search finds exactly one binding, use it,
>otherwise behave as now
>
> This formulation reduces the problem to a more manageable one: a search
> for the default method.
>
> I'm not sure what is supposed to happen if the instance is for something
> more complicated (T a, say, or multi-parameter type class) but I bet you
> could work it out.
>
> All these instances would need to be in the same module:
>   - you can't define Functor T without Monad T, because you
>want to pick up the monad-specific default method
>   - you can't define Monad T without Functor T, because
>the latter is a superclass of the former
>
> It still sounds a bit complicated.
>
> Simon
> ___
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Folding Integrals

2007-12-12 Thread Lennart Augustsson
Not "can", "should".  And it might even survive in th world of Unicode.

On Dec 12, 2007 4:17 PM, Brent Yorgey <[EMAIL PROTECTED]> wrote:

>
> On Dec 12, 2007 10:36 AM, Arie Groeneveld <[EMAIL PROTECTED]> wrote:
>
> > Reinier Lamers schreef:
> > >
> > > printint :: Int -> [Char]
> > > printint = map chr . map (+0x30) . reverse . map (`mod` 10) .
> > > takeWhile (>0) . iterate (`div`10)
> > >
> > Most of the time I use this:
> >
> > digits :: Integer -> [Int]
> > digits = map (flip(-)48.ord) . show
> >
>
> One can also use Data.Char.digitToInt in place of (flip (-) 48 . ord).
>
> -Brent
>
>
> ___
> 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] New slogan for haskell.org

2007-12-12 Thread Andrew Coppin

Bill Wood wrote:

On Wed, 2007-12-12 at 11:19 +, Andrew Coppin wrote:
   . . .
  

...and normal programmers care about the Fibonacci numbers because...?

Seriously, there are many, many programmers who don't even know what 
Fibonacci numbers *are*. And even I can't think of a useful purpose for 
them. (Unless you count Fibonacci codes?)



Knuth[1] pp. 417-419 discusses Fibonacci trees and Fibonacci search.
According to Knuth (and who am I to argue with him) Fibonacci search has
better average case running time than binary search, although worst case
can be slightly slower.

Cormen et. al.[2] devotes chapter 20 to Fibonacci heaps, which they say
are of primarily theoretical interest.

[1] Donald E. Knuth, The Art of Computer Programming, vol. 3, second
edition, Addison Wesley Longman (1998).

[2] Thomas H. Cormen, Charles E. Leiserson, Ronald L. Rivest and
Clifford Stein, Introduction to Algorithms, second edition, The MIT
Press (2001).
  


Mmm, today I learned something.

http://en.wikipedia.org/wiki/Fibonacci_heap
http://en.wikipedia.org/wiki/Fibonacci_search

It seems that at least the latter actually involves the Fibonacci 
numbers, rather than merely having "Fibonacci" in the name. [That was 
going to be my next question...]


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


Re: [Haskell-cafe] eager/strict eval katas

2007-12-12 Thread Benja Fallenstein
On Dec 12, 2007 9:58 PM, Don Stewart <[EMAIL PROTECTED]> wrote:
> And no need to even use custom ones, just use the library strict pairs,
>
> 
> http://hackage.haskell.org/packages/archive/strict/0.2/doc/html/Data-Strict-Tuple.html

Oh, good! :)

'nother Haskell lesson learned. Thanks,
- Benja
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] eager/strict eval katas

2007-12-12 Thread Dan Weston

Dan Weston wrote:
scanl above is not strict in its second argument. The data dependencies 
cause the strictness. Cf:


Prelude> head ([1,3] ++ head ((scanl undefined undefined) undefined))
1


The first claim is of course false, nore would the example show it anyway.

scanl is not strict in its third argument (I forgot about the initial 
value as the second argument):


Prelude Data.List> let z = [1,4,undefined,8,9] in scanl (\x y -> 5) 8 z
[8,5,5,5,5,5]

It is the data dependence in the first argument of scanl that would make 
the above strict:


Prelude Data.List> let z = [1,4,undefined,8,9] in scanl (+) 8 z
[8,9,13,*** Exception: Prelude.undefined


Also note that it is better not to introduce the / operator in your 
test, as it fails with large numbers. Multiply both sides by the 
denominator before the comparison and leave everything as Num a instead 
of Floating a. You can do the division at the end.



Thomas Hartman wrote:



 >Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is 
(n+1) / 2


fair enough.

But I believe  if I restate the problem  so that you need to find the 
average of an arbitrary list, your clever trick doesn't work and we 
need eager eval or we blow the stack.


Not true:

Prelude Data.List> let f a = (\(a,b,c)->c) . head . dropWhile (\(s,n,_) 
-> s <=n*a) . scanl (\(s,n,_) x ->(s+x,n+1,x)) (0,0,0) in f (10^5) [1,3..]

21


Also... on second thought, I actually solved a slightly different 
problem than what I originally said:  the problem of detecting when 
the moving average of an increasing list is greater than 10^6; but my 
solution doesn't give the index of the list element that bumped the 
list over the average. However I suspect my code could be tweaked to 
do that (still playing around with it):


Also I actually used a strict scan not a strict fold and... ach, oh well.


scanl above is not strict in its second argument. The data dependencies 
cause the strictness. Cf:


Prelude> head ([1,3] ++ head ((scanl undefined undefined) undefined))
1

As you see I wrote a customized version of foldl' that is strict on 
the tuple for this to work. I don't think this is necessarily faster 
than what you did  (haven't quite grokked your use of unfold), but it 
does have the nice property of doing everything in one one fold step 
(or one scan step I guess, but isn't a scan


http://thomashartman-learning.googlecode.com/svn/trunk/haskell/lazy-n-strict/average.hs 



You have

Prelude Control.Arrow Data.List>
  let avg5 = uncurry (/) . foldl' (\(s,n) x -> (s + x,n + 1)) (0,0)
   in avg5 [1..1000]
*** Exception: stack overflow
-- This fails in 100 sec

Try this. It is not foldl' that needs to be strict, but the function 
folded:


Prelude Data.List> let avg5 = uncurry (/) . foldl' (\(!s,!n) x -> (s + 
x,n + 1)) (0,0) in avg5 [1..1000]


You will need -fbang-patterns for this (there are other ways to do this 
in Haskell 98 though).





t.

t1 = average_greater_than (10^7) [1..]

average_greater_than max xs = find (>max) $ averages xs

averages = map fst . myscanl' lAccumAvg (0,0)
average = fst . myfoldl' lAccumAvg (0,0)
lAccumAvg (!avg,!n) r = ( (avg*n/n1) + (r/n1),(n1))
 where n1 = n+1

myfoldl' f (!l,!r) [] = (l,r)
myfoldl' f (!l,!r) (x:xs) = ( myfoldl' f q xs )
 where q = (l,r) `f` x

myscanl f z []  = z : []
myscanl f z (x:xs) =  z : myscanl f (f z x) xs

myscanl' f (!l,!r) []  = (l,r) : []
myscanl' f (!l,!r) (x:xs) =  (l,r) : myscanl' f q xs
 where q = (l,r) `f` x




*"Felipe Lessa" <[EMAIL PROTECTED]>*

12/12/2007 02:24 PM


To

Thomas Hartman/ext/[EMAIL PROTECTED]
cc
haskell-cafe@haskell.org
Subject
Re: [Haskell-cafe] eager/strict eval katas









On Dec 12, 2007 2:31 PM, Thomas Hartman <[EMAIL PROTECTED]> wrote:
 > exercise 2) find the first integer such that average of [1..n] is > 
[10^6]
 >   (solution involves building an accum list of (average,listLength) 
tuples.
 > again you can't do a naive fold due to stack overflow, but in this 
case even
 > strict foldl' from data.list isn't "strict enough", I had to define 
my own

 > custom fold to be strict on the tuples.)

What is wrong with

Prelude> snd . head $ dropWhile ((< 10^6) . fst) [((n+1) / 2, n) | n 
<- [1..]]

199.0

Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is
(n+1) / 2. The naive

Prelude Data.List> let avg xs = foldl' (+) 0 xs / (fromIntegral $ 
length xs)

Prelude Data.List> snd . head $ dropWhile ((< 10^6) . fst) [(avg
[1..n], n) | n <- [1..]]

works for me as well, only terribly slower (of course). Note that I
used foldl' for sum assuming the exercise 1 was already done =). How
did you solve this problem with a fold? I see you can use unfoldr:

Prelude Data.List> last $ unfoldr (\(x,s,k) -> if s >= k then Nothing
else Just (x, (x+1,s+x,k+10^6)))  (2,1,10^6)

I'm thinking about a way of folding [1..], but this can't be a left
fold (or else it would never stop), nor can it be a right fold (or
else we wouldn't get the sums already done). Wha

Re: [Haskell-cafe] eager/strict eval katas

2007-12-12 Thread Don Stewart
benja.fallenstein:
> Hi Thomas,
> 
> On Dec 12, 2007 5:31 PM, Thomas Hartman <[EMAIL PROTECTED]> wrote:
> >   (solution involves building an accum list of (average,listLength) tuples.
> > again you can't do a naive fold due to stack overflow, but in this case even
> > strict foldl' from data.list isn't "strict enough", I had to define my own
> > custom fold to be strict on the tuples.)
> 
> Might it be worthwhile considering the use of a custom strict pair
> type instead of rewriting the strict fold functions? I.e., define
> 
> data Pair a b = Pair !a !b
> 
> and then use ordinary foldl' and foldr' on that.

And no need to even use custom ones, just use the library strict pairs,


http://hackage.haskell.org/packages/archive/strict/0.2/doc/html/Data-Strict-Tuple.html

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


Re: [Haskell-cafe] ANNOUNCE: A ReadP style parser for ByteStrings

2007-12-12 Thread Don Stewart
gracjanpolak:
> 
> I'm happy to announce a ReadP style parser for ByteStrings,
> Text.ParserCombinators.ReadP.ByteString.
> 
> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bytestringreadp
> 
> Text.ParserCombinators.ReadP.ByteString is an adaptation of
> Text.ParserCombinators.ReadP to work over Data.ByteString as input
> stream representation. This gives enormous improvements in terms of
> parsing speed but most significantly in memory usage.
> 
> Features:
> 
>  * ReadP style parser over ByteString input
>  * Drop-in replacement for Text.ParserCombinators.ReadP
>  * Fast
>  * Good memory usage
> 
> The algorithm is slightly modified to exploit ByteString as random access
> data input structure. Unlike original ReadP, that stressed garbage collection 
> very much by creating a lot of conses (:), this parser has very good memory
> allocation behaviour.
> 
> Package works out of the box with GHC 6.8.1, with slight (cabal) modifications
> also with GHC 6.6.1.
> 
> Thanks to everyone for their support! Happy hacking!


Great work, Gracjan. I hope to try it out soon. I think this is the
first of the many bytestring parser projects started to actually get
released onto Hackage! Well done!

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


Re: [Haskell-cafe] eager/strict eval katas

2007-12-12 Thread Benja Fallenstein
Hi Thomas,

On Dec 12, 2007 5:31 PM, Thomas Hartman <[EMAIL PROTECTED]> wrote:
>   (solution involves building an accum list of (average,listLength) tuples.
> again you can't do a naive fold due to stack overflow, but in this case even
> strict foldl' from data.list isn't "strict enough", I had to define my own
> custom fold to be strict on the tuples.)

Might it be worthwhile considering the use of a custom strict pair
type instead of rewriting the strict fold functions? I.e., define

data Pair a b = Pair !a !b

and then use ordinary foldl' and foldr' on that.

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


Re: [Haskell-cafe] eager/strict eval katas

2007-12-12 Thread Dan Weston

Thomas Hartman wrote:



 >Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is 
(n+1) / 2


fair enough.

But I believe  if I restate the problem  so that you need to find the 
average of an arbitrary list, your clever trick doesn't work and we need 
eager eval or we blow the stack.


Not true:

Prelude Data.List> let f a = (\(a,b,c)->c) . head . dropWhile (\(s,n,_) 
-> s <=n*a) . scanl (\(s,n,_) x ->(s+x,n+1,x)) (0,0,0) in f (10^5) [1,3..]

21


Also... on second thought, I actually solved a slightly different 
problem than what I originally said:  the problem of detecting when the 
moving average of an increasing list is greater than 10^6; but my 
solution doesn't give the index of the list element that bumped the list 
over the average. However I suspect my code could be tweaked to do that 
(still playing around with it):


Also I actually used a strict scan not a strict fold and... ach, oh well.


scanl above is not strict in its second argument. The data dependencies 
cause the strictness. Cf:


Prelude> head ([1,3] ++ head ((scanl undefined undefined) undefined))
1

As you see I wrote a customized version of foldl' that is strict on the 
tuple for this to work. I don't think this is necessarily faster than 
what you did  (haven't quite grokked your use of unfold), but it does 
have the nice property of doing everything in one one fold step (or one 
scan step I guess, but isn't a scan


http://thomashartman-learning.googlecode.com/svn/trunk/haskell/lazy-n-strict/average.hs 


You have

Prelude Control.Arrow Data.List>
  let avg5 = uncurry (/) . foldl' (\(s,n) x -> (s + x,n + 1)) (0,0)
   in avg5 [1..1000]
*** Exception: stack overflow
-- This fails in 100 sec

Try this. It is not foldl' that needs to be strict, but the function folded:

Prelude Data.List> let avg5 = uncurry (/) . foldl' (\(!s,!n) x -> (s + 
x,n + 1)) (0,0) in avg5 [1..1000]


You will need -fbang-patterns for this (there are other ways to do this 
in Haskell 98 though).





t.

t1 = average_greater_than (10^7) [1..]

average_greater_than max xs = find (>max) $ averages xs

averages = map fst . myscanl' lAccumAvg (0,0)
average = fst . myfoldl' lAccumAvg (0,0)
lAccumAvg (!avg,!n) r = ( (avg*n/n1) + (r/n1),(n1))
 where n1 = n+1

myfoldl' f (!l,!r) [] = (l,r)
myfoldl' f (!l,!r) (x:xs) = ( myfoldl' f q xs )
 where q = (l,r) `f` x

myscanl f z []  = z : []
myscanl f z (x:xs) =  z : myscanl f (f z x) xs

myscanl' f (!l,!r) []  = (l,r) : []
myscanl' f (!l,!r) (x:xs) =  (l,r) : myscanl' f q xs
 where q = (l,r) `f` x




*"Felipe Lessa" <[EMAIL PROTECTED]>*

12/12/2007 02:24 PM


To
Thomas Hartman/ext/[EMAIL PROTECTED]
cc
haskell-cafe@haskell.org
Subject
Re: [Haskell-cafe] eager/strict eval katas








On Dec 12, 2007 2:31 PM, Thomas Hartman <[EMAIL PROTECTED]> wrote:
 > exercise 2) find the first integer such that average of [1..n] is > 
[10^6]
 >   (solution involves building an accum list of (average,listLength) 
tuples.
 > again you can't do a naive fold due to stack overflow, but in this 
case even
 > strict foldl' from data.list isn't "strict enough", I had to define 
my own

 > custom fold to be strict on the tuples.)

What is wrong with

Prelude> snd . head $ dropWhile ((< 10^6) . fst) [((n+1) / 2, n) | n <- 
[1..]]

199.0

Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is
(n+1) / 2. The naive

Prelude Data.List> let avg xs = foldl' (+) 0 xs / (fromIntegral $ length xs)
Prelude Data.List> snd . head $ dropWhile ((< 10^6) . fst) [(avg
[1..n], n) | n <- [1..]]

works for me as well, only terribly slower (of course). Note that I
used foldl' for sum assuming the exercise 1 was already done =). How
did you solve this problem with a fold? I see you can use unfoldr:

Prelude Data.List> last $ unfoldr (\(x,s,k) -> if s >= k then Nothing
else Just (x, (x+1,s+x,k+10^6)))  (2,1,10^6)

I'm thinking about a way of folding [1..], but this can't be a left
fold (or else it would never stop), nor can it be a right fold (or
else we wouldn't get the sums already done). What am I missing?

Cheers,

--
Felipe.


---

This e-mail may contain confidential and/or privileged information. If you
are not the intended recipient (or have received this e-mail in error)
please notify the sender immediately and destroy this e-mail. Any
unauthorized copying, disclosure or distribution of the material in this
e-mail is strictly forbidden.




___
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: Software Tools in Haskell

2007-12-12 Thread apfelmus

Tommy M McGuire wrote:

(Plus, interact is scary. :-D )


You have a scary feeling for a moment, then it passes. ;)


Gwern Branwen wrote:

I... I want to provide a one-liner for 'detab', but it looks
impressively monstrous and I'm not sure I understand it.


On the other hand, I'm not looking for one-liners; I really want clarity 
as opposed to cleverness.


  tabwidth = 4

 -- tabstop !! (col-1) == there is a tabstop at column  col
 -- This is an infinite list, so no need to limit the line width
  tabstops  = map (\col -> col `mod` tabwidth == 1) [1..]

 -- calculate spaces needed to fill to the next tabstop in advance
  tabspaces = snd $ mapAccumR addspace [] tabstops
  addspace cs isstop = let cs'=' ':cs in (if isstop then [] else cs',cs')


  main = interact $ unlines . map detabLine . lines
 where
 detabLine = concat $ zipWith replace tabspaces
 replace cs '\t' = cs -- replace with adequate number of spaces
 replace _  char = [char] -- pass through


How about that?


Regards,
apfelmus

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


Re: [Haskell-cafe] New slogan for haskell.org

2007-12-12 Thread Emre Sahin
> Andrew Coppin <[EMAIL PROTECTED]> writes:

> [...]

> Yeah, we should probably set up a seperate list for this
> stuff...

Agreed. :)

This type of general discussions cannot be concluded. A board of bored
Haskellers socialize themselves. 

To be honest, I didn't read that thing (in Haskell page or Python
page) once. I think we should link to this thread instead. It would be
much more entertaining. (Infinite are the arguments of Haskell
programmers.)

Anyway, I still like code more than buzzwords. 

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


Re: [Haskell-cafe] eager/strict eval katas

2007-12-12 Thread Thomas Hartman
>Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is (n+1)
/ 2

fair enough.

But I believe  if I restate the problem  so that you need to find the
average of an arbitrary list, your clever trick doesn't work and we need
eager eval or we blow the stack.

Also... on second thought, I actually solved a slightly different problem
than what I originally said:  the problem of detecting when the moving
average of an increasing list is greater than 10^6; but my solution
doesn't give the index of the list element that bumped the list over the
average. However I suspect my code could be tweaked to do that (still
playing around with it):

Also I actually used a strict scan not a strict fold and... ach, oh well.

As you see I wrote a customized version of foldl' that is strict on the
tuple for this to work. I don't think this is necessarily faster than what
you did  (haven't quite grokked your use of unfold), but it does have the
nice property of doing everything in one one fold step (or one scan step I
guess, but isn't a scan

http://thomashartman-learning.googlecode.com/svn/trunk/haskell/lazy-n-strict/average.hs

t.

t1 = average_greater_than (10^7) [1..]

average_greater_than max xs = find (>max) $ averages xs

averages = map fst . myscanl' lAccumAvg (0,0)
average = fst . myfoldl' lAccumAvg (0,0)
lAccumAvg (!avg,!n) r = ( (avg*n/n1) + (r/n1),(n1))
  where n1 = n+1

myfoldl' f (!l,!r) [] = (l,r)
myfoldl' f (!l,!r) (x:xs) = ( myfoldl' f q xs )
  where q = (l,r) `f` x

myscanl f z []  = z : []
myscanl f z (x:xs) =  z : myscanl f (f z x) xs

myscanl' f (!l,!r) []  = (l,r) : []
myscanl' f (!l,!r) (x:xs) =  (l,r) : myscanl' f q xs
  where q = (l,r) `f` x





"Felipe Lessa" <[EMAIL PROTECTED]>
12/12/2007 02:24 PM

To
Thomas Hartman/ext/[EMAIL PROTECTED]
cc
haskell-cafe@haskell.org
Subject
Re: [Haskell-cafe] eager/strict eval katas






On Dec 12, 2007 2:31 PM, Thomas Hartman <[EMAIL PROTECTED]> wrote:
> exercise 2) find the first integer such that average of [1..n] is >
[10^6]
>   (solution involves building an accum list of (average,listLength)
tuples.
> again you can't do a naive fold due to stack overflow, but in this case
even
> strict foldl' from data.list isn't "strict enough", I had to define my
own
> custom fold to be strict on the tuples.)

What is wrong with

Prelude> snd . head $ dropWhile ((< 10^6) . fst) [((n+1) / 2, n) | n <-
[1..]]
199.0

Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is
(n+1) / 2. The naive

Prelude Data.List> let avg xs = foldl' (+) 0 xs / (fromIntegral $ length
xs)
Prelude Data.List> snd . head $ dropWhile ((< 10^6) . fst) [(avg
[1..n], n) | n <- [1..]]

works for me as well, only terribly slower (of course). Note that I
used foldl' for sum assuming the exercise 1 was already done =). How
did you solve this problem with a fold? I see you can use unfoldr:

Prelude Data.List> last $ unfoldr (\(x,s,k) -> if s >= k then Nothing
else Just (x, (x+1,s+x,k+10^6)))  (2,1,10^6)

I'm thinking about a way of folding [1..], but this can't be a left
fold (or else it would never stop), nor can it be a right fold (or
else we wouldn't get the sums already done). What am I missing?

Cheers,

--
Felipe.



---

This e-mail may contain confidential and/or privileged information. If you
are not the intended recipient (or have received this e-mail in error)
please notify the sender immediately and destroy this e-mail. Any
unauthorized copying, disclosure or distribution of the material in this
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GUI

2007-12-12 Thread Brandon S. Allbery KF8NH


On Dec 12, 2007, at 14:51 , Felipe Lessa wrote:

On Dec 12, 2007 5:40 PM, Miguel Mitrofanov <[EMAIL PROTECTED]>  
wrote:

Gtk2Hs is good (I suppose), but it requires X. OK, I have X, but it's
not "native" on my Mac; some Mac users don't install it and almost
all Mac users don't always run it.


Gtk is going native on Mac: http://developer.imendio.com/projects/ 
gtk-macosx .


Huh.  I found the sourceforge project, which seems to have died in  
2003; this looks a bit more hopeful.


--
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] GUI

2007-12-12 Thread Conal Elliott
I prefer the elegant high-level style of wxhaskell over the current state of
gtk2hs.  duncan has said he's interested in making a gtk2hs more elegant,
and daan has said he'll start supporting wxhaskell again.  i don't know
which will happen first.  - Conal

On Dec 12, 2007 11:47 AM, Neil Mitchell <[EMAIL PROTECTED]> wrote:

> Hi
>
> > Is there any really cross-platform GUI library for Haskell?
> >
> > Gtk2Hs is good (I suppose), but it requires X. OK, I have X, but it's
> > not "native" on my Mac; some Mac users don't install it and almost
> > all Mac users don't always run it.
>
> On Windows, Gtk2hs is not as native as wxHaskell, but is the best GUI
> toolkit available. On Windows, there is no requirement to have X
> installed. The Gtk2hs developers (or more specifically Duncan) have
> shown a continuing desire to make Gtk2hs more Windows friendly, even
> to the point of filing Gtk bugs and tracking their progress. I'm sure
> having made Mac friendly noises, they will come rushing to your aid
> :-)
>
> Thanks
>
> Neil
> ___
> 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] GUI

2007-12-12 Thread Felipe Lessa
On Dec 12, 2007 5:40 PM, Miguel Mitrofanov <[EMAIL PROTECTED]> wrote:
> Gtk2Hs is good (I suppose), but it requires X. OK, I have X, but it's
> not "native" on my Mac; some Mac users don't install it and almost
> all Mac users don't always run it.

Gtk is going native on Mac: http://developer.imendio.com/projects/gtk-macosx .

The Gtk# guys are starting to try it now, and they're using a
reasonably big software as test case:
http://tirania.org/blog/archive/2007/Dec-02-2.html .

So I guess going with Gtk2Hs isn't a bad path. Well, I confess I don't
have a Mac, but it looks like things are getting better =).

HTH,

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


Re: [Haskell-cafe] GUI

2007-12-12 Thread Brandon S. Allbery KF8NH


On Dec 12, 2007, at 14:47 , Neil Mitchell wrote:


Hi


Is there any really cross-platform GUI library for Haskell?

Gtk2Hs is good (I suppose), but it requires X. OK, I have X, but it's
not "native" on my Mac; some Mac users don't install it and almost
all Mac users don't always run it.


On Windows, Gtk2hs is not as native as wxHaskell, but is the best GUI
toolkit available. On Windows, there is no requirement to have X
installed. The Gtk2hs developers (or more specifically Duncan) have
shown a continuing desire to make Gtk2hs more Windows friendly, even
to the point of filing Gtk bugs and tracking their progress. I'm sure
having made Mac friendly noises, they will come rushing to your aid
:-)


A quick google reveals two different attempts to make a native OSX Gtk 
+ port; one appears moribund and the other vapor.  :(


--
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] GUI

2007-12-12 Thread Neil Mitchell
Hi

> Is there any really cross-platform GUI library for Haskell?
>
> Gtk2Hs is good (I suppose), but it requires X. OK, I have X, but it's
> not "native" on my Mac; some Mac users don't install it and almost
> all Mac users don't always run it.

On Windows, Gtk2hs is not as native as wxHaskell, but is the best GUI
toolkit available. On Windows, there is no requirement to have X
installed. The Gtk2hs developers (or more specifically Duncan) have
shown a continuing desire to make Gtk2hs more Windows friendly, even
to the point of filing Gtk bugs and tracking their progress. I'm sure
having made Mac friendly noises, they will come rushing to your aid
:-)

Thanks

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


[Haskell-cafe] GUI

2007-12-12 Thread Miguel Mitrofanov

Is there any really cross-platform GUI library for Haskell?

Gtk2Hs is good (I suppose), but it requires X. OK, I have X, but it's  
not "native" on my Mac; some Mac users don't install it and almost  
all Mac users don't always run it.


I was able to install wxHaskell (after some hacking - this was really  
painful); and Blobs editor compiled successfully, but then resisted  
to run.


Tk-based libraries seem to be good, and Tk can be run "natively" on  
Mac (i.e., without X), but none of them seem to compile.


Sorry if this message seems like I'm angry; I am, but that's only for  
a moment.

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


Re: [Haskell-cafe] eager/strict eval katas

2007-12-12 Thread Felipe Lessa
On Dec 12, 2007 2:31 PM, Thomas Hartman <[EMAIL PROTECTED]> wrote:
> exercise 2) find the first integer such that average of [1..n] is > [10^6]
>   (solution involves building an accum list of (average,listLength) tuples.
> again you can't do a naive fold due to stack overflow, but in this case even
> strict foldl' from data.list isn't "strict enough", I had to define my own
> custom fold to be strict on the tuples.)

What is wrong with

Prelude> snd . head $ dropWhile ((< 10^6) . fst) [((n+1) / 2, n) | n <- [1..]]
199.0

Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is
(n+1) / 2. The naive

Prelude Data.List> let avg xs = foldl' (+) 0 xs / (fromIntegral $ length xs)
Prelude Data.List> snd . head $ dropWhile ((< 10^6) . fst) [(avg
[1..n], n) | n <- [1..]]

works for me as well, only terribly slower (of course). Note that I
used foldl' for sum assuming the exercise 1 was already done =). How
did you solve this problem with a fold? I see you can use unfoldr:

Prelude Data.List> last $ unfoldr (\(x,s,k) -> if s >= k then Nothing
else Just (x, (x+1,s+x,k+10^6)))  (2,1,10^6)

I'm thinking about a way of folding [1..], but this can't be a left
fold (or else it would never stop), nor can it be a right fold (or
else we wouldn't get the sums already done). What am I missing?

Cheers,

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


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Conal Elliott
Here's a version with cleaner separation between pure & IO:

main = interact $ show . length . words

  - Conal

On Dec 12, 2007 11:12 AM, Neil Mitchell <[EMAIL PROTECTED]> wrote:

> Hi
>
> Having got to the word counting example on the website:
>
> wordcount :: IO ()
> wordcount = do
>wc <- wordcount' False 0
>putStrLn (show wc)
>where
>wordcount' inword wc = do
>   ch <- getc
>   case ch of
>   Nothing -> return wc
>   Just c -> handlechar c wc inword
>handlechar c wc _ | (c == ' ' ||
> c == '\n' ||
> c == '\t') = wordcount' False wc
>handlechar _ wc False = wordcount' True $! wc + 1
>handlechar _ wc True = wordcount' True wc
>
> Eeek. That's uglier than the C version, and has no abstract components.
>
> A much simpler version:
>
> main = print . length . words =<< getContents
>
> Beautiful, specification orientated, composed of abstract components.
> Code doesn't get much more elegant than that. Plus it also can be made
> to outperform C 
> (http://www-users.cs.york.ac.uk/~ndm/supero/
> )
>
> Thanks
>
> Neil
> ___
> 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] PHP/code generation libraries?

2007-12-12 Thread Justin Bailey
I'm working on a project which would generate a PHP data-access layer
from a Haskell model. I'm wondering what libraries might be already be
available for generating PHP or other types of code. The
pretty-printing library is one option. Any other suggestions?

Thanks in advance.

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


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Don Stewart
ndmitchell:
> Hi
> 
> Having got to the word counting example on the website:
> 
> wordcount :: IO ()
> wordcount = do
> wc <- wordcount' False 0
> putStrLn (show wc)
> where
> wordcount' inword wc = do
>ch <- getc
>case ch of
>Nothing -> return wc
>Just c -> handlechar c wc inword
> handlechar c wc _ | (c == ' ' ||
>  c == '\n' ||
>  c == '\t') = wordcount' False wc
> handlechar _ wc False = wordcount' True $! wc + 1
> handlechar _ wc True = wordcount' True wc
> 
> Eeek. That's uglier than the C version, and has no abstract components.
> 
> A much simpler version:
> 
> main = print . length . words =<< getContents
> 
> Beautiful, specification orientated, composed of abstract components.

My thoughts too when reading the initial post was that it was all very
low level imperative programming. Not of the Haskell flavour.

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


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Neil Mitchell
Hi

Having got to the word counting example on the website:

wordcount :: IO ()
wordcount = do
wc <- wordcount' False 0
putStrLn (show wc)
where
wordcount' inword wc = do
   ch <- getc
   case ch of
   Nothing -> return wc
   Just c -> handlechar c wc inword
handlechar c wc _ | (c == ' ' ||
 c == '\n' ||
 c == '\t') = wordcount' False wc
handlechar _ wc False = wordcount' True $! wc + 1
handlechar _ wc True = wordcount' True wc

Eeek. That's uglier than the C version, and has no abstract components.

A much simpler version:

main = print . length . words =<< getContents

Beautiful, specification orientated, composed of abstract components.
Code doesn't get much more elegant than that. Plus it also can be made
to outperform C (http://www-users.cs.york.ac.uk/~ndm/supero/)

Thanks

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


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Neil Mitchell
Hi

> main = do (print . showln . length) =<< getContents
>where showln a = show a ++ "\n"

This can be written better. print puts a newline at the end and does a
show, so lets remove that bit:

main = do (print . length) =<< getContents

Now we aren't using do notation, despite having a do block, and the
brackets are redundant:

main = print . length =<< getContents

Much nicer :-)

Thanks

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


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Tommy M McGuire

Gwern Branwen wrote:

Some of those really look like they could be simpler, like 'copy' -
couldn't that simply be 'main = interact (id)'?

Have you seen ?

For example, 'charcount' could be a lot simpler - 'charcount = showln
. length' would work, wouldn't it, for the core logic, and the whole
thing might look like:


main = do (print . showln . length) =<< getContents


Similarly wordcount could be a lot shorter, like 'wc_l = showln .
length . lines'

(showln is a convenience function: showln a = show a ++ "\n")


Yes, that's absolutely true, and I am adding a section showing 
implementations based on interact as soon as I send this message.  The 
reason I didn't do so before is that I was trying to (to an extent) 
preserve the structure of the original implementations, which means 
using an imperative style.


Strangely, I have considerably more confidence in the imperative-ish 
Haskell code than I do in the imperative Pascal code, in spite of the 
fact that they are essentially the same.  Probably this is due to the 
referential transparency that monadic IO preserves and that does not 
even enter into the picture in traditional Pascal.  For example, the 
pseudo-nroff implementation has a giant, horrible block of a record 
(containing the state taken directly from K&P) that is threaded through 
the program, but I am tolerably happy with it because I know that is the 
*only* state going through the program.


Further, while interact could probably handle all of the filter-style 
programs (and if I understand correctly, could also work for the main 
loop of the interactive editor) and a similar function could handle the 
later file-reading programs, I do not see how to generalize that to the 
out-of-core sort program.


(Plus, interact is scary. :-D )


I... I want to provide a one-liner for 'detab', but it looks
impressively monstrous and I'm not sure I understand it.


If you think that's bad :-)

detab is one of the programs I do not like.  I kept the "direct 
translation" approach up through that, but I think it really hides the 
simplicity there; detab copies its input to its output replacing tabs 
with 1-8 spaces, based on where the tab occurs in a line.  The only 
interesting state dealt with is the count of characters on each line, 
but that gets hidden, not emphasized.


On the other hand, I'm not looking for one-liners; I really want clarity 
as opposed to cleverness.



One final comment: as regards run-length encoding, there's a really
neat way to do it. I wrote a little article on how to do it a while
ago, so I guess I'll just paste it in here. :)


That *is* neat.


--
Tommy M. McGuire
[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] class default method proposal

2007-12-12 Thread Twan van Laarhoven

Simon Peyton-Jones wrote:

Concerning (b) here's a suggestion.  As now, require that every instance 
requires an instance declaration.  So, in the main example of 
http://haskell.org/haskellwiki/Class_system_extension_proposal, for a new data 
type T you'd write
instance Monad T where
  return = ...
  (>>=)  = ...

instance Functor T
instance Applicative T


Another alternative is to allow multiple classes in an instance declaration:

 instance (Monad T, Functor T, Applicative T) where
   return = ...
   (>>=)  = ...

The advantage is that this makes it more clear where the instances come 
from, especially if a class has multiple sub classes with different 
defaults. It also eliminates tricky issues with importing. Of course 
this needs some (albeit very little) new syntax.


I wrote a proposal a while ago, 
http://haskell.org/haskellwiki/Superclass_defaults


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


Re: [Haskell-cafe] New slogan for haskell.org

2007-12-12 Thread Bill Wood
On Wed, 2007-12-12 at 11:19 +, Andrew Coppin wrote:
   . . .
> ...and normal programmers care about the Fibonacci numbers because...?
> 
> Seriously, there are many, many programmers who don't even know what 
> Fibonacci numbers *are*. And even I can't think of a useful purpose for 
> them. (Unless you count Fibonacci codes?)

Knuth[1] pp. 417-419 discusses Fibonacci trees and Fibonacci search.
According to Knuth (and who am I to argue with him) Fibonacci search has
better average case running time than binary search, although worst case
can be slightly slower.

Cormen et. al.[2] devotes chapter 20 to Fibonacci heaps, which they say
are of primarily theoretical interest.

[1] Donald E. Knuth, The Art of Computer Programming, vol. 3, second
edition, Addison Wesley Longman (1998).

[2] Thomas H. Cormen, Charles E. Leiserson, Ronald L. Rivest and
Clifford Stein, Introduction to Algorithms, second edition, The MIT
Press (2001).

 -- Bill Wood

___
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.0pre1, the first prerelease for darcs 2

2007-12-12 Thread zooko

Dear darcs-devel folks:

Oh by the way, let me say: "HOORAY!".  I suspected that darcs 2 was  
never going to actually happen, and now I see that it *is* going to  
happen!  Way to go!  This breathes new life into the darcs project!


Regards,

Zooko

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


[Haskell-cafe] re: generics and grammars

2007-12-12 Thread Greg Meredith
Ken,

Thanks for the references! Have two-level types been applied to parser
generation?

Best wishes,

--greg

Greg Meredith <[EMAIL PROTECTED]> wrote in article
<[EMAIL PROTECTED]
> > in gmane.comp.lang.haskell.cafe:
> > Here is an idea so obvious that someone else must have already thought
> of it
> > and worked it all out. Consider the following grammar.
>
> Hello!
>
> If I understand your basic idea correctly, it is to split a recursive
> data type into two parts, a non-recursive type constructor and a
> knot-tying recursive type.  This idea has been christened "two-level
> types" by
>
>Tim Sheard and Emir Pasalic. 2004.  Two-level types and
>parameterized modules.  Journal of Functional Programming
>14(5):547-587.
>
> The idea dates earlier, to initial-algebra semantics and "functional
> programming with bananas and lenses":
>
>Mark P. Jones. 1995.  Functional programming with overloading and
>higher-order polymorphism.  In Advanced functional programming:
>1st international spring school on advanced functional programming
>techniques, ed. Johan Jeuring and Erik Meijer, 97-136.  Lecture
>Notes in Computer Science 925.
>
> http://web.cecs.pdx.edu/~mpj/pubs/springschool.html
>
>Erik Meijer, Maarten Fokkinga, and Ross Paterson. 1991.  Functional
>programming with bananas, lenses, envelopes and barbed wire.  In
>Functional programming languages and computer architecture: 5th
>conference, ed. John Hughes, 124-144.  Lecture Notes in Computer
>Science 523.
>
> http://research.microsoft.com/~emeijer/Papers/fpca91.pdf
>
> Cheers,
>Ken
>

Best wishes,

--greg

-- 
L.G. Meredith
Managing Partner
Biosimilarity LLC
505 N 72nd St
Seattle, WA 98103

+1 206.650.3740

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


[Haskell-cafe] eager/strict eval katas

2007-12-12 Thread Thomas Hartman
I'm trying to get a better handle on eager/strict eval in haskell, and a 
great way to do this is by building up from simple exercises to harder 
exercises.

So far I have

exercise 1) add the integers [1..10^6] 
  (stack overflows if you do a naive fold, as described on wiki)

exercise 2) find the first integer such that average of [1..n] is > [10^6] 

  (solution involves building an accum list of (average,listLength) 
tuples. again you can't do a naive fold due to stack overflow, but in this 
case even strict foldl' from data.list isn't "strict enough", I had to 
define my own custom fold to be strict on the tuples.)

anybody got other suggestions, or links to places where eager eval is 
required to solve simply stated problems? or exercises that demystify 
doing eager IO/eager whatever monad,  where that is required?

Also am I correct that the terms eager and strict can be used more or less 
interchangeably in this problem space?

Tired of this folk wisdom that haskell is only for the elite because 
getting around stack overflow from lazy eval is impossible to teach to 
newbies.

t.

---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Folding Integrals

2007-12-12 Thread Brent Yorgey
On Dec 12, 2007 10:36 AM, Arie Groeneveld <[EMAIL PROTECTED]> wrote:

> Reinier Lamers schreef:
> >
> > printint :: Int -> [Char]
> > printint = map chr . map (+0x30) . reverse . map (`mod` 10) .
> > takeWhile (>0) . iterate (`div`10)
> >
> Most of the time I use this:
>
> digits :: Integer -> [Int]
> digits = map (flip(-)48.ord) . show
>

One can also use Data.Char.digitToInt in place of (flip (-) 48 . ord).

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


Re: [Haskell-cafe] Folding Integrals

2007-12-12 Thread Arie Groeneveld
Reinier Lamers schreef:
>
> printint :: Int -> [Char]
> printint = map chr . map (+0x30) . reverse . map (`mod` 10) .
> takeWhile (>0) . iterate (`div`10)
>
Most of the time I use this:

digits :: Integer -> [Int]
digits = map (flip(-)48.ord) . show



Regards

=@@i

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


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-12 Thread Hans van Thiel
On Wed, 2007-12-12 at 16:27 +0100, Hans van Thiel wrote:
> [snip]
> > 
> > I fear those people can do vast amounts of damage. :(
> > 
> > When inept programming yields the wrong result, it is clear (even to the 
> > inept) that the program is bad.
> > 
> > When the result is correct but there are egregious time or space leaks, 
> > it is "clear" to everyone but the Haskell guru that it "must" be the 
> > programming language that is deficient, and will be duly flamed far and 
> > wide. This perception will be impossible to reverse when it gains 
> > traction (and nothing ever goes away on the Internet).
> > 
> > Seeming "deus ex machina" code changes (perhaps helpfully offered on 
> > haskell-cafe) to minimize or correct the undesirable runtime behavior 
> > appear even to many Haskellites to be black magic, accompanied by the 
> > runes of profile dumps (like knowing what generation 0 and generation 1 
> > garbage collection is).
> I see your point, but maybe there should be better analyzing tools then,
> as well as tutorials which explain that problem. 
> > 
> > >> Haskell is not a quick-and-dirty language but quite the opposite.  
> > >> Haskell’s 
> > >> unique selling propositions are features like type classes, higher order 
> > >> functions and lazy evaluation which make life easier in the long term.  
> > >> The 
> > >> downside of these features is that they might make life harder in the 
> > >> short 
> > >> term.
> > > I don't know. In a sense Haskell is easier than, for example, C, because
> > > the concept of a function definition is more natural that that of
> > > assignments and loops. The idea that x = 5; x = x + 7 makes sense
> > > requires a complete new way of thinking. OK, once you've been doing it
> > > for a few years switching back to x = 5 + 7 is hard.
> > 
> > I would limit that to say that *denotational* semantic intuition is easy 
> > to wield in Haskell. Operational semantic intuition is Haskell is very 
> > non-obvious to the imperative (and many functional) programmers.
> > 
> > Making matters worse, the first is an advantage well-hyped by 
> > functionistas, the second hurdle is rarely admitted to.
> I admit I don't understand this. 
> > 
> > >> That said, I definitely think that we should make learning the language 
> > >> as 
> > >> easy as possible.  But our ultimate goal should be to primarily show 
> > >> newcomers the Haskell way of problem solving, not how to emulate Python 
> > >> or 
> > >> Java programming in Haskell.
> > > Again, is there a danger of that happening?
> > 
> > Yes. Those absent the necessary humility to approach haskell-cafe with 
> > open mind and flame-retardant dialog will fall back on what they know: 
> > transliterated Java/Python with a morass of do blocks and IO monads, 
> > then (rightly) bash how "ugly" Haskell syntax is when used in this way.
> > 
> > This type of programmer looking to use Haskell casually should sign a 
> > "benefit of the doubt" contract whereby they assume that any runtime 
> > suboptimalities derive from their own coding and not from Haskell's 
> > defects. This is the innate assumption of the curious, the 
> > self-motivated, the clever. This is not typically the starting 
> > assumption of the "I'm an expert at Joe-imperative language" hacker who 
> > took 10 years to perfect his Java skills and expects thereby to jump to 
> > at least year 5 of Haskell without effort.
> But that person will be used to all the help he's gotten from the Java
> and/or Eclipse, with tutorials and reference implementations. Now he has
> to depend on dissertations and JFP articles for anything that's less
> than 10 years old, and a few helpful experts (much appreciated, I want
> to add) who are willing to spend the time to answer questions. 
> > 
> > I do strongly believe in stimulating the curiosity of all comers, just 
> > not in giving the false impression that a quick read-through of a few 
> > tutorials will let you write lightning-fast code, or know when to 
> > abandon [Char] for something more clever, or where to insert those bangs 
> > and fold left instead of right, and how ad hoc and parametric 
> > polymorphism differ, and what Rank-n and existential means (and why you 
> > can just pickle any object in Python but need to know a half dozen 
> > abstract things including who Peano was to do the same in Haskell), and 
> > what the heck an infinite type is, and on and on.
> It's possible, IMO, that Haskell requires a higher skill level in
> information science that the imperative languages. Many working
> programmers come from different backgrounds and are not experts in
> computer science. But, like a skyscraper is not built just by the
> architects, maybe those 'lower' skills have their place too. Maybe not,
> or not in Haskell. Could be, though I don't think so, myself.
> > Haskell has definitely been teaching me some serious humility! Possibly 
> > it is best that those not ready for that lesson might better stick with 
> > Py

[Haskell-cafe] ANNOUNCE: dataenc-0.10.1

2007-12-12 Thread Magnus Therning
Yesterday I uploaded a small update to the dataenc library:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/dataenc-0.10.1

Dependenciesbase
License LGPL
Copyright   Magnus Therning, 2007
Author  Magnus Therning
Maintainer  [EMAIL PROTECTED]
Exposed modules Codec.Binary.DataEncoding, Codec.Binary.Base16,
Codec.Binary.Base32Hex, Codec.Binary.Base32, Codec.Binary.Uu,
Codec.Binary.Base64Url, Codec.Binary.Base64

The visible change is the addition of a function, decode', that allows
lazier decoding  by shifting some responisility to the user.

/M

-- 
Magnus Therning (OpenPGP: 0xAB4DFBA4)
magnus@therning.org Jabber: magnus.therning@gmail.com
http://therning.org/magnus

Time is a great teacher, but unfortunately it kills all its pupils.
 -- Hector Louis Berlioz


pgpiPpbEtSEBY.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] class default method proposal

2007-12-12 Thread Yitzchak Gale

Simon Peyton-Jones wrote:

Given "instance C T where ...", for any method 'm' not
defined by "...":
for every class D of which C is a superclass
where there is an instance for (D T)
see if the instance gives a binding for 'm'
If this search finds exactly one binding, use it,
otherwise behave as now


A better rule would be:

If this search finds exactly one binding that is
minimal in the partial ordering defined by the
superclass hierarchy, use it, otherwise behave
as now.

Would that be much harder to implement?

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


[Haskell-cafe] ANNOUNCE: dataenc-0.10.1

2007-12-12 Thread Magnus Therning
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Yesterday I uploaded a small update to the dataenc library:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/dataenc-0.10.1

Dependenciesbase
License LGPL
Copyright   Magnus Therning, 2007
Author  Magnus Therning
Maintainer  [EMAIL PROTECTED]
Exposed modules Codec.Binary.DataEncoding, Codec.Binary.Base16,
Codec.Binary.Base32Hex, Codec.Binary.Base32, Codec.Binary.Uu,
Codec.Binary.Base64Url, Codec.Binary.Base64

The visible change is the addition of a function, decode', that allows
lazier decoding  by shifting some responisility to the user.

/M
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)

iD8DBQFHX9G+iMWTaatN+6QRAqclAKC6/BM7/e9jRAjVCMYYAZd7D/fAPACfe0sd
EfPoHw4HW7snU3RilejfIIY=
=XPUb
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New slogan for haskell.org

2007-12-12 Thread Reinier Lamers

Andrew Coppin wrote:

Yeah, we should probably set up a seperate list for this stuff... 


Perhaps you can use 
http://haskell.org/haskellwiki/?title=Talk:FrontpageDraft&action=edit ? 
That page is also a better place to fight your edit wars than the front 
page is.


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


Re: [Haskell-cafe] Re: New slogan for haskell.org

2007-12-12 Thread Henning Thielemann

On Wed, 12 Dec 2007, apfelmus wrote:

> gwern wrote:
> > Now, the Main Page on haskell.org is not protected, so I could just edit
> > in one of the better descriptions proposed, but as in my Wikipedia editing,
> > I like to have consensus especially for such visible changes.
>
> Hey, why has the front-page already been changed then? I don't like
> neither this nor the new slogan.

Edit war!

> In any case: it's not our task to convince others by means of an
> enterprisey formulation, people are free to choose. If they don't want
> it, so be it. We provide data points ("I have written a big but robust
> program, it's called ", "We have a FFI and its use is
> explained here", "look, this quicksort function is so beautiful") but
> judgment is what everybody has to do for himself.

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


Re: [Haskell-cafe] New slogan for haskell.org

2007-12-12 Thread Andrew Coppin

Emre Sahin wrote:

Why don't you let Haskell speak for itself?

Instead of putting such buzzwords nobody really understands (and
cares), put random problem descriptions and one-line solutions in
Haskell. Well known problems like Fibonacci, Quicksort, etc. may be
good candidates, even "add 1 to all elements of an Integer list" may
be. 
  


...and normal programmers care about the Fibonacci numbers because...?

Seriously, there are many, many programmers who don't even know what 
Fibonacci numbers *are*. And even I can't think of a useful purpose for 
them. (Unless you count Fibonacci codes?)


Quicksort is a well-used example, but several closely related sorting 
algorithms turn out to be fairly wordy in Haskell. It just so happens 
that [a very simple] quicksort is quite short.


I guess the question we've got to ask [hmm, we are repeating aren't we?] 
is who we're trying to attract.


Yeah, we should probably set up a seperate list for this stuff...

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


Re: [Haskell-cafe] Folding Integrals

2007-12-12 Thread Henning Thielemann

On Wed, 12 Dec 2007, Reinier Lamers wrote:

> Back in my Introduction to Functional Programming course, Daan Leijen
> demonstrated how to print integers in Haskell using function
> composition. Something along the lines of:
>
> printint :: Int -> [Char]
> printint = map chr . map (+0x30) . reverse . map (`mod` 10) . takeWhile
> (>0) . iterate (`div`10)

Nice, that is even without 'unfoldr'. It might be a bit better style to
use
   map (+ ord '0')
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: New slogan for haskell.org

2007-12-12 Thread apfelmus

gwern wrote:

Now, the Main Page on haskell.org is not protected, so I could just edit
in one of the better descriptions proposed, but as in my Wikipedia editing,
I like to have consensus especially for such visible changes.


Hey, why has the front-page already been changed then? I don't like 
neither this nor the new slogan.



Concerning what slogan should be on the front page, I prefer technical 
terms to buzzwords.


  myReadText = filter (not . buzzword)

In any case: it's not our task to convince others by means of an 
enterprisey formulation, people are free to choose. If they don't want 
it, so be it. We provide data points ("I have written a big but robust 
program, it's called ", "We have a FFI and its use is 
explained here", "look, this quicksort function is so beautiful") but 
judgment is what everybody has to do for himself.



Regards,
apfelmus

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


Re: [haskell-art] [Haskell-cafe] library to read/write audio files

2007-12-12 Thread Rohan Drape
hello john & stefan,

Stefan Kersten <[EMAIL PROTECTED]> writes:

> incidentally, i've been working on libsndfile bindings the last few
> days; here's the darcs repository:
> 
> http://darcs.k-hornz.de/cgi-bin/darcsweb.cgi?r=hsndfile;a=summary

excellent news! i have, _much_ more incidentally,
a simple minded NeXT/Au library, just adequate for 
communicating moderate size signals to scsynth.
darcs repository at:

http://slavepianos.org/rd/sw/hsc3-sf/

> it's not quite finished yet, but if you're interested you could have
> a look at the interface and make suggestions. maybe both projects
> could benefit from each other? i personally don't see much advantages
> in _not_ using libsndfile underneath ...

i agree, sound file formats are a deep
and dark well...

John Lato <[EMAIL PROTECTED]> writes:

> It's likely possible to wrap libsndfile in a functional
> interface, but that is beyond my current abilities.

perhaps once a working sndfile binding
is done experimenting with interface 
designs could be done on the haskell-art
list, i'd be interested in following
along with discussions.

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


Re: [Haskell-cafe] Folding Integrals

2007-12-12 Thread Reinier Lamers

Mattias Bengtsson wrote:


I found myself writing this for an Euler-problem:

 


digits :: Int -> [Int]
digits i | i < 10= [i]
| otherwise = i `mod` 10 : digits ( i `div` 10 )
   



And i realised it was quite some time ago (before this function) i had
actually written any explicitly recursive function. 

Back in my Introduction to Functional Programming course, Daan Leijen 
demonstrated how to print integers in Haskell using function 
composition. Something along the lines of:


printint :: Int -> [Char]
printint = map chr . map (+0x30) . reverse . map (`mod` 10) . takeWhile 
(>0) . iterate (`div`10)


You can easily translate a number to a list of digits without explicit 
recursion.


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


Re: [Haskell-cafe] New slogan for haskell.org

2007-12-12 Thread Michael Vanier

Bayley, Alistair wrote:
From: [EMAIL PROTECTED] 
[mailto:[EMAIL PROTECTED] On Behalf Of Derek Elkins



  

(Not directed at gwern in particular)

I have a better idea.  Let's decide to do nothing.  The 
benefits of this

approach are: 1) it takes zero effort to implement, 2) the number of
people who immediately give up on Haskell from reading that is, I
suspect, neglible (actually I suspect it is zero; I think the 
number of
people who actually read that at all is probably negligible), 
and 3) it
accomplishes the same end as debating endlessly while 
creating much less

list traffic.




Should we set up a haskell-marketing mailing list for people who still
have some passion (or merely stamina) for the discussion? Or is there a
lighter-weight way to take the discussion off-list/to another list?

Alistair
  


This is a great idea!  Other languages have advocacy mailing lists 
and/or newsgroups.  I think Haskell should have one too.  I know if 
there was one I'd be the first person not to subscribe ;-)


Mike, bored of these endless debates


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


RE: [Haskell-cafe] New slogan for haskell.org

2007-12-12 Thread Bayley, Alistair
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of Derek Elkins

> (Not directed at gwern in particular)
> 
> I have a better idea.  Let's decide to do nothing.  The 
> benefits of this
> approach are: 1) it takes zero effort to implement, 2) the number of
> people who immediately give up on Haskell from reading that is, I
> suspect, neglible (actually I suspect it is zero; I think the 
> number of
> people who actually read that at all is probably negligible), 
> and 3) it
> accomplishes the same end as debating endlessly while 
> creating much less
> list traffic.


Should we set up a haskell-marketing mailing list for people who still
have some passion (or merely stamina) for the discussion? Or is there a
lighter-weight way to take the discussion off-list/to another list?

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*

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


Re: [Haskell-cafe] New slogan for haskell.org

2007-12-12 Thread Henning Thielemann

On Wed, 12 Dec 2007, Emre Sahin wrote:

> > How do you think the description could be improved?
>
> Why don't you let Haskell speak for itself?
>
> Instead of putting such buzzwords nobody really understands (and
> cares), put random problem descriptions and one-line solutions in
> Haskell. Well known problems like Fibonacci, Quicksort, etc. may be
> good candidates, even "add 1 to all elements of an Integer list" may
> be.

Indeed, we are catched in a loop:
  http://www.haskell.org/pipermail/haskell-cafe/2007-November/035491.html

"When I want to judge a programming language I like to see a 'gallery', a
collection of beautiful programs."
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New slogan for haskell.org

2007-12-12 Thread Emre Sahin
> gwern0  <[EMAIL PROTECTED]> writes:

> If the reader is still interested and still takes Haskell
> seriously after puzzling over the foregoing, this would either
> be pointless or off-putting. Well, *of course* there are
> compilers for most computers. You aren't a serious
> general-purpose language in this day and age if there aren't
> compilers free for most computers. Such a line either tells the
> reader what they assume to be true, or strikes them as 'the lady
> doth protest too much, methinks'...

> So, the Haskell one uses more than twice as many technical
> terms, uses more off-putting ones, offers less information, does
> not reassure as Python's does that switching costs are not high,
> and so on.

> It needs to change.

> Now, the Main Page on haskell.org is not protected, so I could
> just edit in one of the better descriptions proposed, but as in
> my Wikipedia editing, I like to have consensus especially for
> such visible changes.

> How do you think the description could be improved?

Why don't you let Haskell speak for itself?

Instead of putting such buzzwords nobody really understands (and
cares), put random problem descriptions and one-line solutions in
Haskell. Well known problems like Fibonacci, Quicksort, etc. may be
good candidates, even "add 1 to all elements of an Integer list" may
be. 

First impressions of a language usually not by a slogan, I don't tell
my friends about Haskell saying "it's a statically typed, functional,
blah blah blah" language. Instead "the thing that you write with a
loop in C, I write in Haskell like this --oh, and it also has infinite
lists..."

I think Haskell code impresses me much more that those words. 

Emre







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


Re: [Haskell-cafe] Folding Integrals

2007-12-12 Thread Henning Thielemann

On Wed, 12 Dec 2007, Mattias Bengtsson wrote:

> I found myself writing this for an Euler-problem:
>
> > digits :: Int -> [Int]
> > digits i | i < 10= [i]
> >  | otherwise = i `mod` 10 : digits ( i `div` 10 )
>
> And i realised it was quite some time ago (before this function) i had
> actually written any explicitly recursive function. I managed to finish
> the Euler problem however and i was happy about that.
> However it frustrated me that i couldn't find a nice way to abstract
> away that explicit recursion but today i managed to! :)
> My first thought was that the solution probably was using some function
> like scanr, mapAccum or unfoldr to do it (especially the name of unfoldr
> made me think that it would be the solution).
> After abstracting my digits function i realised that it wasn't anything
> more than a fold over the Int type (treating the Int as a sequence of
> digits). "i `mod` 10" and "i `div` 10" would be nothing more than the
> head and tail functions (that corresponds to the (:) pattern matching).
>
> This is what i came up with finally:
> (I'm not 100% sure on the foldr- and foldl names though. Not sure if the
> semantics are correct, perhaps the function names should be switched?)
>
> > module FoldIntegral (foldr, foldl) where
> > import Prelude hiding (foldr,foldl,head,tail)
> >
> > head, tail :: Integral a => a -> a
> > head i = i `mod` 10
> > tail i = i `div` 10
> >
> > foldr :: Integral a => (a -> b -> b) -> b -> a -> b
> > foldr f z i
> > | i == 0= z
> > | otherwise = foldr f (h `f` z) t
> > where h = head i
> >   t = tail i
> >
> > foldl :: Integral b => (a -> b -> a) -> a -> b -> a
> > foldl f z i
> > | i == 0= z
> > | otherwise = (foldl f z t) `f` h
> > where h = head i
> >   t = tail i
>
> Which would make the digits function a one-liner:
>
> > digits = foldr (:) []
>
> I hope someone enjoys this.

Hm, I like the 'separation of concerncs' approach and thus I would plainly
convert the number to its digit representation and then apply List.foldr
on it. In your case the applied List.foldr is just 'id'. You can nicely
solve the problem with unfoldr. Why not considering List.unfoldr being the
'integral fold'?

toBase :: Integral a => a -> a -> [a]
toBase b =
   reverse . List.unfoldr (\n -> toMaybe (n>0) (swap (divMod n b)))

Implementing 'swap' and 'toMaybe' is left as an exercise. :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] New slogan for haskell.org

2007-12-12 Thread Bulat Ziganshin
Hello Steve,

Wednesday, December 12, 2007, 6:47:36 AM, you wrote:

>  * clear distinction between functional and imperative (is this
> really an advantage? almost everything I deal with is IO, network,
> and db related, what is left for purely functional?)

if your program has simple computations and mainly toss data in&out,
this is drawback. if you have complex algorithms which compute output
data from input ones, this is an advantage because Haskell allows to
write more complex algorithms easier and have better performance

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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