Re: [Haskell-cafe] generating Maybe

2007-11-07 Thread Yitzchak Gale
guarded = liftM2 ((>>) . guard)
toMaybe = (. return) . (>>) . guard

Regards,
lambdabot

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


[Haskell-cafe] type annotations elsewhere

2007-11-07 Thread Jason Dusek
Haskell offers a few different annotations, for example
strictness, to optimize programs. It would sure be nice if there
were a way to pull the annotations out and put them somewhere
else, enabling them, or not, at compile time. There could be
several different annotation sets, even -- you could try
different ones for different things.

However, there are some real practical difficulties here -- how
do you write an 'expresssion selector' to pair with the
annotation, in order to find its target? It may involve walking
the AST -- a fancy and potentially brittle way to go about
optimization (a brittle thing to start with!).

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


Re: [Haskell-cafe] About Fibonacci again...

2007-11-07 Thread Ross Paterson
On Thu, Nov 08, 2007 at 12:56:46AM +0100, [EMAIL PROTECTED] wrote:
> This nasty acquaintance of mine asked the students to write down a simple
> procedure which generates the sequence after the infinite number of units
> of time. Of course, any finite prefix of it.

rabbit = let rs = 0 : [x | r <- rs, x <- if r==0 then [1] else [1,0]] in 1 : rs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memory-mapped arrays? (IArray interfaces, slices, and so on)

2007-11-07 Thread Stefan O'Rear
On Wed, Nov 07, 2007 at 10:10:16PM +, Jules Bean wrote:
> Joel Reymont wrote:
>> Is there such a thing as memory-mapped arrays in GHC?
>
> In principle, there could be an IArray instance to memory-mapped files.
>
> (There could also be a mutable version, but just the IArray version would 
> be useful).
>
> I noticed just the other day that there are some 'obvious' IArray 
> constructors missing. It ought, for example, be possible to build a new 
> IArray from an old from a subset of the elements; a dimensional slice going 
> from an (Int,Int,Int) indexed array to (Int,Int), or a stride taking 'one 
> element in three' along each axis, etc.
>
> Annoyingly, it doesn't seem to be straightforward to make your own 
> instances of IArray, since the important methods aren't exported.

They are, from the undocumented module Data.Array.Base.

Stefan


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


Re: [Haskell-cafe] generating Maybe

2007-11-07 Thread Henning Thielemann

On Thu, 8 Nov 2007, Stuart Cook wrote:

> On 11/8/07, Tim Newsham <[EMAIL PROTECTED]> wrote:
> > Data.Maybe has functions for processing Maybe's but nothing useful
> > for creating maybe.  I think the following would be a very useful
> > addition, a guarded function:
> >
> >  guarded :: (a -> Bool) -> (a -> b) -> a -> Maybe b
> >  guarded p f x | p x   = Just (f x)
> >| otherwise = Nothing
> >
> > such a function in the std libs would make functions like "unfoldr"
> > more attractive -- uses of foldr nearly always encapsulate this
> > notion.
>
> How about this variant:
>
>   ensure :: (MonadPlus m) => (a -> Bool) -> a -> m a
>   ensure p x | p x   = return x
>  | otherwise = mzero
>
> Which as Jonathan points out, could also be written:
>
>   ensure p x = guard (p x) >> return x
>
> Now we can define
>
>   guarded p f x = ensure p x >>> fmap f

My 'toMaybe' is a specialisation of '\b x -> guard b >> return x'. This
let us return to the discussion, whether there should be a specialised
function, if there is a general function which does the same.
  http://www.haskell.org/haskellwiki/Simple_to_complex#Type_class_methods

I use 'toMaybe' a lot, because it allows partial application and I have
seen library code, where 'toMaybe' could have been used, but its author
didn't seem to know or like 'guard b >> return x'.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [OT] GHC uninstall on Linux

2007-11-07 Thread Stefan O'Rear
On Wed, Nov 07, 2007 at 10:41:53AM +0100, Dusan Kolar wrote:
> Hello all,
>
>  I use tar.bz2 binary distribution of GHC compiler as my distro does not 
> use any supported packaging system. Everything is fine, but... I want to 
> install the new version of the GHC compiler. Is there any (easy) way, how 
> to get information about what was copied and where during installation? 
> (./configure; make install) There seems to be no uninstall target in the 
> Makefile. :-( And I want to uninstall the previous version of the compiler.

You don't need to uninstall GHC, ever, except for disk space reasons.
You can easily have thirteen versions of GHC installed and happily
coexisting:

[EMAIL PROTECTED]:~$ ghci-6.
ghci-6.4.2 ghci-6.7   ghci-6.7.20070223
ghci-6.7.20070402  ghci-6.7.20070502  ghci-6.7.20070601
ghci-6.7.20070712  ghci-6.7.20070829  ghci-6.6.1
ghci-6.7.20070213  ghci-6.7.20070323  ghci-6.7.20070413
ghci-6.7.20070518  ghci-6.7.20070612  ghci-6.7.20070826

Stefan


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


Re: [Haskell-cafe] More on Fibonacci numbers

2007-11-07 Thread Stefan O'Rear
On Wed, Nov 07, 2007 at 10:30:30AM +0100, [EMAIL PROTECTED] wrote:
> [I changed the subject, so (hopefully) rare people who just follow the
> thread may miss it, but I couldn't look at the name of Fibonacci with
> two errors in it anymore...] 

People with real e-mail clients will still see it in the thread because
you still have In-reply-to and References set up correctly.  Changing
the topic in mid-thread isn't hazardous to us.

Stefan


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


Re: [Haskell-cafe] generating Maybe

2007-11-07 Thread Henning Thielemann

On Wed, 7 Nov 2007, Tim Newsham wrote:

> Data.Maybe has functions for processing Maybe's but nothing useful
> for creating maybe.  I think the following would be a very useful
> addition, a guarded function:
>
>  guarded :: (a -> Bool) -> (a -> b) -> a -> Maybe b
>  guarded p f x | p x   = Just (f x)
>| otherwise = Nothing
>
> such a function in the std libs would make functions like "unfoldr"
> more attractive -- uses of foldr nearly always encapsulate this
> notion.

This would be

guarded p f x = toMaybe (p x) (f x)

in terms of my beloved but already rejected 'toMaybe':
  http://www.haskell.org/pipermail/libraries/2004-July/002326.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] About Fibonacci again...

2007-11-07 Thread Bernie Pope


Is this what you are looking for:

   mrs = [0] : [1] : zipWith (++) (tail mrs) mrs

then you can get the one you want with:

   mrs !! index

given a suitable value for index


It seems I didn't read the question carefully - you want the infinite  
list.


You can recover the solution from mrs if you want, but its not very  
pretty:


infrs = [(mrs !! n) !! (n-1) | n <- [1..]]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fibbonachi numbers algorithm work TOO slow.

2007-11-07 Thread ajb

G'day all.

I wrote:


However, this is still an O(log n) algorithm, because that's the
complexity of raising-to-the-power-of.  And it's slower than the
simpler integer-only algorithms.


Quoting Henning Thielemann <[EMAIL PROTECTED]>:


You mean computing the matrix power of

/1 1\
\0 1/

?


I mean all of the most efficient ones.  The Gosper-Salamin algorithm
is the matrix power algorithm in disguise, more or less.

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


Re: [Haskell-cafe] About Fibonacci again...

2007-11-07 Thread Bernie Pope


On 08/11/2007, at 10:56 AM, [EMAIL PROTECTED] wrote:



rs 0 = [0]
rs 1 = [1]
rs n = rs (n-1) ++ rs (n-2)


Would somebody try to solve it, before I unveil the solution? It isn't
difficult.

Jerzy Karczmarczuk



Is this what you are looking for:

   mrs = [0] : [1] : zipWith (++) (tail mrs) mrs

then you can get the one you want with:

   mrs !! index

given a suitable value for index

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


Re: [Haskell-cafe] About Fibonacci again...

2007-11-07 Thread ajb

G'day all.

Quoting [EMAIL PROTECTED]:


zipWith (!!) (fix (([1]:).map(>>= \x->if x==0 then [1] else [1,0]))) [0..]


This was the shortest variant I could manage in the time allotted:

zipWith(!!)(fix(([1]:).map(>>= \x->1:[0|x==1])))[0..]

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


Re: [Haskell-cafe] About Fibonacci again...

2007-11-07 Thread ajb

G'day all.

Quoting [EMAIL PROTECTED]:


This nasty acquaintance of mine asked the students to write down a simple
procedure which generates the sequence after the infinite number of units
of time.


Cool problem!  "Simple" is, of course, in the eye of the beholder.

zipWith (!!) (fix (([1]:).map(>>= \x->if x==0 then [1] else [1,0]))) [0..]

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


Re: [Haskell-cafe] Standalone PNG module?

2007-11-07 Thread Cale Gibbard
On 06/11/2007, Peter Verswyvelen <[EMAIL PROTECTED]> wrote:
> I would like to load 32-bit images (RGB+alpha) for use with GLUT/OpenGL.
>
> I know GTK2HS has support for loading images, but does a standalone Haskell
> (wrapper) module exists for loading images?
>
> PNG or TGA would be enough for me.

The Imlib2 binding (called Imlib-0.1.0) on Hackage provides the
necessary tools to load and manipulate images in a variety of formats
including PNG, but it's under-documented and a little rough and
untested.

I'm currently working on a new version with proper documentation, a
number of bugfixes, and a somewhat more Haskellish interface.

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


Re: [Haskell-cafe] Should I step into a minefield? / Writing a trading studio in Haskell

2007-11-07 Thread Manuel M T Chakravarty

Joel Reymont:
I need to pick among the usual list of suspects for a commercial  
product that I'm writing. The suspects are OCaml, Haskell and Lisp  
and the product is a trading studio. My idea is to write something  
like TradeStation [1] or NinjaTrader, only for the Mac.


It would be quite nifty to use SPJ's financial combinator approach  
and, for example, embed Yi (Haskell editor).


One of the key features of the product would be the ability to model  
your trading logic using a trading DSL. I'm thinking that this DSL  
could well be Haskell but I'm concerned about stepping into a  
minefield.


I will need to embed GHC into the app, for example, and I understand  
that the GHC API does not offer unloading of code at the moment. I  
would prefer not to bundle GHC separately so I don't think the hs- 
plugins approach would work for me. Maybe I'm mistaken.


I don't see how embedding GHC into the app is any more or less  
complicated than bundling it with the app.  Hence, I'd actually start  
with hs-plugins and see whether that's sufficient.  If hs-plugins is  
sufficient for your purpose, it's surely simpler (by virtue of a much  
smaller API) and does code unloading just fine.




Most of all, I'm concerned that my users will need to face the error  
reports from GHC and could get tripped by laziness, i.e. write  
something that would make the app run out of memory. Off the top of  
my head I can't figure out a way to limit what my users can do  
without analyzing the Haskell AST within the GHC API and complaining  
if necessary.


Error message are always an issue with embedded DSLs, independent of  
whether you use Haskell, OCaml or Lisp.  The same holds for running  
out of memory and for inadvertently coding unbound recursion or  
loops.  An *E*DSL comes with the full power of the host language for  
better or worse.


You can sandbox the EDSL code to varying degrees to shield the end- 
user from such problems; eg, use asynchronous exceptions to spot and  
terminate long running computations and use AST inspection to prevent  
the use of certain language features.  Incidentally, hs-plugins  
already has some support for this, based on haskell-src (again that's  
a simpler API then the GHC API).


With errors messages you can add some post-processing before  
presenting them to the user.


One possible approach is to run with an EDSL for starters, sandbox the  
execution of EDSL components, and post-process error messages.  This  
will get you a prototype quickly with which you can collect some  
experience.  If you find that, eg, the error messages are too often  
too cryptic then you can turn you EDSL into a DSL by writing a parser  
for the DSL in parsec, do static checks and error reporting on the DSL  
AST, and finally translate the DSL AST into the corresponding EDSL  
code.  The last step is barely more than pretty printing and enables  
you to reuse almost all the effort that you put into the EDSL  
development.


In this way you get the quick prototyping advantage of the EDSL  
without prematurely committing yourself to either an EDSL or DSL  
approach.




Can someone with experience in offering a Haskell DSL to their users  
please comment?


Notice that I'm not even mentioning being concerned with the  
unpredictable effects of laziness. There's probably a reason why  
Jane St Capital is using OCaml instead of Haskell. I'm not going to  
play in that league but my knee-jerk reaction is to use OCaml or  
Lisp and avoid laziness altogether. I just can't see how laziness  
can help in processing real-time price data.


I strongly suspect the reason that Jane St Capital is using OCaml is  
because the people who started the coding already knew OCaml and stuck  
with what they know and love.  Laziness, in particular, and Haskell,  
in general, is going to help you with the EDSL (it's no coincidence  
that most EDSL work was done in Haskell).


Otherwise, I don't see why laziness is going to be a big obstacle.   
Lennart has just recently nicely demonstrate that Haskell performance  
even in numeric applications is no worse than OCaml's:   In fact, in this benchmark, Haskell performance turned out to be  
better.


A second data point is xmonad which is often commended for its  
responsiveness, in a domain where the competition is using C.


Manuel

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


Re: [Haskell-cafe] About Fibonacci again...

2007-11-07 Thread Stuart Cook
On 11/8/07, [EMAIL PROTECTED]
<[EMAIL PROTECTED]> wrote:
> Would somebody try to solve it, before I unveil the solution? It isn't
> difficult.

*** SPOILER WARNING ***

Here's my attempt, which I wrote without peeking:

  let fibs' = 1 : 2 : zipWith (+) fibs' (tail fibs')
  rabbits = 1 : 0 : (fibs' >>= flip take rabbits)

It can be golfed down to a single line without difficulty.

Is there a nicer solution?


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


[Haskell-cafe] Flymake Haskell

2007-11-07 Thread Daisuke IKEGAMI
Hello emacsen users, 

Here is a setting to check your Haskell code /on-the-fly/ 
with 'flymake-mode'.

  (require 'flymake)
  
  ;; flymake for Haskell
  (defun flymake-Haskell-init ()
(flymake-simple-make-init-impl
  'flymake-create-temp-with-folder-structure nil nil
  buffer-file-name
  'flymake-get-Haskell-cmdline))
  (defun flymake-get-Haskell-cmdline (source base-dir)
(list "ghc" (list "--make" (concat "-i" base-dir) source)))
  (push '(".+\\.hs$" flymake-Haskell-init)
flymake-allowed-file-name-masks)
  (push '(".+\\.lhs$" flymake-Haskell-init)
flymake-allowed-file-name-masks)
  (push '("^\\(.*\\):\\([0-9]+\\):\\([0-9]+\\): \\(.*\\)$" 1 2 3 4)
flymake-err-line-patterns)

The 'flymake-mode' has been developed at http://flymake.sourceforge.net/
Emacs22 has this mode already.

dons recommends to me at IRC to write this code into the wiki, however, 
I don't know where we should put the snippet.

You can watch a short demo at the following blog:
  http://madscientist.jp/~ikegami/diary/20071108.html#p01

I have some complaints though it works:
  - it's slow (hmm)
  - error and warning seems not distinguished
  (we may have to modify 'flymake-err-line-patterns')
Any comment is appreciated.

Best regards,
Ike

P.S.
I like vi-clone, such as vim, too. ;-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] XMonad architecture paper?

2007-11-07 Thread Galchin Vasili
Kind thanks, Don.

Vasya

On Nov 7, 2007 9:40 PM, Don Stewart <[EMAIL PROTECTED]> wrote:

> vigalchin:
> >Hello,
> >
> >  I was watching Simon Peyton-Jones' video on "A Taste of
> Haskell"
> >Part 1. .. Is there any paper discussing the architecture? I am not
> afraid
> >to read code but sometimes a paper overview is good ...
> >
> >Regards, Vasya
>
>
> There's one quick paper describing the general approach:
>
>
> http://www.cse.unsw.edu.au/~dons/papers/haskell51d-stewart.pdf
>
> The internal architecture is also covered in the accompanying talk:
>
>
> http://www.ludd.ltu.se/~pj/hw2007/xmonad.mov
>
> and in an early series of blog articles,
>
>
> http://cgi.cse.unsw.edu.au/~dons/blog/2007/05/01#xmonad_part1_model
>
> http://cgi.cse.unsw.edu.au/~dons/blog/2007/05/17#xmonad_part1b_zipper
>
> http://cgi.cse.unsw.edu.au/~dons/blog/2007/06/02#xmonad-0.2
>
> Cheers,
>  Don
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] XMonad architecture paper?

2007-11-07 Thread Don Stewart
vigalchin:
>Hello,
> 
>  I was watching Simon Peyton-Jones' video on "A Taste of Haskell"
>Part 1. .. Is there any paper discussing the architecture? I am not afraid
>to read code but sometimes a paper overview is good ...
> 
>Regards, Vasya


There's one quick paper describing the general approach:

http://www.cse.unsw.edu.au/~dons/papers/haskell51d-stewart.pdf

The internal architecture is also covered in the accompanying talk:

http://www.ludd.ltu.se/~pj/hw2007/xmonad.mov

and in an early series of blog articles,

http://cgi.cse.unsw.edu.au/~dons/blog/2007/05/01#xmonad_part1_model
http://cgi.cse.unsw.edu.au/~dons/blog/2007/05/17#xmonad_part1b_zipper
http://cgi.cse.unsw.edu.au/~dons/blog/2007/06/02#xmonad-0.2

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


Re: [Haskell-cafe] FP design

2007-11-07 Thread Levi Stephen

Tim Docker wrote:

levi.stephen wrote:

My concern (which may be inexperience ;) ) is with the monads here
though. What if I hadn't seen that the IO monad (or any other Monad)
was going to be necessary in the type signatures?



You'd have some refactoring to do :-) But actually, it's not possible
to create an interface that works this way without using some monad,
as the interface relies on side-effects. A pure interface would have
to look something like:



I agree in this case the monad use is clear. Practically it might a case of if a 
monad is needed, it's either obvious, or its introduction indicates a refactor 
being a good thing and will lead to a better design.


Levi


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


Re: [Haskell-cafe] Fibbonachi numbers algorithm work TOO slow.

2007-11-07 Thread Guido Genzone
Hi,

sorry my english is not the best :(
2007/11/5, gitulyar <[EMAIL PROTECTED]>:
>
> Please help me. I'm new in Haskell programming, but wrote some things in
> Scheme. I make so function:
>
> fib 1 = 1
> fib 2 = 2
> fib n = fib (n-1) + fib (n-2)
>
> And when I call "fib 30" it works about 5 seconds. As for me it's really TOO
> SLOW.

Because the scheme is Inefficient
If you define fib like this:

dfib 0 = (1,1)
dfib n = let (a,b) = dfib (n-1) in (b, b+a)
-- dfib n = (fib n, fib (n+1)) this explote lazy evaluation

fib n = fst (dfib n)

With this definition the lazy evaluation calculate only one fib 1, one
fib 2..etc.


>
> Tell me please if I have something missed, maybe some compiler
> (interpretaitor) options (I use ghc 6.6.1).

The scheme is bad, no ghci.

> P.S. As I understand function "fib n" should be calculated one time. For
> example if I call "fib 30" compiler builds tree in which call function "fib
> 28" 2 times and so on. But as for lazy calculation principle it should be
> calculated just ones and then it's value is used for all other calls of this
> function with the same argument. But it seems that this principle doesn't
> work in this algorithm.

If you have this:
mult:Int->Int
mult x = x + x + x
---
mult (fib 20)

=  
(fib 20)  + (fib 20)  + (fib 20)

=< By lazy evaluation, this is equal..>
x + x + x
where x = fib 20
---
In this case fib 20 calculate only the first call, no three times.

But fib 20

fib 20
=  < Definition>
fib 19 + fib 18

Then the calulate of fib 19 and fib 18 individualy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] FP design

2007-11-07 Thread Derek Elkins
On Thu, 2007-11-08 at 13:21 +1100, Tim Docker wrote:
> levi.stephen wrote:
> > My concern (which may be inexperience ;) ) is with the monads here
> > though. What if I hadn't seen that the IO monad (or any other Monad)
> > was going to be necessary in the type signatures?
> 
> 
> You'd have some refactoring to do :-) 

http://www.cs.kent.ac.uk/projects/refactor-fp/catalogue/Monadification1.html


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


[Haskell-cafe] XMonad architecture paper?

2007-11-07 Thread Galchin Vasili
Hello,

  I was watching Simon Peyton-Jones' video on "A Taste of Haskell" Part
1. .. Is there any paper discussing the architecture? I am not afraid to
read code but sometimes a paper overview is good ...

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


RE: [Haskell-cafe] FP design

2007-11-07 Thread Tim Docker

levi.stephen wrote:
> My concern (which may be inexperience ;) ) is with the monads here
> though. What if I hadn't seen that the IO monad (or any other Monad)
> was going to be necessary in the type signatures?


You'd have some refactoring to do :-) But actually, it's not possible
to create an interface that works this way without using some monad,
as the interface relies on side-effects. A pure interface would have
to look something like:

data ObjectStore = ObjectStore {
save :: Object -> (ID,ObjectStore),
retrieve :: ID -> Maybe Object,
retrieveByName :: Maybe Object
}

(ie the save method would have to return a new object store).

Instead of using IO, you could have parameterised the store over the
monad:

data ObjectStore m = ObjectStore {
save :: Object -> m ID,
retrieve :: ID -> m (Maybe Object),
retrieveByName :: String -> m (Maybe Object)
}

but given your planned use, this may well be over-abstraction.

Tim

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


Re: [Haskell-cafe] About Fibonacci again...

2007-11-07 Thread Alfonso Acosta
How about this,

infiniteRS :: [Int]
infiniteRS = let acum a1 a2 = a2 ++ acum (a1++a2) a1 in 1 : acum [1] [0]

it certainly fits in one line but it's not really elegant
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FP design

2007-11-07 Thread Levi Stephen

Tim Docker wrote:

levi.stephen wrote:

I have similar questions about Haskell abstracting away
implementations behind interfaces as well. I have become
used to an approach where I will not worry about
databases/persistence when beginning. I will create an
interface to a database layer (e.g., save(object), retrieve(id),
findByName(name)) etc., and an implementation that uses in
memory collections to begin with. Later I will replace this with
database calls.



How does this type of approach work in Haskell?
or what is the Haskell way to achieve this?



If OO is a good approach for a problem, it's straightforward to model
it in haskell. If you plan to access an external DB in any case, then
the interface will involve the IO Monad. Something along the lines
of:

data Object
data ID

data ObjectStore = ObjectStore {
save :: Object -> IO ID,
retrieve :: IO -> IO (Maybe Object),
retrieveByName :: String -> IO (Maybe Object)
}

createMemoryStore :: IO ObjectStore
connnectExternalStore :: ConnectionParams -> IO ObjectStore

Tim 



Thanks for the example. I keep forgetting that I can have use functions like 
this. I keep having data types made up of just values and/or type classes. I 
should probably use types like the above more often.


My concern (which may be inexperience ;) ) is with the monads here though. What 
if I hadn't seen that the IO monad (or any other Monad) was going to be 
necessary in the type signatures?


Levi

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


Re: [Haskell-cafe] FP design

2007-11-07 Thread Donn Cave
On Wed, 7 Nov 2007, Justin Bailey wrote:

> > So I'm the one user in a thousand that will want to provide my own I/O
> > functions, for example.  In the old world, I guess I would be looking
> > for some extended API where my I/O functions are parameters to the "open"
> > or "init" function, and the IMAP functions take over from there.  In a
> > more pure functional oriented model, could it be an extended API that
> > exposes the IMAP functionality as operations on data, and leaves it to
> > me to deal with the I/O?
> 
> I believe a typeclass could solve this for you. The typeclass member
> functions serve as your interface definition. For example, say "auth"
> was a member function. Then you could implement instances which
> authorized using NTLM, HTTP Basic, etc.
> 
> It's similar to how you'd do the same thing in java with interfaces, in fact.

That auth function is not a bad example, because there are a number of
cross dependencies along the way to authentication.  When you try to design
a generic API that will supports all kinds of authentication, you end up 
with some abominable tangle like SASL, and even then you end up punting
on some of them (where does your SSL certificate go?)  Some of the 
underlying protocols involve more than one round trip (Kerberos), others
need access to the SSL state, etc.

What I'm running up the flagpole here, so to speak, is the notion that
if at a larger scale you write your application protocol engine so that
it just operates on data and doesn't need to take control over "the wire",
that might give you a thinner API, and fewer problems to solve via typeclass.

Donn Cave, [EMAIL PROTECTED]

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


[Haskell-cafe] Should I step into a minefield? / Writing a trading studio in Haskell

2007-11-07 Thread Joel Reymont
I need to pick among the usual list of suspects for a commercial  
product that I'm writing. The suspects are OCaml, Haskell and Lisp and  
the product is a trading studio. My idea is to write something like  
TradeStation [1] or NinjaTrader, only for the Mac.


It would be quite nifty to use SPJ's financial combinator approach  
and, for example, embed Yi (Haskell editor).


One of the key features of the product would be the ability to model  
your trading logic using a trading DSL. I'm thinking that this DSL  
could well be Haskell but I'm concerned about stepping into a minefield.


I will need to embed GHC into the app, for example, and I understand  
that the GHC API does not offer unloading of code at the moment. I  
would prefer not to bundle GHC separately so I don't think the hs- 
plugins approach would work for me. Maybe I'm mistaken.


Most of all, I'm concerned that my users will need to face the error  
reports from GHC and could get tripped by laziness, i.e. write  
something that would make the app run out of memory. Off the top of my  
head I can't figure out a way to limit what my users can do without  
analyzing the Haskell AST within the GHC API and complaining if  
necessary.


Can someone with experience in offering a Haskell DSL to their users  
please comment?


Notice that I'm not even mentioning being concerned with the  
unpredictable effects of laziness. There's probably a reason why Jane  
St Capital is using OCaml instead of Haskell. I'm not going to play in  
that league but my knee-jerk reaction is to use OCaml or Lisp and  
avoid laziness altogether. I just can't see how laziness can help in  
processing real-time price data.


Thanks, Joel

[1] http://www.tradestation.com/default_2.shtm
[2] http://www.ninjatrader.com/webnew/index.htm

--
http://wagerlabs.com





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


Re: [Haskell-cafe] Re: FP design

2007-11-07 Thread Emil Axelsson

You mean:

  Jonh Hughes. The Design of a Pretty-printing Library.

:)

/ Emil



On 2007-11-07 05:16, apfelmus wrote:

  Paul Hudak. The Design of a Pretty-printing Library.



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


[Haskell-cafe] Re: HOC is dead! Long live HOC!

2007-11-07 Thread Joel Reymont


On Nov 7, 2007, at 9:57 PM, Wolfgang Thaller wrote:

One big piece of information we need that is currently missing from  
the BridgeSupport files is which declaration comes form which header  
file. HOC's module structure currently follows Apple's .h files, and  
we need the module system for resolving naming ambiguities.


Why not assume that each class goes into a file of its own and all  
classes in a directory matching the name of the framework? You will  
then have AppKit/NSWindow.hs, etc. I think this is how it's done right  
now. Constants and such can be gathered in AppKit/AppKit.hs.


I haven't had a chance recently to do a thorough comparison of  
different open source hosting providers, so I have no opinion on  
this one. So if you want to invest time in maintaining HOC, and you  
want to maintain it on GoogleCode, then so be it. How do I give my  
permission?



Either you or Andre should have received an email from Google Code.  
Please add wagerlabs to the project admins on SourceForge and I'll  
look into it.


Thanks, Joel

--
http://wagerlabs.com





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


[Haskell-cafe] About Fibonacci again...

2007-11-07 Thread jerzy . karczmarczuk

Don't shoot me...

The last exchange with Andrew Bromage made me recall a homework which was
given to some students by a particularly nasty teacher I happen to know.

The question is to generate the whole infinite Rabbit Sequence in one
shot (co-recursive, selbstverständlich).

The Rabbit Sequence:
1,0,1,1,0,1,0,1,1,0,1,1,0,1,0,1,1,0,1,0,1,1,0,1,1,0,1,0,1,1,0,1,1,0,...
may be obtained in two ways.

A.
1. Begin with one *young* rabbit: 0.
2. In one unit of time a young rabbit grows, becomes *old*: 1.
3. In one unit of time an old rabbit has an offspring, transmutes into [1,0]
 (Yes, the rewriting order is meaningful).

The evelution continues...
So, after three units we have: 1 0 1. After four: 10110. Then 10110101. Etc.

B.
The n-th instance fulfils the recurrence

rs 0 = [0]
rs 1 = [1]
rs n = rs (n-1) ++ rs (n-2)
===

That's it, you see now what is the relation between the Rabbit Sequence
and Fibonacci.

This nasty acquaintance of mine asked the students to write down a simple
procedure which generates the sequence after the infinite number of units
of time. Of course, any finite prefix of it.

The pedagogical result was a disaster. Some students began to work, but
then the teacher went crazy and demanded the solution (in Haskell) as
a one-liner. Just one line, and standard Prelude functions, nothing more.
So, the students thought that if it is a one liner, it must be stupid, and
abandoned this exercise.

Would somebody try to solve it, before I unveil the solution? It isn't
difficult.

Jerzy Karczmarczuk


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


Re: [Haskell-cafe] Building Haskell stuff on Windows

2007-11-07 Thread Duncan Coutts
On Wed, 2007-11-07 at 23:20 +0100, Arthur van Leeuwen wrote:

> With kind regards, Arthur. (Who will surely do more Windows development
>   with Haskell soonish)

Good! We need more developers to help us with windows stuff. We're in
this difficult situation where half of our users use Windows (according
to the GHC survey) but the vast majority of developers use Linux,
several use Mac OS and approximately 3 use Windows as their primary
platform. So supporting Windows becomes difficult.

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


RE: [Haskell-cafe] FP design

2007-11-07 Thread Tim Docker

levi.stephen wrote:
> I have similar questions about Haskell abstracting away
> implementations behind interfaces as well. I have become
> used to an approach where I will not worry about
> databases/persistence when beginning. I will create an
> interface to a database layer (e.g., save(object), retrieve(id),
> findByName(name)) etc., and an implementation that uses in
> memory collections to begin with. Later I will replace this with
> database calls.

> How does this type of approach work in Haskell?
> or what is the Haskell way to achieve this?


If OO is a good approach for a problem, it's straightforward to model
it in haskell. If you plan to access an external DB in any case, then
the interface will involve the IO Monad. Something along the lines
of:

data Object
data ID

data ObjectStore = ObjectStore {
save :: Object -> IO ID,
retrieve :: IO -> IO (Maybe Object),
retrieveByName :: String -> IO (Maybe Object)
}

createMemoryStore :: IO ObjectStore
connnectExternalStore :: ConnectionParams -> IO ObjectStore

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


Re: [Haskell-cafe] FP design

2007-11-07 Thread Levi Stephen

Donn Cave wrote:


But in the specific matter I'm wrestling with, the Java library's OOP
model is, to its credit, allowing me to do some things.  I'm using their
standard LDAP client library, but swapping in my own function to read
X509 certificates for the SSL.  Actually, swapping in my own SSL socket
"implementation", which in my case just calls the standard library SSL
socket implementation to do most of the work.

Now it's not like I can't imagine it working better - it may be a little
fragile, for one thing - but I have wondered what facilities a Haskell
design could have drawn on to de-couple implementation components like that.
Let's say you download an IMAP mail client library, and look to see if it
can operate on a UNIX pipe;  on an SSL socket;  authenticate with GSSAPI
Kerberos 5  -- when none of those things are supported out of the box.
(As I have needed, and done, all three of those with the standard Python
IMAP library module.)  You may also want its I/O operations to integrate
with some dispatching core, for a GUI.  But of course you also want the
basic interface to be simple in this area - the IMAP protocol itself is
complicated enough!



I have similar questions about Haskell abstracting away implementations behind
interfaces as well. I have become used to an approach where I will not worry
about databases/persistence when beginning. I will create an interface to a
database layer (e.g., save(object), retrieve(id), findByName(name)) etc., and an
implementation that uses in memory collections to begin with. Later I will
replace this with database calls.

This also helps in my current project as we support multiple databases. If
findByName requires different SQL on different databases it's easy to have a
different implementation used at run time.

How does this type of approach work in Haskell? or what is the Haskell way to
achieve this?

Levi


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


Re: [Haskell-cafe] FP design

2007-11-07 Thread Levi Stephen

Bulat Ziganshin wrote:

Hello Andrew,

Tuesday, November 6, 2007, 10:55:58 PM, you wrote:


for me, abstraction is anything that i want to be an abstraction. i
just write code in the close-to-natural language and it becomes
Haskell program when appropriate syntax applied.



Well, in my experience, figuring out just the right abstractions to use


i don't think about abstractions, just using top-down approach. for
me, FP benefit is that when you see that some two things are similar -
you can factor out this similarity. in OOP, you should translate it
into some class interface, in Haskell you just define parameterized
code/data and it works. selection of good abstractions based on these
two criteria: 1) factoring out common parts and 2) existence of
natural description of the factored part. if i don't see natural
description, i can slightly change the factored part




This thread sums up some of my thoughts pretty well. I'm coming from OOP where I
was getting comfortable and was confident of spotting appropriate abstractions.

Now I have to learn how to select the appropriate abstractions in Haskell. e.g.,
selecting between a variant type or type class is often a tricky one for me.

It is good to hear that people are having success with the code, refactor
duplication, repeat process. I have used this in OOP as well and the path it
takes is interesting to compare with initial design thoughts. Again, it's just
choosing the best way to remove this duplication :)

Levi

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


Re: [Haskell-cafe] generating Maybe

2007-11-07 Thread Stuart Cook
On 11/8/07, Tim Newsham <[EMAIL PROTECTED]> wrote:
> Data.Maybe has functions for processing Maybe's but nothing useful
> for creating maybe.  I think the following would be a very useful
> addition, a guarded function:
>
>  guarded :: (a -> Bool) -> (a -> b) -> a -> Maybe b
>  guarded p f x | p x   = Just (f x)
>| otherwise = Nothing
>
> such a function in the std libs would make functions like "unfoldr"
> more attractive -- uses of foldr nearly always encapsulate this
> notion.

How about this variant:

  ensure :: (MonadPlus m) => (a -> Bool) -> a -> m a
  ensure p x | p x   = return x
 | otherwise = mzero

Which as Jonathan points out, could also be written:

  ensure p x = guard (p x) >> return x

Now we can define

  guarded p f x = ensure p x >>> fmap f


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


Re: [Haskell-cafe] FP design

2007-11-07 Thread Justin Bailey
> So I'm the one user in a thousand that will want to provide my own I/O
> functions, for example.  In the old world, I guess I would be looking
> for some extended API where my I/O functions are parameters to the "open"
> or "init" function, and the IMAP functions take over from there.  In a
> more pure functional oriented model, could it be an extended API that
> exposes the IMAP functionality as operations on data, and leaves it to
> me to deal with the I/O?

I believe a typeclass could solve this for you. The typeclass member
functions serve as your interface definition. For example, say "auth"
was a member function. Then you could implement instances which
authorized using NTLM, HTTP Basic, etc.

It's similar to how you'd do the same thing in java with interfaces, in fact.

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


Re: [Haskell-cafe] Re: Doubly-linked zipper list w/ insert implementation

2007-11-07 Thread Justin Bailey
On Nov 7, 2007 10:16 AM, apfelmus <[EMAIL PROTECTED]> wrote:

> Do you really need to realize the cycle by sharing? I mean, sharing
> doesn't go well with insertion / updates / deletion since each of these
> operations breaks it and needs to restore it everywhere. In other words,
> your  insert  takes O(n) time. I'd simply drop the sharing and use two
> double ended queues (or something like that) instead

Very good point, and much easier to implement with Data.Sequence to
boot. All that circular programming made my brain hurt.

Thanks for your feedback.

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


Re: [Haskell-cafe] ByteString search code available in easy-to-digest form

2007-11-07 Thread Justin Bailey
On Nov 7, 2007 2:21 PM, Bryan O'Sullivan <[EMAIL PROTECTED]> wrote:
> Chris mentioned that he did, but I haven't had time to write anything
> benchmarky yet.

I used the attached program to benchmark the various functions against
"endo.dna"[1], a 7 MB file that came with this year's ICFP contest. It
appends a pattern that occurs nowhere in the file to the end of that
file and then searches for it. Strict and lazy bytestring searches
using KMP are performed, plus a search using the existing bytestring
searches and using a List.

You'll have to change the import from Data.ByteString.KMP for it to
compile but otherwise it should work out of the box..

Justin

[1] http://www.icfpcontest.org/endo.zip
module Main

where

import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString as S
import qualified Data.ByteString.KMP as K
import Data.List (isInfixOf)

main =
  do
testStr <- readFile "endo.dna" >>= \s -> return $ s ++ searchStr
lazyTestStr <- L.readFile "endo.dna" >>= \s -> return $ L.append s lazySearchStr
strictTestStr <- S.readFile "endo.dna" >>= \s -> return $ S.append s strictSearchStr
putStrLn $ ("(kmpMatchLL): " ++ show ({-# SCC "kmpMatchLL" #-} K.kmpMatchLL lazySearchStr lazyTestStr))
putStrLn $ ("(kmpMatchSS): " ++ show ({-# SCC "main_kmpMatchSS" #-} K.kmpMatchSS strictSearchStr strictTestStr))
putStrLn $ ("(strict): " ++ show ({-# SCC "main_findStrict" #-} S.findSubstring strictSearchStr strictTestStr))
putStrLn $ ("(naive): " ++ show ({-# SCC "main_findSubstringLazy" #-} findSubstringLazy lazySearchStr lazyTestStr))
putStrLn $ ("(list) found: " ++ show ({-# SCC "main_findList" #-} searchStr `isInfixOf` testStr))
putStrLn "Done!"


searchStr = "IFPIFPIFPIFPIFPIFPIFPIFP"
lazySearchStr = toLazyBS searchStr
strictSearchStr = toStrictBS searchStr

toLazyBS = L.pack . map (toEnum . fromEnum) 
toStrictBS = S.pack . map (toEnum . fromEnum)

findSubstringLazy :: L.ByteString -> L.ByteString -> Maybe Int
findSubstringLazy !test !big = go big 0
where
go !s !n | test `L.isPrefixOf` s = Just n
 | L.null s  = Nothing
 | otherwise = go (L.tail s) (n+1)

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


Re: [Haskell-cafe] ByteString search code available in easy-to-digest form

2007-11-07 Thread Bryan O'Sullivan

Don Stewart wrote:


Do we have any benchmarks, for say, 1G files, versus linear, naive
(strict) search?


Chris mentioned that he did, but I haven't had time to write anything 
benchmarky yet.


http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ByteString search code available in easy-to-digest form

2007-11-07 Thread Don Stewart
bos:
> I've packaged up the fast Boyer-Moore and Knuth-Morris-Pratt code that 
> Chris Kuklewicz posted a few months ago:
> 
>   http://article.gmane.org/gmane.comp.lang.haskell.libraries/7363
> 
> The consensus at the time was that the code was not ready for rolling 
> into the bytestring package, but now it's easy to install and start 
> working with.
> 
> API docs:
> 
>   http://darcs.serpentine.com/stringsearch/dist/doc/html/stringsearch/
> 
> Patches against the darcs repo welcome:
> 
>   darcs get http://darcs.serpentine.com/stringsearch
> 
> Credit to Justin Bailey, Daniel Fischer, and Chris Kuklewicz for their 
> hard work.
> 
> (Currently only tested against GHC 6.6.1, FYI.)

Do we have any benchmarks, for say, 1G files, versus linear, naive
(strict) search?

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


Re: [Haskell-cafe] Building Haskell stuff on Windows

2007-11-07 Thread Arthur van Leeuwen


On 7-nov-2007, at 17:43, Neil Mitchell wrote:


Hi Arthur,

The correct steps to take are:

1) install GHC from the windows installer - trivial
2) install Gtk2hs from the windows installer

Unfortunately Gtk2hs hasn't been updated to work with GHC 6.8.1, so
step 2 will fail. The person who is going to do this is Duncan. He
usually breaks down and does this once people start complaining on the
mailing list.


- Installed MinGW 5.1.3


Generally, if you have to install MinGW you can pretty much guarantee
that something somewhere is going to go wrong - not enough people test
this route to make it reliable.


Actually, the MinGW/MSYS thing was also necessary for another package  
that
I needed, plus, the GTK2Hs build instructions explicitly state that  
you need it.


Oh, and I *definitely* liked the vim and bash that I got from it. No  
cmd.exe

and it's odd syntax for me! :)


Windows and Haskell is not a well travelled route, but if you stray of
the cuddly installer packages, it gets even worse.


But it shouldn't. Really it shouldn't. Even though Windows is not my
preferred platform, it is by no means different enough to warrant such
additional complexity. Plus, GHC is developed at Microsoft, and the
currently most featureful Haskell IDE is on Windows...

With kind regards, Arthur. (Who will surely do more Windows development
with Haskell soonish)

--

  /\/ |   [EMAIL PROTECTED]   | Work like you don't need  
the money
/__\  /  | A friend is someone with whom | Love like you have never  
been hurt
/\/__ | you can dare to be yourself   | Dance like there's nobody  
watching




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


Re: [Haskell-cafe] Memory-mapped arrays? (IArray interfaces, slices, and so on)

2007-11-07 Thread Jules Bean

Joel Reymont wrote:

Is there such a thing as memory-mapped arrays in GHC?


In principle, there could be an IArray instance to memory-mapped files.

(There could also be a mutable version, but just the IArray version 
would be useful).


I noticed just the other day that there are some 'obvious' IArray 
constructors missing. It ought, for example, be possible to build a new 
IArray from an old from a subset of the elements; a dimensional slice 
going from an (Int,Int,Int) indexed array to (Int,Int), or a stride 
taking 'one element in three' along each axis, etc.


Annoyingly, it doesn't seem to be straightforward to make your own 
instances of IArray, since the important methods aren't exported.


I think there is real scope for some expansion here.


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


[Haskell-cafe] Re: HOC is dead! Long live HOC!

2007-11-07 Thread Wolfgang Thaller

On 7-Nov-07, at 5:14 PM, Joel Reymont wrote:

BridgeSupport [1] is new functionality in Leopard that makes the  
current Haskell Objective-C bindings (HOC) obsolete (almost).


"Almost" here means about five to ten percent of the code ;-). If the  
BridgeSupport files really contain all the information we need, then  
we can indeed drop the Objective-C parsing code from HOC and use a  
BridgeSupport parser instead.
Unfortunately, that parser itself is less than 500 lines out of 7000  
(in the HOC library and the InterfaceGenerator taken together). But  
the sheer beauty of having someone else maintain the parser for us  
should make it worthwhile.


One big piece of information we need that is currently missing from  
the BridgeSupport files is which declaration comes form which header  
file. HOC's module structure currently follows Apple's .h files, and  
we need the module system for resolving naming ambiguities. So either  
we need to change that, or we need to get the information from  
elsewhere. There might be other small things missing, we'll have to  
carefully look at the details.


[...] It's no longer necessary to bundle libffi with HOC either  
since Leopard comes with a much improved version.


Yes, that's one great little addition to Mac OS X :-).

I hereby propose to close up the old HOC project on SourceForge and  
set up a new one at GoogleCode. I already did this but GoogleCode  
noticed the SF project and is now waiting for permission from  
Wolfgang and Andre.


I haven't had a chance recently to do a thorough comparison of  
different open source hosting providers, so I have no opinion on this  
one. So if you want to invest time in maintaining HOC, and you want to  
maintain it on GoogleCode, then so be it. How do I give my permission?



Cheers,

Wolfgang

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


Re: [Haskell-cafe] Memory-mapped arrays?

2007-11-07 Thread Don Stewart
joelr1:
> Is there such a thing as memory-mapped arrays in GHC?
> 
> I'm looking for something that would let me memory-map a file of  
> floats and access it as an array.
> 

There's a commented out mmapFile for ByteString in Data.ByteString's
source. Use that, and then extract the ForeignPtr from the resulting 
ByteString, and castPtr it to a Ptr CFloat, then you're in business.

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


[Haskell-cafe] Memory-mapped arrays?

2007-11-07 Thread Joel Reymont

Is there such a thing as memory-mapped arrays in GHC?

I'm looking for something that would let me memory-map a file of  
floats and access it as an array.


Thanks, Joel

--
http://wagerlabs.com





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


Re: [Haskell-cafe] generating Maybe

2007-11-07 Thread Jonathan Cast

On 7 Nov 2007, at 12:40 PM, Tim Newsham wrote:


Data.Maybe has functions for processing Maybe's but nothing useful
for creating maybe.  I think the following would be a very useful
addition, a guarded function:

guarded :: (a -> Bool) -> (a -> b) -> a -> Maybe b
guarded p f x | p x   = Just (f x)
  | otherwise = Nothing

such a function in the std libs would make functions like "unfoldr"
more attractive -- uses of foldr nearly always encapsulate this
notion.


guarded p f x = guard (p x) >> f x

which I would expect looks even better in practice:

[1..10] = unfoldr (\ n -> guard (n <= 10) >> return (n, n + 1)) 1

vs.

[1..10] = unfoldr (guarded (<= 10) (\ n -> return (n, n + 1)) 1

For example.

jcc

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


Re: [Haskell-cafe] Screen scraping with an interactive process: Buffering problems?

2007-11-07 Thread David Benbennick
On Nov 7, 2007 5:12 AM, Denis Bueno <[EMAIL PROTECTED]> wrote:
> Ironically, this was my first problem.  First of all, I don't think I
> want the semi-closed state -- I want to be able to read and write
> freely later on (I may be misunderstanding semi-closed, however).

I don't think that makes sense.  First of all, pout is only the stdout
of the program, so you can only read from it, not write to it.  And
once you do hGetContents, you have read all the data that will ever
exist on that handle, so there's nothing to read from it "later on".

> Second, when I used this approach, after the hGetContents call I did
> the regexp matching, and the program hung during matching.

That's not surprising.  You first match for "Proof succeeded".  So if
the proof failed, the matcher will go past the "attempt has failed"
message, looking for a later succeeded.  Which means it will block
waiting for more output from your subprocess, which will never produce
more output until you give it another request.

Assuming that each call to ACL2 produces exactly one of either "Proof
succeeded" or "attempt has failed", you can get a list of results like
this (where aclOutput :: String is the result of hGetContents):

let results = map (\l -> if l == "Proof succeeded" then True else
False) $ filter (\l -> elem l ["Proof succeeded", "attempt has
failed"]) $ lines aclOutput

Then results :: [Bool], and results !! n is True if the nth call
succeeded.  Just make sure not to inspect results !! n until after
making the nth call to ACL2, or it will block.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type/class question: toString

2007-11-07 Thread Nicholas Messenger
If you're willing to have an extra Typeable constraint, this does what you want:

> import Data.Typeable (Typeable, cast)
> import Data.Maybe (fromMaybe)
>
> toString :: (Show a, Typeable a) => a -> String
> toString x = fromMaybe (show x) (cast x)

*Main> toString "blah"
"blah"
*Main> toString 1
"1"
*Main> toString (Just 0.5)
"Just 0.5"

So Strings are just cast into the result.  Non-strings become Nothing,
which fromMaybe turns into (show x).

--
Nicholas Messenger
[EMAIL PROTECTED]


On Nov 6, 2007 4:23 PM, Graham Fawcett <[EMAIL PROTECTED]> wrote:
> On Nov 6, 2007 3:29 PM, Graham Fawcett <[EMAIL PROTECTED]> wrote:
> > On Nov 6, 2007 2:21 PM, Jeff Polakow <[EMAIL PROTECTED]> wrote:
> > >   Have you tried using -fglasgow-exts? That should enable all ghc
> > > extensions.
>
> If anyone's interested, I had best results when I added the flag
> -fallow-incoherent-instances. Without it, I could not handle numbers
> without declaring their types, e.g. 'toString (33 :: Int)' would work,
> but 'toString 33' would lead to:
>
> Ambiguous type variable `t' in the constraints:
>   `ToString t'
> arising from use of `toString'
> at /home/graham/tmp/ToString.hs:13:15-25
>   `Num t'
> arising from the literal `33'
> at /home/graham/tmp/ToString.hs:13:24-25
> Probable fix: add a type signature that fixes these type variable(s)
>
> Here's the code I ended up with.
>
> {-# OPTIONS -fglasgow-exts -fallow-overlapping-instances #-}
> {-# OPTIONS -fallow-incoherent-instances -fallow-undecidable-instances #-}
>
> module ToString (ToString(..)) where
>
> class Show a => ToString a  where toString :: a -> String
> instance ToString Stringwhere toString s = s
> instance (Show a) => ToString a where toString s = show s
>
>
> Thanks to all who responded; I learned a lot from this.
>
> Graham
>
> ___
> 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] FP design

2007-11-07 Thread Jonathan Cast


On 7 Nov 2007, at 11:26 AM, Donn Cave wrote:


I have been working on a little Java project lately at work, by way
of an introduction to the language, and naturally I often have cause
to regret that it isn't Haskell instead.

But in the specific matter I'm wrestling with, the Java library's OOP
model is, to its credit, allowing me to do some things.  I'm using  
their

standard LDAP client library, but swapping in my own function to read
X509 certificates for the SSL.  Actually, swapping in my own SSL  
socket

"implementation", which in my case just calls the standard library SSL
socket implementation to do most of the work.

Now it's not like I can't imagine it working better - it may be a  
little

fragile, for one thing - but I have wondered what facilities a Haskell
design could have drawn on to de-couple implementation components  
like that.
Let's say you download an IMAP mail client library, and look to see  
if it
can operate on a UNIX pipe;  on an SSL socket;  authenticate with  
GSSAPI

Kerberos 5  -- when none of those things are supported out of the box.
(As I have needed, and done, all three of those with the standard  
Python
IMAP library module.)  You may also want its I/O operations to  
integrate
with some dispatching core, for a GUI.  But of course you also want  
the
basic interface to be simple in this area - the IMAP protocol  
itself is

complicated enough!

So I'm the one user in a thousand that will want to provide my own I/O
functions, for example.  In the old world, I guess I would be looking
for some extended API where my I/O functions are parameters to the  
"open"

or "init" function, and the IMAP functions take over from there.  In a
more pure functional oriented model, could it be an extended API that
exposes the IMAP functionality as operations on data, and leaves it to
me to deal with the I/O?


That would be my ideal: protocol layers implemented as functions over  
lazy lists.  Naturally, those compose very cleanly (at least in a  
pipeline-like fashion.  Combining that with running protocol modules  
in serial (e.g., using some standard initial authentication protocol,  
then switching to something else) is a bit more complicated (but  
certainly very doable)).


jcc

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


[Haskell-cafe] ByteString search code available in easy-to-digest form

2007-11-07 Thread Bryan O'Sullivan
I've packaged up the fast Boyer-Moore and Knuth-Morris-Pratt code that 
Chris Kuklewicz posted a few months ago:


  http://article.gmane.org/gmane.comp.lang.haskell.libraries/7363

The consensus at the time was that the code was not ready for rolling 
into the bytestring package, but now it's easy to install and start 
working with.


API docs:

  http://darcs.serpentine.com/stringsearch/dist/doc/html/stringsearch/

Patches against the darcs repo welcome:

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

Credit to Justin Bailey, Daniel Fischer, and Chris Kuklewicz for their 
hard work.


(Currently only tested against GHC 6.6.1, FYI.)

http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: infinity 0.3

2007-11-07 Thread Austin Seipp
After quite a bit of work and other such stuff, I pretty much totally
rewrote my previous IRC bot and instead updated it from v0.1 to v0.3.
You may wonder where 0.2 went; so do I.

This is basically an entire rewrite (I threw the first one out.) Now
all code can be dynamically hot-swapped via the techniques described
in Don's Yi paper. This can happen across multiple servers and as
servers are taken down and the like. All code swaps near flawlessly,
and even after the initial mechanism was working, the bot ran for
quite a while with a good amount of success.

I didn't plan to release it in this state, however, with it's
dependencies on hs-plugins (which is ghc 6.6 only as of right now,)
and my recent installation of GHC 6.8.1, I can't work on it because
apparently although both versions appear to be installed, it seems as
if ghc-6.6.1 is picking up configuration and package info from 6.8.1
(and therefore ghc-6.6.1 tells me it can't find packages like irc and
plugins, although 'ghc-pkg-6.6.1 list' obviously shows they exist.) I
also can't work on this on my OpenBSD box which only has 6.6.1, due to
some arcane error with hs-plugins (can't find the __errno symbol, I
believe.) So because of that, development is temporarily stalled and
if you want to test it, you'll need 6.6.1 installed and working
properly.
I don't think this would have been *too* far from the actual, official
release though. At this point I only planned minor tweaks and its
release was pretty inevitable anyway.

You can get a tarball from hackage:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/infinity-0.3

The darcs repository is here:

http://code.haskell.org/infinity/src/

Personally, it was real fun to work on this thing. I wrote almost all
the base code for plugins, and for the Net and Monitor to use before
the bot ever made its first connection, and a lot of it seemed to just
piece together really easily. The code is undeniably cleaner and more
extensible than the previous 0.1 code, but I still feel by most
standards it's somewhat cluttered, so if anybody here would like to
give any comments just from reading the source, that'd be pretty
awesome.

Until I can continue to work on it (whether hs-plugins is available
for 6.8.1 or I get another box with 6.6.1 installed,) this will be
considered the stable version by my definition, and all patches are of
course welcome. darcs send austin at youareinferior dot net. Criticism
is advised.

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


[Haskell-cafe] generating Maybe

2007-11-07 Thread Tim Newsham

Data.Maybe has functions for processing Maybe's but nothing useful
for creating maybe.  I think the following would be a very useful
addition, a guarded function:

guarded :: (a -> Bool) -> (a -> b) -> a -> Maybe b
guarded p f x | p x   = Just (f x)
  | otherwise = Nothing

such a function in the std libs would make functions like "unfoldr"
more attractive -- uses of foldr nearly always encapsulate this
notion.

Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fibbonachi numbers algorithm work TOO slow.

2007-11-07 Thread Dan Piponi
There are some nice formulae for the Fibonacci numbers that relate f_m
to values f_n where n is around m/2. This leads to a tolerably fast
recursive algorithm.

Here's a complete implementation:
fib 0 = 0
fib 1 = 1
fib 2 = 1
fib m | even m = let n = m `div` 2 in fib n*(fib (n-1)+fib (n+1))
  | otherwise  = let n = (m-1) `div` 2 in fib n^2+fib (n+1)^2

Combine that with the NaturalTree structure here:
http://www.haskell.org/haskellwiki/Memoization and it seems to run
faster than Mathematica's built in Fibonacci function taking about 3
seconds to compute fib (10^7) on my PC.
--
Dan

On 11/7/07, Henning Thielemann <[EMAIL PROTECTED]> wrote:
>
> On Tue, 6 Nov 2007 [EMAIL PROTECTED] wrote:
>
> > However, this is still an O(log n) algorithm, because that's the
> > complexity of raising-to-the-power-of.  And it's slower than the
> > simpler integer-only algorithms.
>
> You mean computing the matrix power of
>
> /1 1\
> \0 1/
>
> ?
> ___
> 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] Fibbonachi numbers algorithm work TOO slow.

2007-11-07 Thread Lennart Augustsson
When discussing the complexity of fib don't forget that integer
operations for bignums are no longer constant time.

  -- Lennart

On Nov 7, 2007 6:55 AM, Henning Thielemann
<[EMAIL PROTECTED]> wrote:
>
> On Tue, 6 Nov 2007 [EMAIL PROTECTED] wrote:
>
> > However, this is still an O(log n) algorithm, because that's the
> > complexity of raising-to-the-power-of.  And it's slower than the
> > simpler integer-only algorithms.
>
> You mean computing the matrix power of
>
> /1 1\
> \0 1/
>
>
> ?
> ___
> 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] FP design

2007-11-07 Thread Donn Cave
I have been working on a little Java project lately at work, by way
of an introduction to the language, and naturally I often have cause
to regret that it isn't Haskell instead.

But in the specific matter I'm wrestling with, the Java library's OOP
model is, to its credit, allowing me to do some things.  I'm using their
standard LDAP client library, but swapping in my own function to read
X509 certificates for the SSL.  Actually, swapping in my own SSL socket
"implementation", which in my case just calls the standard library SSL
socket implementation to do most of the work.

Now it's not like I can't imagine it working better - it may be a little
fragile, for one thing - but I have wondered what facilities a Haskell
design could have drawn on to de-couple implementation components like that.
Let's say you download an IMAP mail client library, and look to see if it
can operate on a UNIX pipe;  on an SSL socket;  authenticate with GSSAPI
Kerberos 5  -- when none of those things are supported out of the box.
(As I have needed, and done, all three of those with the standard Python
IMAP library module.)  You may also want its I/O operations to integrate
with some dispatching core, for a GUI.  But of course you also want the
basic interface to be simple in this area - the IMAP protocol itself is
complicated enough!

So I'm the one user in a thousand that will want to provide my own I/O
functions, for example.  In the old world, I guess I would be looking
for some extended API where my I/O functions are parameters to the "open"
or "init" function, and the IMAP functions take over from there.  In a
more pure functional oriented model, could it be an extended API that
exposes the IMAP functionality as operations on data, and leaves it to
me to deal with the I/O?

Donn Cave, [EMAIL PROTECTED]

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


[Haskell-cafe] Re: Doubly-linked zipper list w/ insert implementation

2007-11-07 Thread apfelmus

Justin Bailey wrote:

The other day I decided to implement a ring buffer with a current
element (i.e. a doubly-linked zipper list). In order to allow inserts
(and, in the future, deletes and updates), I have a special sentinel
element called "Join" in the structure. When inserting, I find the
join first, insert and then rebuild the buffer using circular
programming techniques. This also allows the buffer to be converted
back to a list. The current element can be changed by rotating right
or left, which never fails. Rotating n positions takes n steps.

I'm posting it here for comments and feedback. How could the structure
be smarter? Would storing a unique ID with each element make more
sense? Any comments on the space behavior under insert and rotates? I
wanted to "maximize" sharing. Thanks in advance.


Do you really need to realize the cycle by sharing? I mean, sharing 
doesn't go well with insertion / updates / deletion since each of these 
operations breaks it and needs to restore it everywhere. In other words, 
your  insert  takes O(n) time. I'd simply drop the sharing and use two 
double ended queues (or something like that) instead


  data Ring a = Ring (DeQueue a) a (DeQueue a)

-- pseudo-code missing lots of cases. I want views!
  left (Ring (l' :< ls :> l) x (r :< rs :> r')) =
Ring (ls :> l :> x) r (rs :> r' :> l')

This way, you can implement update operations in O(1) time instead of 
O(n). With a fancy random access queue like Data.Sequence , you can even 
have rotations like  rotL xs n  in O(log n) time.


(I keep mixing up the meaning of  rotL  and  rotR , does L push the 
current element to the left or does it rotate the ring clockwise?)



Regards,
apfelmus

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


Re: [Haskell-cafe] Standalone PNG module?

2007-11-07 Thread Tim Newsham

Peter Verswyvelen wrote:


I would like to load 32-bit images (RGB+alpha) for use with GLUT/OpenGL.


I know GTK2HS has support for loading images, but does a standalone Haskell 
(wrapper) module exists for loading images?


See the message "PNG files" by Tim Newsham, sent to haskell-cafe on the 30th 
of october.


The code I wrote is onthe wiki at:
http://www.haskell.org/haskellwiki/Library/PNG

However, it does not load files, it generates files, and monochrome ones
at that.  Loading files would be slightly harder since you'd have
to support (or at least test for) more options, but the format isn't
that complicated.


Reinier


Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Building Haskell stuff on Windows

2007-11-07 Thread Duncan Coutts
On Wed, 2007-11-07 at 17:34 +0100, Arthur van Leeuwen wrote:
> Hello all,
> 
> maybe I'm just not used enough to Windows, but let me explain my woes of
> today. It seems to me to be *much* too hard to get a full install of  
> GHC + GTK2Hs
> going on Windows, going from the idea that I want the currently  
> released stable versions of everything.

It is far too hard. For one thing the released tarball does not build
with ghc-6.8.1. That's why I'm working on a new point release.

> So, this is the way I progressed (from a clean Windows install):
>   - Installed MinGW 5.1.3
>   - Installed MSYS 1.0.10
>   - Installed GHC 6.8.1
>   - edit /etc/fstab in MSYS to correctly bind MinGW
>   - Installed gtk-dev-2.10.11-win32-1
>   - Downloaded gtk2hs-0.9.12.tar.gz
>   - cd /d/haskell/gtk2hs-0.9.12
>   - ran configure
>   - discovered I needed happy (this was not documented!)

Hmm, that's not right. The gtk2hs tarballs come with the lexer and
parser pre generated. The configure script checks for alex and happy but
does not (should not) fail if they're not present and the pre-generated
code is present. I certainly build on a windows server where alex and
happy are not installed.

>   - Downloaded happy-1.17.tar.gz
>   - unpacked, configured, built, installed
>   - ran configure for gtk2hs
>   - discovered I needed alex (this was not documented!)
>   - Downloaded alex-2.10.tar.gz
>   - Setup.lhs of alex-2.10 did not compile due importing  
> Distribution.Simple(compilerPath)
>   - Installed darcs
>   - darcs got alex development tree
>   - Setup.lhs of alex-2.10 compiled
>   - building alex-2.10 failed due to wishing an existing alex
>   - broke down and downloaded alex-2.10 binaries
>   - installed alex-2.10 next to happy in C:\Program Files\Haskell\bin
>   - ran configure for gtk2hs
>   - ran make
>   - discovered alex should not be in C:\Program Files as make breaks  
> on paths with embedded spaces...
>   - copied C:\Program Files\Haskell to C:\Haskell and modified $PATH
>   - reran configure for gtk2hs
>   - ran make
>   - discovered gtk2hs 0.9.12 hides 'containers'

That's the bit where we notice gtk2hs-0.9.12 was released well before
ghc-6.8.1 and thus does not work with it. Every non-trivial package
needs updating in various minor ways to work with ghc-6.8.1.

>   - broke down and darcs got gtk2hs development tree
>   - installed automake
>   - ran autoreconf

I've never managed to get automake to work on windows. I always generate
tarballs under linux and then build them on windows. This also allows me
to avoid installing happy/alex on windows.

>   - discovered automake for MSYS 1.0.10 is too old
>   - installed automake-1.9
>   - ran aclocal-1.9
>   - ran autoconf
>   - ran configure
>   - discovered I need to explicitly add GTK libs to aclocal
>   - ran aclocal-1.9 -I with GTK library path
>   - ran autoconf

Wow, it actually worked did it?

>   - ran configure for gtk2hs
>   - ran make

Oh good, glad that bit works :-)

>   - complained on IRC
>   - ran make install

I expect it fails in the package registration stage right? Yes, I never
do that, I always build images for the installer and never install
direct, so that path is probably bit-rotted.

>   - sighed deeply
> 
> Ofcourse, on complaining I learned that hackage contains alex 2.2,  
> rather than 2.10, but that is not apparent from the alex webpages. It
> seems to me that much of this is way too hard to figure out...
> figuring out the dependency graph should not be necessary, as the
> developers should know what parts go into their code!

Yes it is too hard. In the case of Gtk2Hs I think it'll be easier when
Gtk2hs changes to use Cabal for it's build system. Then it will not
require mingw/msys which should improve things dramatically.

> Furthermore, as much as I applaud hackage, it is not ready for use,  
> as it does not afford things you might want, such as searching for
> latest (stable) releases of packages.

Yes, there is nothing to distinguish "latest" from "stable". With
sufficiently accurate deps I think this is solvable, and perhaps the
ability to tweak the deps after a package is released (to tighten them
if they were too lax for example).

> Plus, it is still not the default go-to place for many things.

That's changing reasonably quickly. Especially if you put pressure on
maintainers of packages that you get from anywhere other than hackage.
Repeat the mantra "if it's not on hackage it doesn't exist".

> Maybe developers that decide to put their most recent versions on
> hackage could document that on the main webpages of their code? (I've
> ran into this with FileManip as well, not just with Alex).

Good idea.

So the good news for you is that the windows installer for Gtk2Hs (which
will be compatible with ghc-6.6.1 and 6.8.1) will be released in a day
or so. 

Re: [Haskell-cafe] Building Haskell stuff on Windows

2007-11-07 Thread Neil Mitchell
Hi Arthur,

The correct steps to take are:

1) install GHC from the windows installer - trivial
2) install Gtk2hs from the windows installer

Unfortunately Gtk2hs hasn't been updated to work with GHC 6.8.1, so
step 2 will fail. The person who is going to do this is Duncan. He
usually breaks down and does this once people start complaining on the
mailing list.

> - Installed MinGW 5.1.3

Generally, if you have to install MinGW you can pretty much guarantee
that something somewhere is going to go wrong - not enough people test
this route to make it reliable.

Windows and Haskell is not a well travelled route, but if you stray of
the cuddly installer packages, it gets even worse.

Thanks

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


[Haskell-cafe] Building Haskell stuff on Windows

2007-11-07 Thread Arthur van Leeuwen

Hello all,

maybe I'm just not used enough to Windows, but let me explain my woes of
today. It seems to me to be *much* too hard to get a full install of  
GHC + GTK2Hs
going on Windows, going from the idea that I want the currently  
released stable

versions of everything.

So, this is the way I progressed (from a clean Windows install):
- Installed MinGW 5.1.3
- Installed MSYS 1.0.10
- Installed GHC 6.8.1
- edit /etc/fstab in MSYS to correctly bind MinGW
- Installed gtk-dev-2.10.11-win32-1
- Downloaded gtk2hs-0.9.12.tar.gz
- cd /d/haskell/gtk2hs-0.9.12
- ran configure
- discovered I needed happy (this was not documented!)
- Downloaded happy-1.17.tar.gz
- unpacked, configured, built, installed
- ran configure for gtk2hs
- discovered I needed alex (this was not documented!)
- Downloaded alex-2.10.tar.gz
	- Setup.lhs of alex-2.10 did not compile due importing  
Distribution.Simple(compilerPath)

- Installed darcs
- darcs got alex development tree
- Setup.lhs of alex-2.10 compiled
- building alex-2.10 failed due to wishing an existing alex
- broke down and downloaded alex-2.10 binaries
- installed alex-2.10 next to happy in C:\Program Files\Haskell\bin
- ran configure for gtk2hs
- ran make
	- discovered alex should not be in C:\Program Files as make breaks  
on paths with embedded spaces...

- copied C:\Program Files\Haskell to C:\Haskell and modified $PATH
- reran configure for gtk2hs
- ran make
- discovered gtk2hs 0.9.12 hides 'containers'
- broke down and darcs got gtk2hs development tree
- installed automake
- ran autoreconf
- discovered automake for MSYS 1.0.10 is too old
- installed automake-1.9
- ran aclocal-1.9
- ran autoconf
- ran configure
- discovered I need to explicitly add GTK libs to aclocal
- ran aclocal-1.9 -I with GTK library path
- ran autoconf
- ran configure for gtk2hs
- ran make
- complained on IRC
- ran make install
- sighed deeply

Ofcourse, on complaining I learned that hackage contains alex 2.2,  
rather than 2.10,
but that is not apparent from the alex webpages. It seems to me that  
much of this
is way too hard to figure out... figuring out the dependency graph  
should not be

necessary, as the developers should know what parts go into their code!

Furthermore, as much as I applaud hackage, it is not ready for use,  
as it does not
afford things you might want, such as searching for latest (stable)  
releases of packages.
Plus, it is still not the default go-to place for many things. Maybe  
developers that decide
to put their most recent versions on hackage could document that on  
the main webpages
of their code? (I've ran into this with FileManip as well, not just  
with Alex).


With kind regards, Arthur.

--

  /\/ |   [EMAIL PROTECTED]   | Work like you don't need  
the money
/__\  /  | A friend is someone with whom | Love like you have never  
been hurt
/\/__ | you can dare to be yourself   | Dance like there's nobody  
watching




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


[Haskell-cafe] HOC is dead! Long live HOC!

2007-11-07 Thread Joel Reymont
BridgeSupport [1] is new functionality in Leopard that makes the  
current Haskell Objective-C bindings (HOC) obsolete (almost).


---
The metadata is intended to be a resource for use beyond bridging.  
Most frameworks on the system provide two chunks of XML BridgeSupport  
metadata; succinct and full.


The succinct version contains all of the metadata not provided by the  
Objective-C runtime (which provides about 80% of what is necessary to  
do full fidelity calls in / out of Objective-C via libffi).


The full version contains just that, the full metadata required to  
describe the APIs of the framework, including all the bits that could  
be gleaned at runtime.

---

BridgeSupport makes it unnecessary to parse Cocoa headers since all  
the required data is right there in plain XML [2]. It's no longer  
necessary to bundle libffi with HOC either since Leopard comes with a  
much improved version.


I hereby propose to close up the old HOC project on SourceForge and  
set up a new one at GoogleCode. I already did this but GoogleCode  
noticed the SF project and is now waiting for permission from Wolfgang  
and Andre.


Thanks, Joel

[1] http://www.friday.com/bbum/2007/10/27/pyobjc-20-pyobjc-in-leopard/
[2] /System/Library/Frameworks/AppKit.framework/Resources/ 
BridgeSupport/AppKitFull.bridgesupport


--
http://wagerlabs.com





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


[Haskell-cafe] Doubly-linked zipper list w/ insert implementation

2007-11-07 Thread Justin Bailey
The other day I decided to implement a ring buffer with a current
element (i.e. a doubly-linked zipper list). In order to allow inserts
(and, in the future, deletes and updates), I have a special sentinel
element called "Join" in the structure. When inserting, I find the
join first, insert and then rebuild the buffer using circular
programming techniques. This also allows the buffer to be converted
back to a list. The current element can be changed by rotating right
or left, which never fails. Rotating n positions takes n steps.

I'm posting it here for comments and feedback. How could the structure
be smarter? Would storing a unique ID with each element make more
sense? Any comments on the space behavior under insert and rotates? I
wanted to "maximize" sharing. Thanks in advance.

Justin

p.s. The original motivation for writing this was to model cellular
automata. The CA world is "circular", so that got me thinking about a
structure that made connecting the ends easy to do.

-- cut here ---

module Ring (Ring, create, insert, current, rotR, rotL, toListL, toListR)
-- Thanks to Keith Wansbrough  for his posting describing a doubly-linked list
-- in Haskell for inspiration here.
-- 
-- http://groups.google.com/group/comp.lang.functional/msg/8c65fdd16f7e91e1
where

import Data.List (foldl')
-- For testing
import Test.QuickCheck
import Control.Monad (replicateM_)
import System.Random (randomRIO)
import System.Environment (getArgs)

data Ring a = Ring (Ring a) a (Ring a) | Join (Ring a) (Ring a)

instance (Show a) => Show (Ring a) where
  show r = "{" ++ show' (findLeftOfJoin r)
where
  show' (Join _ _) = "}"
  show' (Ring l v _)
| isJoin l = show v ++ show' l
| otherwise = show v ++ "," ++ show' l

create v =
  let me = Ring join v join
  join = Join me me
  in me

insert r a =
let (left, right) = insert' left right start a
start = findLeftOfJoin r
in left
  where
insert' left right (Join _ _) val =
  let last = Ring join val right
  join = Join left last
  in (last, join)
insert' left right (Ring l v _) val =
  let this = Ring newL val right
  (newL, newR) = insert' left this l v
  in (this, newR)

fromList [] = error "Can't create empty ring"
fromList ls =
let (left, right) = fromList' left right ls
in left
  where
-- compute this ring, given left and right pointers. Return
-- left and right pointers for this segment
fromList' left right [] =
  let join = Join left right
  in (join, right)
fromList' left right (x:xs) =
  let this = Ring l x right
  (l, r) = fromList' left this xs
  in (this, r)

toList = toListL

-- View of list from left hand side
toListL = toList' . findLeftOfJoin
  where
toList' (Join _ _) = []
toList' (Ring l v _) = v : toList' l

toListR = toList' . findRightOfJoin
  where
toList' (Join _ _) = []
toList' (Ring _ v r) = v : toList' r

current (Ring r v l) = v
current _ = error "Join is never current (curr)"

rotR r amt
  | amt > 0 = goRight r amt
  | amt < 0 = goLeft r (negate amt)
  | otherwise = r

rotL r amt
  | amt > 0 = goLeft r amt
  | amt < 0 = goRight r (negate amt)
  | otherwise = r

goRight r 0 = r
goRight (Ring _ _ r@(Ring _ _ _)) amt = goRight r (amt - 1)
goRight (Ring _ _ (Join _ r)) amt = goRight r (amt - 1)
goRight (Join _ _) _ = error "Join is never current (goRight)"

goLeft r 0 = r
goLeft (Ring l@(Ring _ _ _) _ _) amt = goLeft l (amt - 1)
goLeft (Ring (Join l _) _ _) amt = goLeft l (amt - 1)
goLeft (Join _ _) _ = error "Join is never current (goLeft)"

isRing (Ring _ _ _) = True
isRing _ = False

isJoin (Join _ _) = True
isJoin _ = False

findLeftOfJoin (Join l _) = l
findLeftOfJoin (Ring l _ _) = findLeftOfJoin l

findRightOfJoin (Join _ r) = r
findRightOfJoin (Ring _ _ r) = findRightOfJoin r
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] hoogle broken?

2007-11-07 Thread Neil Mitchell
Hi Mike,

> It looks as if hoogle isn't working.  I get 404s whenever I try to do any 
> search on hoogle.

I have fixed quite a lot of the links, some will still be broken, but
hopefully not too many. Really, hoogle needs upgrading to use the new
base library etc - I'll try and do that sometime next week.

Thanks

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


Re: [Haskell-cafe] Fibbonachi numbers algorithm work TOO slow.

2007-11-07 Thread Henning Thielemann

On Tue, 6 Nov 2007 [EMAIL PROTECTED] wrote:

> However, this is still an O(log n) algorithm, because that's the
> complexity of raising-to-the-power-of.  And it's slower than the
> simpler integer-only algorithms.

You mean computing the matrix power of

/1 1\
\0 1/

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


Re: [Haskell-cafe] Screen scraping with an interactive process: Buffering problems?

2007-11-07 Thread Denis Bueno
On Nov 6, 2007 10:15 PM, David Benbennick <[EMAIL PROTECTED]> wrote:
> What about using hGetContents to just read ALL of the input, as a lazy
> string?  Then you look through that string for success or failure.  In
> other words,
>
> readACL2Answer pout = do
> s <- hGetContents pout
> parse s here

Ironically, this was my first problem.  First of all, I don't think I
want the semi-closed state -- I want to be able to read and write
freely later on (I may be misunderstanding semi-closed, however).
Second, when I used this approach, after the hGetContents call I did
the regexp matching, and the program hung during matching.

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


RE: [Haskell-cafe] WideFinder

2007-11-07 Thread Bayley, Alistair
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of manu
> 
> Haskell is conspicuously absent from the languages used to tackle Tim

> Bray's Wide Finder problem
>
(http://www.tbray.org/ongoing/When/200x/2007/10/30/WF-Results?updated).
> So far we have Ocaml, Erlang, Python, Ruby, etc...

Tim Bray mentions that GHC won't build on Solaris, so presumably that
problem would need to be solved before Haskell appears in his table. I
see that there are Solaris binary packages:
  http://www.haskell.org/ghc/download_ghc_661.html#sparcsolaris

so perhaps he just needs to be pointed to them?

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


[Haskell-cafe] WideFinder

2007-11-07 Thread manu
Haskell is conspicuously absent from the languages used to tackle Tim  
Bray's Wide Finder problem (http://www.tbray.org/ongoing/When/200x/ 
2007/10/30/WF-Results?updated).

So far we have Ocaml, Erlang, Python, Ruby, etc...

Bryan quickly wrote a program on his blog (http://www.serpentine.com/ 
blog/2007/09/25/what-the-heck-is-a-wide-finder-anyway/) that would  
place Haskell right in the second position.


JoCaml is the fastest so far (http://eigenclass.org/hiki.rb?fast- 
widefinder)...


Can Haskell do better ? Care to take a shot ?


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


Re: [Haskell-cafe] hoogle broken?

2007-11-07 Thread Andrea Rossato
On Wed, Nov 07, 2007 at 10:36:05AM +0100, Thomas Schilling wrote:
> On Tue, 2007-11-06 at 19:20 -0800, Michael Vanier wrote:
> > It looks as if hoogle isn't working.  I get 404s whenever I try to do any 
> > search on hoogle.
> > 
> > Mike
> 
> Yes, that's because the ghc-docs now have been slightly reorganized.
> Neil said he's working on it.

I'm trying to package ghc-6.8.1 and I'm getting literally crazy in
trying to properly build the documentation. The problem is that I do
not find any track of something documenting this document
reorganization.

Can you point me somewhere?

Thanks

Andrea

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


Re: [Haskell-cafe] Haskell home page not updated

2007-11-07 Thread Yitzchak Gale
Paul Johnson wrote:
> The Haskell home page hasn't been updated since 23rd September, even
> though a "Haskell Weekly News" came out on October 25th.

Not to mention GHC 6.8.1.

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


Re: [Haskell-cafe] More on Fibonacci numbers

2007-11-07 Thread jerzy . karczmarczuk
Andrew Bromage: 


I do note that nobody has tried it with continued fractions yet.


Now, it depends... If we take the PHI expansion as a CF: 1,1,1,1,1,... then
the convergents constitue the (rations of) Fibonaccis, but it goes through
the standard recurrence, so it is not so fancy. 


But we can take a decent representation of the Rabbit Number, in binary:
0.101101011011010110101101101011, and then develop it in CF, which will
give
[0; 1, 2, 2, 4, 8, 32, 256, ...],
then we find that those numbers are powers of Fibonaccis, 8=2^3, 32=2^5,
256=2^8, the next is 2^13, etc. It suffices to take the binary logarithm
and the problem is solved. This is an industrial-strength, serious
algorithm, involving lazy Rabbit Sequences, infinite Continued Fractions and
Binary Logarithms, so everybody sees that it will for sure contribute to the
Progress of the Western Civilization. I leave the homework for some
Haskell newbies who want to become famous. 


Anyway, if somebody finds in his/her library The Fibonacci Quarterly, there
is therein most probably much more about this fascinating subject, essential
for our comprehension of the Universe, and of Phyllotaxis in particular. 

Jerzy Karczmarczuk 



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


Re: [Haskell-cafe] More on Fibonacci numbers

2007-11-07 Thread ajb

G'day all.

Quoting [EMAIL PROTECTED]:


Andrew Bromage rebukes me once more that
the fl. point solution diverges
from the integer one [as if I didn't know that...],


Sorry if it came across as that.  I just meant it as a segue into a way
to make the algorithm practical.

I do note that nobody has tried it with continued fractions yet.

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


[Haskell-cafe] Haskell home page not updated

2007-11-07 Thread Paul Johnson
The Haskell home page hasn't been updated since 23rd September, even 
though a "Haskell Weekly News" came out on October 25th.


Paul.

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


Re: [Haskell-cafe] Best Linux for Haskell?

2007-11-07 Thread david48
On Nov 7, 2007 9:05 AM, Ketil Malde <[EMAIL PROTECTED]> wrote:
> david48 <[EMAIL PROTECTED]> writes:

> > Didn't work for me : Installs fine, ghci works fine, but I get linking
> > problems. ld complains about -lgmp

> Did you try installing any of these?

>   % apt-cache search libgmp
>   libgmp3-dev - Multiprecision arithmetic library developers tools
>   libgmp3c2 - Multiprecision arithmetic library

I have to admit that I didn't... Since it already worked with 6.6.1.
Anyways that dit it ( I was missing libgmp3-dev ), it works now.
Thanks !

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


Re: [Haskell-cafe] Re: Problem linking with GHC 6.8.1

2007-11-07 Thread david48
On Nov 7, 2007 10:44 AM, Simon Marlow <[EMAIL PROTECTED]> wrote:

> /usr/local/lib/ghc-6.8.1 (or wherever you installed it).  Alternatively you
> can install a suitable gmp package using your OS's package manager (you
> didn't say which flavour of Linux you're on).

This is what I did, following an advice on another thread. It worked.
I didn't think of doing that because it worked with 6.6.1.
( I'm on Kubuntu 7.10 )

> BTW, a better place to ask questions about GHC is
> [EMAIL PROTECTED], you're more likely to get a quick answer.

Thanks for the heads up ...

... and sorry everyone for the noise here.

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


[Haskell-cafe] Re: FP design

2007-11-07 Thread apfelmus

Thomas Schilling wrote:

Levi Stephen wrote:


I'm was wondering how most people work during when designing a functional 
program. Do you create data structures/types first? Do you work from some type 
signatures?


But there's a third thing that you can
do, other than start implementing:  think about the laws/properties that
should hold.  That's not always simple, in fact, it rarely is.


Yes, the classic approach: systematically derive programs from their 
specification. The classic paper on that is


  Paul Hudak. The Design of a Pretty-printing Library.
  http://citeseer.ist.psu.edu/hughes95design.html

with a follow-up

  Philip Wadler. A prettier printer.
  http://decenturl.com/homepages.inf.ed/wadler-98-prettier-printer

The man who derives all his programs from specification is Richard
Bird. You may want to have a look at his recent sudoku solver

  Richard Bird. A program to solve Sudoku.
  Slides: http://icfp06.cs.uchicago.edu/bird-talk.pdf

where he starts with an apparently correct but hopelessly slow
specification and transforms it into a blazingly fast one. His
introduction to Haskell

  Richard Bird.
  Introduction to Functional Programming using Haskel (2nd edition).
  http://decenturl.com/amazon/bird-introduction-functional

emphasizes the classic style, too.

You may think "this is all nice, but my problem is too 'soft' for 
mathematical laws and properties and such". Well, if you don't search, 
you won't find. Here's an example for a "soft" problem domain:


  Simon Peyton Jones, Jean-Marc Eber, Julian Seward.
  Composing contracts: an adventure in financial engineering.
  http://decenturl.com/research.microsoft/spj-financial-contracts

Of course, the laws "of nature" governing your problem domain may be 
hard to find, so it may be worth to "just implement" and let some "law 
intuition" guide you. Well-known example: darcs.



Regards,
apfelmus

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


Re: [Haskell-cafe] [OT] GHC uninstall on Linux

2007-11-07 Thread Philip Armstrong

On Wed, Nov 07, 2007 at 10:41:53AM +0100, Dusan Kolar wrote:
 I use tar.bz2 binary distribution of GHC compiler as my distro does not 
use any supported packaging system. Everything is fine, but... I want to 
install the new version of the GHC compiler. Is there any (easy) way, how 
to get information about what was copied and where during installation? 
(./configure; make install) There seems to be no uninstall target in the 
Makefile. :-( And I want to uninstall the previous version of the compiler.


 Is it safe to delete files/folders just from /usr/local/lib/ghc-6.6.1 and 
/usr/local/bin/gh* ?


Probably. At least you installed it in /usr/local, not /usr...

For future reference, this is what GNU stow is for: you do

$ ./configure --prefix=/usr/local/stow/packagename

when you build the binaries and then use the stow command to put
appropriate symlinks in to /usr/local/bin, /usr/local/lib etc etc for
the version you want to use. This way you can have several versions
installed in parallel in /usr/local/stow/ghc-6.6.1
/usr/local/stow/ghc-6.8 etc etc, but have one default version
symlinked into your $PATH.

Very useful...

Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Problem linking with GHC 6.8.1

2007-11-07 Thread Simon Marlow

Alberto Ruiz wrote:
If you don't use the foreign function interface I think that you only need 
the -L option:


ghc --make -L/usr/local/lib/ghc-6.8.1/gmp -O2 -o edimail Main.hs

Something similar worked for me, but this new behavior is not very reasonable. 
Could it be a bug?


It looks like a problem with the binary distributions.  They include gmp, 
but somehow don't install it.  As a workaround, you can take gmp.h and 
libgmp.a from from the binary tarball and put them by hand into 
/usr/local/lib/ghc-6.8.1 (or wherever you installed it).  Alternatively you 
can install a suitable gmp package using your OS's package manager (you 
didn't say which flavour of Linux you're on).


BTW, a better place to ask questions about GHC is 
[EMAIL PROTECTED], you're more likely to get a quick answer.


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


[Haskell-cafe] [OT] GHC uninstall on Linux

2007-11-07 Thread Dusan Kolar

Hello all,

 I use tar.bz2 binary distribution of GHC compiler as my distro does 
not use any supported packaging system. Everything is fine, but... I 
want to install the new version of the GHC compiler. Is there any (easy) 
way, how to get information about what was copied and where during 
installation? (./configure; make install) There seems to be no uninstall 
target in the Makefile. :-( And I want to uninstall the previous version 
of the compiler.


 Is it safe to delete files/folders just from /usr/local/lib/ghc-6.6.1 
and /usr/local/bin/gh* ?


 Thanks for any hint

   Dusan

P.S.
Tried google with no usable results.
D.

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


Re: [Haskell-cafe] hoogle broken?

2007-11-07 Thread Thomas Schilling
On Tue, 2007-11-06 at 19:20 -0800, Michael Vanier wrote:
> It looks as if hoogle isn't working.  I get 404s whenever I try to do any 
> search on hoogle.
> 
> Mike

Yes, that's because the ghc-docs now have been slightly reorganized.
Neil said he's working on it.


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


Re: [Haskell-cafe] Standalone PNG module?

2007-11-07 Thread Reinier Lamers

Peter Verswyvelen wrote:


I would like to load 32-bit images (RGB+alpha) for use with GLUT/OpenGL.

 

I know GTK2HS has support for loading images, but does a standalone 
Haskell (wrapper) module exists for loading images?


See the message "PNG files" by Tim Newsham, sent to haskell-cafe on the 
30th of october.


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


[Haskell-cafe] More on Fibonacci numbers

2007-11-07 Thread jerzy . karczmarczuk

[I changed the subject, so (hopefully) rare people who just follow the
thread may miss it, but I couldn't look at the name of Fibonacci with
two errors in it anymore...] 


Andrew Bromage rebukes me once more that the fl. point solution diverges
from the integer one [as if I didn't know that...], and proposes to make
this calculation in an algebraic extension field. OK. His program has
just 20 lines. 


It seems that we are slowly streaming to the generation of all possible and
impossible Fibonacci generators, which - as everybody knows - is absolutely
essential for the future of Humanity. 


So, I have another contribution. I hope that the complexity is linear, but
I don't want to check. 


The generation function of Fibonaccis: SUM_{n=0}^infty f_n*x^n, where x
is a formal variable, is equal to x/(1-x-x^2). Thus, it suffices to
represent this rational expression as formal power series in x. Let's
write a small *lazy* package which manipulates such power series,
implemented as lists: u_0 + u_1*x + u_2*x^2 + ... ==>  [u_0, u_1, u_2,...]. 


I have written such a package some 12 years ago, then Doug McIlroy wrote
independently a Functional Pearl paper about series... Here you are just
a fragment of it, without transcendental functions (nor sqrt), without
reversal, composition, or other thinks the series lovers appreciate.
-- *** 


-- The 'x' variable is a series with coeff_1=1, remaining: zero. So:
zeros = 0 : zeros
x = 0:1:zeros 


-- Good to have something to multiply series by scalars.
infixr 7 *>
c *> s = map (c*) s 


-- Num instance. Only interesting line is the multiplication, co-recursive.
instance (Num a) => Num [a] where
fromInteger n = fromInteger n : zeros
(+) = zipWith (+)
(-) = zipWith (-)
(u0:uq)*v@(v0:vq) = u0*v0 : u0*>vq + v*uq 


-- The division. Reconstructed from the multiplication. Also co-recursive.
instance (Fractional a) => Fractional [a]
where
fromRational c = fromRational c : zeros
(u0:uq) / v@(v0:vq) = let w0 = u0/v0
  in  w0:(uq - w0*>vq)/v
-- and now the solution:
fibs = x/(1-x-x*x) 

-- ** 


If you complain that you don't want floating point numbers, just add the
signature :: [Rational] (and import Ratio before). Everything becomes
fraction with denominator 1. 


Now Fritz Ruehr can take the Haskell Wiki page and reconstruct from it
a new instance of the 'Evolution of Haskell Programmer', based on the
most useless Fibonacci algorithms. 


BTW, for your general culture: you *should* know that Fibonacci numbers
have been invented by an Indian mathematician and grammarian Pangala, famous
for his book Chandas Shastra. Not too much is known about him. WP says: 


"In Indian literary tradition, Pingala is identified as the younger brother
of Panini..." [who was a great grammarian from 4BC, and who - as some think
also invented a specific version of Italian hot sandwiches. This brings us
nearer to Leonardo Pisano]. 

Jerzy Karczmarczuk 



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


Re: [Haskell-cafe] hoogle broken?

2007-11-07 Thread Neil Mitchell
Hi Mike,

> It looks as if hoogle isn't working.  I get 404s whenever I try to do any 
> search on hoogle.

Hoogle works for performing searches, but the documentation links are
incorrect. Expect this fixed by this evening!

Thanks

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


Re: [Haskell-cafe] GHC 6.8 and Mac OS X Leopard

2007-11-07 Thread Tim Clark
Thanks that is the x86 binary is exactly what I need!

On 06/11/2007, Brian P. O'Hanlon <[EMAIL PROTECTED]> wrote:
> On Nov 6, 2007 5:10 PM, Tim Clark <[EMAIL PROTECTED]> wrote:
> > Has anyone got GHC 6.8.1 building on Leopard? Unfortunately macports
> > isn't even letting me build GHC 6.6.1 since the bootstrap GHC isn't
> > working. Does anyone have any ideas or am I just too impatient?
>
> Oh, right... that thread is in ghc-users.  We are seeing if we can get
> it built... is this on PPC?  I installed the binary ghc-6.6.1 from the
> website, and am trying to build ghc while messing with build platform
> fun.  There is a binary build for x86, though, if you are on such a
> platform.
> -Brian
>
> Manuel M T Chakravarty wrote:
> > A full binary distribution of GHC 6.8.1 for Mac OS X 10.5 (Leopard) is
> > available from
> >
> >
> > http://www.cse.unsw.edu.au/~chak/haskell/ghc-6.8.1-i386-apple-darwin.tar.bz2
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Best Linux for Haskell?

2007-11-07 Thread Ketil Malde
david48 <[EMAIL PROTECTED]> writes:

> Didn't work for me : Installs fine, ghci works fine, but I get linking
> problems. ld complains about -lgmp

Did you try installing any of these?

  % apt-cache search libgmp
  libgmp3-dev - Multiprecision arithmetic library developers tools
  libgmp3c2 - Multiprecision arithmetic library

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