Re: [Haskell-cafe] ANNOUNCE: docidx-1.0.0

2011-07-18 Thread Andy Gimblett
With apologies, I now announce docidx-1.0.1 which fixes a problem kindly 
pointed out by Jack Henahan.  If you tried to install docidx using cabal 
install over the weekend and failed, please try again now.

The docidx-1.0.0.tar.gz uploaded to hackage on Friday was missing most of its 
source code (everything except its Main module in fact), because I hadn't added 
an other-modules field to docidx.cabal.  I hadn't actually tried to build 
from that tarball, so I didn't spot this: I had assumed that if I could cabal 
install in my source directory, then the tarball (produced by cabal sdist) 
would work too.  (And yes, I've tested this version before announcing it! :-) )

Apologies again, and many thanks to Jack for pointing this out.

-Andy


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


[Haskell-cafe] ANNOUNCE: docidx-1.0.0

2011-07-15 Thread Andy Gimblett
Hi all.  I'd like to announce docidx, a new tool for Haskell documentation:

http://hackage.haskell.org/package/docidx
http://github.com/gimbo/docidx.hs

docidx is a program which creates a static HTML page indexing your installed 
packages, with links to your local haddock docs and to each package's hackage 
page.  It covers global and user packages, and handles multiple installed 
versions sensibly.  Here's how the output looks:

http://github.com/gimbo/docidx.hs/raw/master/examples/example.png

The idea is to complement the index by module name which Cabal creates and 
maintains.  Sometimes you want to find things by package.  :-)  (But note that 
unlike Cabal's index, docidx's isn't automatically updated when you install a 
new package; so, I run it once an hour from cron.)

Please see the github page for more details, including customisation options.

Hopefully somebody will find this useful.  Maybe one day it could be part of 
cabal-install?  :-)

Thanks!

-Andy

PS: A bit of history/due credit: Martijn van Steenbergen did something similar 
in PHP in early 2009: 
http://thread.gmane.org/gmane.comp.lang.haskell.cafe/53531/focus=53572 ; then I 
wrote a static version in Python later that year: 
http://gimbo.org.uk/blog/2009/09/23/ ; then Andy Price ported that to Haskell: 
https://github.com/andyprice/docidx.hs ; finally, I rewrote that to build the 
index via Cabal rather than walking the filesystem directly - and here we are.

--
Andy Gimblett
hask...@gimbo.org.uk


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


[Haskell-cafe] Re: Proper round-trip HughesPJ/Parsec for Doubles?

2010-02-25 Thread Andy Gimblett

Hi Christian,

On 24 Feb 2010, at 13:24, Christian Maeder wrote:

I hope you don't mind if I make some style comments to your final  
version.


Not at all - thanks!


1. break the line after do
(to avoid a layout change when change name or arguments of float' or
rename the variable e)


I'm not convinced by this; perhaps while editing the code it's useful,  
but those changes don't happen very often, and when they do, any half- 
decent editor ought to be able to handle making the change  
consistently.  I do sometimes drop the do to the next line, but  
usually in order to keep things within 80 columns.  I think this is  
somewhat a matter of personal taste though.  More on this at the end...



2. The t :: TokenParser st is only used for the white spaces.
This should be done separately (use lexeme from the TokenParser if  
you

really need to). Just using spaces is also an alternative.


OK - but what I'm trying to do here is create something I can use as a  
drop-in replacement for float from Text.ParserCombinators.Parsec.Token  
- in which case it shouldn't be done separately, I think?



3. liftCtoS is only applied to '-', so an optSign would suffice.
 optSign = option  $ fmap (: []) (char '-')


Agreed - although I resurrect it later as maybeChar (see below),  
matching against a choice of characters (to handle +/-) or returning  
 if empty.



(read also allows a capital 'E' and a '+' before the exponent, but no
initial '+' sign.


OK: didn't catch this because show doesn't (it seems) ever write them  
like that.  Thanks.



The decimal point is optional.


Same comment.  :-)  Fixed below, although I remove this optionality  
for my application (for now) because (I think) I want to be explicit  
about int vs float...


Also NaN and Infinity can be read, both possibly preceded by a  
'-' sign followed by

spaces. But you may restrict yourself to the possible outputs of show,
which would include NaN and Infinity, though.)


OK.  Indeed, it seems an initial '-' can be followed by spaces for  
other cases, e.g. - 2e4, so have implemented that more general  
form.  Adding the NaN and Infinity cases gives us another level of  
indent, and pushes us close enough to 80 columns that I've dropped the  
outermost do to the next line.



It may make sense to use something like readMaybe (which is missing in
the Prelude) instead of read to allow the parser to fail more  
nicely.


It seems to be kicking up reasonable errors as it is, e.g.:

*Main parse aFloat  2e-h
Left (line 1, column 4):
unexpected h
expecting digit

I haven't seen any uncaught exceptions propagating, if that's what  
you're worried about...?



Btw I observed the following problem with read (that readMaybe would
also not solve). http://hackage.haskell.org/trac/ghc/ticket/3897


Ah, well that's out of scope for me, I fear.  :-)

So here's what I have now:

float' :: TokenParser st - GenParser Char st Double
float' t =
  do n - maybeChar -
 spaces
 fs - choice [symbol t NaN,
   symbol t Infinity,
   do whole - many1 digit
  frac - option  $ do char '.'
 ds - many1 digit
 return $ '.' : ds
  ex - option  $ do choice [char 'e', char 'E']
   s - maybeChar +-
   ds - many1 digit
   return $ concat [e, s, ds]
  return $ concat [whole, frac, ex]
  ]
 whiteSpace t
 return $ read $ n ++ fs
  where maybeChar :: String - GenParser Char st String
maybeChar as = option  (choice (map char as) = \a -  
return [a])



You can also break it immediately before do, which I think is
sometimes more clear.


If not an extra space is added following do this leads to an odd
indentation of at least one line.


I'm curious: which line in the above is indented oddly?  Oh, wait: you  
don't mean odd as in strange, do you?  You mean odd as in not  
even?  So, e.g. the spaces line starts at column 5?  What's wrong  
with that?


Cheers!

-Andy

--
Andy Gimblett
http://gimbo.org.uk/

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


[Haskell-cafe] Building/installing OS X application bundles for GUIs - cabal-macosx

2010-02-24 Thread Andy Gimblett

Hi all,

Last week I quietly released v0.1.0 of cabal-macosx, providing support  
for building OSX application bundles (e.g. and in particular for GUIs  
created using wxHaskell and gtk2hs - hence all the cross-posting):


http://hackage.haskell.org/package/cabal-macosx

I'm now soliciting input on how to handle the install stage, leading  
(I hope) to a loudly-announcable release soon. :-)


The current package provides a post-build hook which creates an  
application bundle at dist/build/foo.app (for example).  It seems to  
work well.  See the source repository for examples.


However, running runghc Setup install copies the bare executable at  
dist/build/foo/foo (rather than the foo.app bundle) to the install  
location, which is no good.  So I need to put in some install  
infrastructure to copy the .app, not the bare executable, to the right  
place.


That raises the question: what is the right place?  It seems to me  
that the defaults are not the right defaults for this case.  --global  
should probably go to /Applications, and --user should perhaps go to ~/ 
Applications (though I'm less sure about that).  Of course, end-users  
can explicitly set this on a per-install basis, but it seems that for  
bundles we'd want to override the default.


Thus I'm currently asking:

* What do people think about the default installation question?

* Can anyone advise me on the right way to handle this (installing  
the .app, and overriding the default locations) with Cabal?  I'm  
hoping I can just tweak part of the LocalBuildInfo and let the default  
machinery then handle the work, but at present it's not clear to me  
how to do that, and rather than spend ages trying to figure it out,  
perhaps someone who knows can help me out?  I'm hoping I'm not going  
to have to completely override the install machinery - that would feel  
somewhat self-defeating.


Many thanks,

-Andy

--
Andy Gimblett
http://gimbo.org.uk/

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


[Haskell-cafe] Proper round-trip HughesPJ/Parsec for Doubles?

2010-02-23 Thread Andy Gimblett

Hi all,

Short version: How can I pretty print and parse values of type Double  
such that those operations are each other's inverse?


Long version: I'm writing and QuickCheck-testing a parser using the  
approach set out here:


http://lstephen.wordpress.com/2007/07/29/parsec-parser-testing-with-quickcheck/

That is, each syntactic category gets a pretty-printer and a parser  
and an Arbitrary instance, and QuickCheck checks that (parse .  
prettyPrint) == id, basically.  Somewhat unsurprisingly, this  
sometimes fails for floating point values (I'm using Doubles).


Now, I know that floats are in some sense imprecise, and comparing for  
equality is fraught with peril, but it seems that if x==x then it  
ought to be at least _possible_ to arrange matters such that (parse .  
prettyPrint x) == x as well.  At worst, pretty-printing the underlying  
binary representation!?  So my feeling is that my parser could be  
improved.


At the moment I'm working around it by defining a type class which  
checks for equality within some margin of error, and using that  
instead of Eq - but it's messier than I'd like, so I wondered if there  
was something obvious I'm missing.


As hpaste.org seems to be down, I'll attach a code example here instead.

Thanks!

-Andy

--
Andy Gimblett
http://gimbo.org.uk/



TestParse.hs
Description: Binary data



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


[Haskell-cafe] Re: Proper round-trip HughesPJ/Parsec for Doubles?

2010-02-23 Thread Andy Gimblett



Short version: How can I pretty print and parse values of type Double
such that those operations are each other's inverse?


Maybe you have more luck with show and read (without Parsec.Token).

Your example:
x = 9.91165677454629

fails because the computation performed by the parser
9.0 + 0.91165677454629 yields 9.911656774546291


That seems to do the trick!  Below, for the record, the code I've come  
up with (I threw away the Either Integer Double part so it's a bit  
simpler, also).  I'm sure it can be improved, but this is passing all  
tests reliably, it seems.


Many thanks, Christian and Daniel, for your help!

Best,

-Andy

parseDouble :: Parser Double
parseDouble = try $ do (symbol toks) -
   n - floater
   return $ negate n
  | floater
  where toks = makeTokenParser emptyDef

-- This could definitely be improved, but it's working. :-)
floater :: Parser Double
floater = do w - many1 digit
 char '.'
 f - many1 digit
 e - optionMaybe $ do char 'e' -- Optional exponent part
   n - option  (char '-'  return  
-) -- Optional negation in exponent

   m - many1 digit
   return $ n ++ m
 case e of Nothing - return $ read $ w ++ . ++ f
   Just e' - return $ read $ w ++ . ++ f ++  
e ++ e'


--
Andy Gimblett
http://gimbo.org.uk/

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


Re: [Haskell-cafe] Re: Proper round-trip HughesPJ/Parsec for Doubles?

2010-02-23 Thread Andy Gimblett

For the record, here's the final improved version:

float' :: TokenParser st - GenParser Char st Double
float' t = do n - liftCtoS '-'
  w - many1 digit
  char '.'
  f - many1 digit
  e - option  $ do char 'e'
  n' - liftCtoS '-'
  m - many1 digit
  return $ concat [e, n', m]
  whiteSpace t
  return $ read $ concat [n, w, ., f, e]
  where liftCtoS a = option  (char a  return [a])

Thanks for all the help, again.

-Andy

--
Andy Gimblett
http://gimbo.org.uk/

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


[Haskell-cafe] Broken registration link on hackage trac

2010-01-18 Thread Andy Gimblett

Hi all,

I want to register an account on hackage's trac instance, but the  
register an account link on the start page:


http://hackage.haskell.org/trac/hackage/wiki/WikiStart

is broken.

I'm guessing someone here knows what it should be and has registered  
already and thus can fix it.  :-)


Cheers,

-Andy

--
Andy Gimblett
http://gimbo.org.uk/

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


[Haskell-cafe] A small (?) problem with type families

2009-11-13 Thread Andy Gimblett

Hi all,

This email is literate Haskell.  I'm trying to use type families to
express some dependencies between type classes, and I'm running into
trouble, I think because I'm producing chains of dependencies which
the checker can't resolve...  Here's a minimised version of the state
I've got myself into.  :-)

 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE TypeFamilies #-}

 module Families where

First a type family where the type Y is functionally dependent on
the type X, and we have a function from Y to ().

 class X a where
   type Y a
   enact :: Y a - ()

Now another type family, where the type Q is functionally dependent
on the type P, _and_ it must also be an instance of the X
class.

 class (X (Q s)) = P s where
   type Q s

(Perhaps there's a better way to express that dependency?)

Now a function which takes a value whose type is an instance of the Y
depending on the Q depending on the P.  (Phew!)  The function just
tries to call enact on that value.

 bar :: P s = Y (Q s) - ()
 bar w = enact w

The error we get is:

src/Families.lhs:35:16:
Couldn't match expected type `Y a' against inferred type `Y (Q s)'
In the first argument of `enact', namely `w'
In the expression: enact w
In the definition of `bar': bar w = enact w

Presumably this way I'm chaining type dependencies is flawed.  Any
suggestions on how to improve it, and/or what to read to understand
what I'm dealing with better?  (So far I've read Fun with type
functions V2, but that's about it, and I admit I didn't grok it all.)

Thanks!

-Andy

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


Re: [Haskell-cafe] A small (?) problem with type families

2009-11-13 Thread Andy Gimblett
Ack. I've just realised that P/Q is not a functional dependency.  I  
need to use a multi-parameter type class there.  So my question is  
probably completely pointless - sorry!


Thanks anyway,

-Andy

On 13 Nov 2009, at 20:26, Andy Gimblett wrote:


Hi all,

This email is literate Haskell.  I'm trying to use type families to
express some dependencies between type classes, and I'm running into
trouble, I think because I'm producing chains of dependencies which
the checker can't resolve...  Here's a minimised version of the state
I've got myself into.  :-)

 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE TypeFamilies #-}

 module Families where

First a type family where the type Y is functionally dependent on
the type X, and we have a function from Y to ().

 class X a where
   type Y a
   enact :: Y a - ()

Now another type family, where the type Q is functionally dependent
on the type P, _and_ it must also be an instance of the X
class.

 class (X (Q s)) = P s where
   type Q s

(Perhaps there's a better way to express that dependency?)

Now a function which takes a value whose type is an instance of the Y
depending on the Q depending on the P.  (Phew!)  The function just
tries to call enact on that value.

 bar :: P s = Y (Q s) - ()
 bar w = enact w

The error we get is:

src/Families.lhs:35:16:
   Couldn't match expected type `Y a' against inferred type `Y (Q s)'
   In the first argument of `enact', namely `w'
   In the expression: enact w
   In the definition of `bar': bar w = enact w

Presumably this way I'm chaining type dependencies is flawed.  Any
suggestions on how to improve it, and/or what to read to understand
what I'm dealing with better?  (So far I've read Fun with type
functions V2, but that's about it, and I admit I didn't grok it all.)

Thanks!

-Andy

___
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] A small (?) problem with type families

2009-11-13 Thread Andy Gimblett
Hahaha, this is what I get for trying to think about Haskell on a  
Friday night.  Now I think it _is_ a functional dependency after all.   
Who knows how long it will be before I change my mind again? :-)


I shall think about this more carefully tomorrow...

Thanks again,

-Andy

On 13 Nov 2009, at 20:48, Andy Gimblett wrote:

Ack. I've just realised that P/Q is not a functional dependency.  I  
need to use a multi-parameter type class there.  So my question is  
probably completely pointless - sorry!


Thanks anyway,

-Andy

On 13 Nov 2009, at 20:26, Andy Gimblett wrote:


Hi all,

This email is literate Haskell.  I'm trying to use type families to
express some dependencies between type classes, and I'm running into
trouble, I think because I'm producing chains of dependencies which
the checker can't resolve...  Here's a minimised version of the state
I've got myself into.  :-)

 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE TypeFamilies #-}

 module Families where

First a type family where the type Y is functionally dependent on
the type X, and we have a function from Y to ().

 class X a where
   type Y a
   enact :: Y a - ()

Now another type family, where the type Q is functionally dependent
on the type P, _and_ it must also be an instance of the X
class.

 class (X (Q s)) = P s where
   type Q s

(Perhaps there's a better way to express that dependency?)

Now a function which takes a value whose type is an instance of the Y
depending on the Q depending on the P.  (Phew!)  The function just
tries to call enact on that value.

 bar :: P s = Y (Q s) - ()
 bar w = enact w

The error we get is:

src/Families.lhs:35:16:
  Couldn't match expected type `Y a' against inferred type `Y (Q s)'
  In the first argument of `enact', namely `w'
  In the expression: enact w
  In the definition of `bar': bar w = enact w

Presumably this way I'm chaining type dependencies is flawed.  Any
suggestions on how to improve it, and/or what to read to understand
what I'm dealing with better?  (So far I've read Fun with type
functions V2, but that's about it, and I admit I didn't grok it  
all.)


Thanks!

-Andy

___
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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: simple-observer-0.0.1, a simple implementation of the observer design pattern

2009-11-11 Thread Andy Gimblett

Hi all,

Further to earlier discussion on this topic, I've just released a  
first version of this package to hackage:


http://hackage.haskell.org/package/simple-observer

It is a fairly simple implementation of subject/observer which I've  
recently used to good effect in an GUI written using wxHaskell.


Here's a blog post discussing it further and giving a simple example  
of use:


http://gimbo.org.uk/blog/2009/11/12/simple-observers-in-haskell/

Many thanks for the earlier comments, even if they haven't resulted in  
any changes (yet?).


Best regards,

-Andy

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


[Haskell-cafe] Observer pattern in Haskell?

2009-11-09 Thread Andy Gimblett

Hi all,

I've been doing some GUI programming recently, using wx.  To help  
manage dependencies between state and UI elements, I looked for a  
Haskell version of the Observer design pattern, and I found an  
implementation written by Bastiaan Heeren of ou.nl [1].


It pretty much did what I wanted, though I made a few changes along  
the way.  Since this seems to be of general use (ie beyond wx), I've  
proposed to Bastiaan that I package it up for release on hackage, and  
he's happy for me to do so.  Before I do so, I thought I'd ask for  
comments.


The code is on github: http://github.com/gimbo/observer.hs where we  
have:


Control.Observer - a typeclass for observable objects.
Control.Observer.Synchronous - an implementation based on IORefs.

This is essentially the same as Bastiaan's original, except I've  
changed the names, split it into two modules, commented it, added one  
or two small things, and Cabalised it.


I've also made a branch where Control.Observer.Synchronous uses MVars  
instead of IORefs, in an attempt to achieve thread safety:


http://github.com/gimbo/observer.hs/blob/threadsafeSync/Control/Observer/Synchronous.hs

Now, before I make a hackage release:

0. Is this completely insane, in a Haskell setting?  Are there better  
ways to do this that aren't laden with OO-worldview baggage?


1. Does anyone have any comments, on either version?

2. In particular, is the MVar version sensible?  I'm aiming for mutual  
exclusion between threads.  I _think_ I've got it, but I'm perhaps not  
familiar enough with the semantics of MVar to be certain.  Advice  
appreciated.  If it _is_ sensible, then is there any reason not to  
just use this, and discard the IORef version?


The current implementation is synchronous, in that any observer  
functions are called immediately and synchronously (and in the same  
thread as the change of subject value).  I'm pondering extending the  
package with an asynchronous version where the update just trips a  
flag, and the observer function picks this up later - possibly in  
another thread.  The idea there is to help in cases where certain  
operations have to be in a particular thread.  But this will mean a  
change to the typeclass too, I guess - or the addition of another one  
for observers themselves.  Again, any thoughts?


Thanks!

-Andy

[1] http://www.cs.uu.nl/wiki/bin/view/Afp0607/ExerciseWXHaskell

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


Re: [Haskell-cafe] Observer pattern in Haskell?

2009-11-09 Thread Andy Gimblett

Hi Neil,

On 9 Nov 2009, at 14:50, Neil Brown wrote:


1. Does anyone have any comments, on either version?
There is no way to remove an observer, which is something I'd expect  
to have available.  I realise this would require assigning a key to  
each observer (and thus perhaps storing them in an associative map)  
or some way to filter them, but I think if you can only ever add  
observers, it will get awkward.


Good point. This occurred to me when I referred to the Gang of Four  
book, while changing names for consistency.  I must confess, in my  
current project I haven't needed it, but I see your point.


2. In particular, is the MVar version sensible?  I'm aiming for  
mutual exclusion between threads.  I _think_ I've got it, but I'm  
perhaps not familiar enough with the semantics of MVar to be  
certain.  Advice appreciated.  If it _is_ sensible, then is there  
any reason not to just use this, and discard the IORef version?
It looks fine (and thread-safe) to me, but I'd agree that you may as  
well just use the MVar version and leave out the IORef version.


Cool, thanks.

was a bit surprised at first that the observers were called  
synchronously.  Asynchronous is what I'd expect, and it's also  
harder to code the asynchronous handlers wrongly.  One blocking  
call (such as putMVar) in a synchronous handler can screw up your  
whole program by delaying the subsequent observers (and at that  
stage, the order in which the observers were added begins to matter).


True, but the observers shouldn't be able to access the MVars  
directly, I think?  They should only be able to use the exposed  
interface, which won't let that happen?


But my idea of how asynchronous would be implemented seems different  
to yours, judging by your description.  Why not just augment this  
function in the synchronous version:


notifyObservers :: Subject sub val = sub - IO ()
notifyObservers subject =
 do value - getValue subject
observers - getObservers subject
mapM_ ($ value) observers to become:

notifyObserversAsync :: Subject sub val = sub - IO ()
notifyObserversAsync subject =
 do value - getValue subject
observers - getObservers subject
mapM_ (forkIO . ($ value)) observers

This is what I was expecting to happen -- all the observer actions  
are spawned off into their own thread to run whatever code they want  
(either communicating back to an existing thread, or performing some  
long in-depth action).


Interesting.  That might be quite sensible.  My thoughts have probably  
been coloured by how I've been doing things in wx.  Ta for the  
suggestion.


Cheers,

-Andy

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


Re: [Haskell-cafe] Observer pattern in Haskell?

2009-11-09 Thread Andy Gimblett


On 9 Nov 2009, at 15:21, Eduard Sergeev wrote:


Andy Gimblett-2 wrote:
To help manage dependencies between state and UI elements, I looked  
for a

Haskell version of the Observer design pattern


Isn't Reactive Programming approach more suitable than Observer if  
we talk

about Haskell?


Possibly.  Care to expand?  If you have a more elegant solution, which  
fits in well with ordinary wxHaskell, I'd be interested.


Cheers,

-Andy

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


Re: [Haskell-cafe] Observer pattern in Haskell?

2009-11-09 Thread Andy Gimblett


On 9 Nov 2009, at 16:47, Eduard Sergeev wrote:


Andy Gimblett-2 wrote:
Possibly.  Care to expand?  If you have a more elegant solution,  
which

fits in well with ordinary wxHaskell, I'd be interested.


I believe there are a few experimental frameworks built on top of  
wxHaskell

which use Functional Reactive Programming, like
http://www.haskell.org/haskellwiki/Phooey Phooey . They seem to be  
more

ellegant, but probably less practical for now since they are still
experimental. I just thought that FRP is more suitable for Haskell but
probably in case of wxHaskell it is not a case. Sorry if it was off  
topic.


In that case, I am 100% in agreement with you.  :-)  I do look forward  
to using such technology in the future...


Thanks!

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


Re: [Haskell-cafe] Observer pattern in Haskell?

2009-11-09 Thread Andy Gimblett


On 9 Nov 2009, at 17:41, Neil Brown wrote:

Just to clarify -- I meant access to another MVar.  Basically, if I  
do this:


do v - newMVar
  addObserver sub (putMVar v)

If when the observers are run, the MVar v (that I've allocated) is  
non-empty, my code will block until it is empty, which will also  
block all the subsequent observers from being run (and block the  
code that called setValue) until the MVar is cleared by another  
thread.  So my one poorly-written observer could deadlock (or cause  
stutter in) the system, whereas in the forkIO version, this observer  
would be fine -- it would block in its own new thread.


Ah yes, of course - I understand.  Of course, there's nothing really  
to stop application authors doing such things in the main thread  
too...  ;-)


Thanks for the clarification,

-Andy

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


[Haskell-cafe] ANN: fp-southwales, the South Wales Functional Programming User Group

2009-10-14 Thread Andy Gimblett

Dear friends,

It is my pleasure to announce the formation of fp-southwales, a user  
group for anybody interested in functional programming in the area of  
south Wales, UK.  We're based out of Swansea University's Computer  
Science department, where there are a few of us using Haskell for our  
research, but we welcome anyone who wants to join in, from academia or  
industry, from Swansea, or Cardiff, or indeed anywhere in south  
Wales.  As the name of the group also suggests, we're interested in  
all aspects of functional programming, not just Haskell, although we  
expect that to be a central topic, for now at least.


We exist online as a google group: http://groups.google.com/group/fp-southwales

The first point of business is: hello, what shall we do, and when  
shall we do it?  :-)

http://groups.google.com/group/fp-southwales/browse_thread/thread/ddb2d352a14896d8

All welcome!

-Andy

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


[Haskell-cafe] Haddock and literate Haskell: annotations must be marked as source?

2009-09-24 Thread Andy Gimblett

Hi all,

I've developed a bit of a taste for literate Haskell lately, being a  
verbose sort of guy.  Unfortunately, it doesn't seem to interact with  
Haddock in the way I'd like/expect.  I just wanted to check that my  
understanding of the situation is correct before I (regretfully) give  
up on LHS.


It seems to me that Haddock only picks up annotation comments (ie  
those that should be included in the produced documentation) from  
literate Haskell source when those annotations are themselves marked  
up as source - it seems not to recognise them in the general text.


For example, I was expecting/hoping that from the point of view of  
Haddock, the following literate Haskell code with an annotation-marked  
paragraph (starts with a vertical bar) in the non-source text.


| Turn a foo into a bar.

 foo :: Foo - Bar
 foo b = ...

ought to be equivalent to the following illiterate Haskell:

-- | Turn a foo into a bar.
foo :: Foo - Bar
foo b = ...

ie, it should produce Haddock docs where the definition of foo is  
annotated with that comment.


Sadly, that appears not to be the case.  It appears the literate  
version needs to look like this:


 -- | Turn a foo into a bar
 foo :: Foo - Bar
 foo b = ...

which to my mind rather defeats the purpose of being literate.

So: am I right that this is the intended/expected behaviour?  If not,  
how does one get round it?  If so, could someone perhaps comment on  
the prospects/complexity of implementing this - or the reasons why it  
is in fact a bad idea?


Many thanks!

-Andy


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


Re: [Haskell-cafe] Haddock and literate Haskell: annotations must be marked as source?

2009-09-24 Thread Andy Gimblett


On 24 Sep 2009, at 18:28, Duncan Coutts wrote:


On Thu, 2009-09-24 at 17:49 +0100, Andy Gimblett wrote:


So: am I right that this is the intended/expected behaviour?  If not,
how does one get round it?  If so, could someone perhaps comment on
the prospects/complexity of implementing this - or the reasons why it
is in fact a bad idea?


As Brad says, we implemented this in Cabal by doing a non-standard
unlit operation. So cabal haddock will do the right thing for your
examples. Running haddock directly and letting it do the unlitting  
will

get different results.


That's great news for me, except: that's what I tried first, and I've  
just tried it again and it still doesn't seem to work for me.  Perhaps  
I am doing something wrong...?


Here's a toy example LHS file: 
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=9802

and here's the corresponding .cabal file: 
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=9803

and here's a screenshot of the resultant HTML: http://is.gd/3DzmT

(produced via runghc Setup configure  runghc Setup haddock )

Any idea what I'm doing wrong?

One thing I did try was removing the blank line between the annotation  
and the code.  Of course, that breaks the LHS rules, so it doesn't  
build.  (I wondered if it was special cased for this purpose.)


Thanks again,

-Andy

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


Re: [Haskell-cafe] Haddock and literate Haskell: annotations must be marked as source?

2009-09-24 Thread Andy Gimblett


On 24 Sep 2009, at 20:10, Duncan Coutts wrote:


On Thu, 2009-09-24 at 19:48 +0100, Andy Gimblett wrote:


That's great news for me, except: that's what I tried first, and I've
just tried it again and it still doesn't seem to work for me.   
Perhaps

I am doing something wrong...?


You're quite right, it got broken with the move to haddock2. The  
code in
Cabal-1.6 skips the pre-processing when using haddock2, assuming  
haddock

will handle it. In the current Cabal development version it works
properly and I get the right output for your example.


Ah, righto.  In that case, I won't shy away from LHS, and I'll be  
patient for the next Cabal release, or maybe even check out the  
development version.  :-)


Many thanks for your reassurance!

Cheers,

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


Re: [Haskell-cafe] Re: [Hs-Generics] how to automatically create and install documentations of a package?

2009-09-23 Thread Andy Gimblett


On 21 Sep 2009, at 09:14, Martijn van Steenbergen wrote:


Michael Shulman wrote:

Is there a way to make it automatically update a single contents page
with links to the documentation of all installed packages?


See:
 http://thread.gmane.org/gmane.comp.lang.haskell.cafe/53531/ 
focus=53560
 http://thread.gmane.org/gmane.comp.lang.haskell.cafe/53531/ 
focus=53572


Seeing this today (I'm catching up on haskell-cafe!) made me want this  
too, so I rolled my own.


Main nice feature: I pointed it at the hackage CSS file, so it's  
pleasingly familiar/pretty.


Anything that doesn't have a 'html/index.html' in it gets indexed  
separately at the end.


I used Python.  I was going for quick and dirty.  Sorry, Dijkstra!   
Haskell next time, I promise!  :-)


More info, screenshots, and code here:

http://gimbo.org.uk/blog/2009/09/23/generating-an-index-of-haskell-haddock-docs-automatically/

Best,

-Andy


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


Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-19 Thread Andy Gimblett


On 17 Sep 2009, at 18:01, Ryan Ingram wrote:


Here's a way that works more closely to your original version:

instance Enumerated a = Target a where
   convert n
   | n = 0  n  numConstrs = Just (constrs !! n)
   | otherwise = Nothing
where
   constrs = constructors
   numConstrs = length constrs


Aha - that's great, and it works without OverlappingInstances (but  
still with FlexibleInstances and UndecidableInstances - should that  
worry me?)


Just making sure constructors is only referenced once is the key, it  
seems.


Thanks!

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


[Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Andy Gimblett

Hi all.  This email is in literate Haskell; you should be able to load
it into ghci and verify what I'm saying (nb: it won't compile without
alteration: see below).

I'm trying to do something which may anyway be stupid / not the best
approach to what I'm trying to achieve; however, it's not working and
I can't see why not.  So I'm asking for help on two fronts:

1) Why is this failing?

2) Maybe more usefully, how should I actually be doing this?  It seems
   an ugly approach; a voice in my head is saying scrap your
   boilerplate, but I've no idea yet if that's actually applicable
   here; should I look at it?

On with the show...

I need these for subclass stuff later on...

 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE OverlappingInstances #-}
 {-# LANGUAGE UndecidableInstances #-}

 module Ambig where

I wish to define a number of algebraic data types with the ability to
turn Int values into instances of those types.  So I define a
typeclass saying this is possible.  I use Maybe so I can encode the
existence of out-of-range Int values, which will vary from target type
to target type.

 class Target a where
 convert :: Int - Maybe a

E.g. here's a type Foo which only wants values between 1 and 10:

 data Foo = Foo Int deriving (Show)
 instance Target Foo where
 convert n | n `elem` [1..10] = Just $ Foo n
   | otherwise = Nothing

(That's a simple example; some are rather more complex.  How to do
this isn't what I'm asking about, really.)

So we have, for example:

*Ambig (convert 1) :: Maybe Foo
Just (Foo 1)
*Ambig (convert 11) :: Maybe Foo
Nothing

Now, some of those algebraic data type types happen to be
enumerations; in this case, my idea is to list the constructors, with
the rule that each constructor's position in the list is the Int which
gets converted into that constructor.

 class Enumerated a where
 constructors :: [a]

E.g. here's a type Bar with three constructors:

 data Bar = X | Y | Z deriving (Show)
 instance Enumerated Bar where
 constructors = [X, Y, Z]

(This is certainly ugly.  Any suggestions?)

Now we get to the crux.  If a type is an instance of Enumerated, it
should also be a Target, because we should be able to convert from Int
just by list lookup.  But we include a bounds check, naturally...

 instance (Enumerated a) = Target a where
 convert n | n `elem` [0..len-1] = Just $ constructors !! n
   | otherwise = Nothing
 where len = length constructors

So I would _hope_ that then, e.g., we'd have:

*Ambig (convert 0) :: Maybe Bar
Just X
*Ambig (convert 1) :: Maybe Bar
Just Y
*Ambig (convert 3) :: Maybe Bar
Nothing

Sadly, this function doesn't compile, dying with an Ambiguous type
variable error:

Ambig.lhs:75:29:
Ambiguous type variable `a' in the constraint:
  `Enumerated a'
arising from a use of `constructors' at Ambig.lhs:74:29-40
Probable fix: add a type signature that fixes these type  
variable(s)


If we replace length constructors with 3 (say), it compiles (but
is useless).  Adding a type signature doesn't help: it's misplaced
in that context.  If I break it out of the instance declaration so I
can add one, I still get the same problem:

 convert' :: (Enumerated a, Target a) = Int - Maybe a
 convert' n | n `elem` [0..len-1] = Just $ constructors !! n
| otherwise = Nothing
 where len = length constructors

I guess I see roughly what's going on; the question is which
constructors instance is meant?, right?  In the Just part it's OK,
because it can be inferred from the function's return type (right?).
But in the guard we don't have that help, so it could be any
Enumerated instance?

Any advice appreciated!  Particularly if this is just a dumb approach.
For context, this is related to deserialisation of binary data (they'll
actually be Word8's, not Int's) into a variety of data structures.

Hmmm, maybe I should just be using Data.Binary...

Many thanks,

-Andy

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


Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Andy Gimblett


On 17 Sep 2009, at 15:21, José Pedro Magalhães wrote:


  E.g. here's a type Bar with three constructors:
   data Bar = X | Y | Z deriving (Show)
   instance Enumerated Bar where
   constructors = [X, Y, Z]
 
  (This is certainly ugly.  Any suggestions?)
 
 |constructors| is expressible in SYB:
Wow.

What about

data Bar = X | Y | Z deriving (Show, Eq, Ord, Enum, Bounded)

instance Enumerated Bar where
   constructors = [minBound .. maxBound]

?

Oh yes, that will certainly work for this very simple datatype.  
However, one cannot automatically derive instances of |Bounded| for  
datatypes with non-nullary constructors.


That would be OK in this instance, I think; I'm already dealing with  
some of those cases by hand, but there were enough purely nullary ones  
that this seemed worth doing.


I don't know if that will work any better with Foo/convert,  
though... :-)


Thanks though Daniel - it's good to meet Enum and Bounded.

-Andy

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


Re: [Haskell-cafe] Ambiguous type variable with subclass instance (also: is there a better way to do this?)

2009-09-17 Thread Andy Gimblett


On 17 Sep 2009, at 16:50, Daniel Fischer wrote:

Yes, the second appearance of 'constructors' is at an unspecified  
type.


instance (Enumerated a) = Target a where
   convert n
  | n  0 = Nothing
  | otherwise = case drop n constructors of
   (x:_) - Just x
   _ - Nothing

would make it compile.


Neat trick.  It works: thanks!

But there'd be a risk that Target is unusable, depending on how  
instance resolution is

done.


Unusable?  How so?  Sorry, but I don't follow...

-Andy

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


Re: [Haskell-cafe] Re: Simple quirk in behavior of `mod`

2009-07-23 Thread Andy Gimblett

On 23 Jul 2009, at 11:59, Matthias Görgens wrote:

Round-to-even means x.5 gets rounded to x if x is even and x+1 if x  
is

odd. This is sometimes known as banker's rounding.


OK.  That's slightly unusual indeed.


It's meant to minimise total rounding error when rounding over large  
data sets; there's some discussion on wikipedia: http://en.wikipedia.org/wiki/Rounding


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


[Haskell-cafe] Typeclass default implementation in subclasses

2009-07-20 Thread Andy Gimblett

Hi all,

This email is literate Haskell.  I have a question about default
implementations of typeclasses.

 {-# LANGUAGE TypeSynonymInstances #-}

 module Thing where

 import Text.PrettyPrint.HughesPJ

Let say I want to pretty-print some values, enclosed in double quotes.
The natural thing to do (within the HughesPJ pretty-printing
framework, anyway - and that's where I am in this problem's wider
context) is:

 ppQuote :: Show a = a - Doc
 ppQuote = doubleQuotes . text . show

Now, this works nicely for (say) Int:

 x :: Int
 x = 1

*Thing ppQuote x
1

But less nicely for String and Char, because their Show instances
already insert double/single quotes respectively:

 y :: String
 y = hello
 z :: Char
 z = 'a'

*Thing ppQuote y
hello
*Thing ppQuote z
'a'

I don't want this.  I'd like them to be hello and a respectively.

So I thought I'd create a typeclass, whose default implementation is
as above...

 class (Show a) = Quotable a where
   quote :: a - Doc
   quote = ppQuote

... but with specialised instances for String and Char (the former
seems to need the TypeSynonymInstances extension?):

 instance Quotable String where
   quote = text . show -- don't need the doubleQuotes call for String
 instance Quotable Char where
   quote c = quote [c] -- just lift it to String

Unfortunately, while this works great for String and Char...

*Thing quote y
hello
*Thing quote z
a

... the default implementation mechanism doesn't work as I'd
expect/hope:

*Thing quote x

interactive:1:0:
No instance for (Quotable Int)
  arising from a use of `quote' at interactive:1:0-6
Possible fix: add an instance declaration for (Quotable Int)
In the expression: quote x
In the definition of `it': it = quote x

What I would _like_ would be for the compiler to say OK, the Quotable
class depends on the Show class, and Int is an instance of Show so Int
is also an instance of Quotable, having the default implementation
(since there isn't a specialised one for it) - but clearly it
doesn't.

Please can someone tell me why this doesn't happen, and if there is a
way of making it happen?  Also, if there's a more sensible way of
attacking this whole problem, I'd be curious to hear it.

I should perhaps add that this isn't a huge problem for me, because my
instances will in practice tend to be String and Char anyway, and one
can of course add Quotable instances for anything else easily enough -
but I'm curious now I've come this far.  :-)

Many thanks!

-Andy

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


Re: [Haskell-cafe] So far, so good! Until... (Haskell 98 Report questions)

2007-08-17 Thread Andy Gimblett
On Fri, Aug 17, 2007 at 04:50:02AM -0700, Ian Duncan wrote:

 So here's my list of questions so far:
 1. What are nonterminals?
 2. What are productions and substitutions?
 [snip]

Sounds to me like you want a book on language design, grammars,
parsing, etc. :-)

There are many good ones out there, but a quite nice, free, and (as it
happens, though it's irrelevant for this question) Haskellish example
is Grammars and Parsing by Jeuring  Swierstra (PDF, 1.2MB):

http://www.cs.uu.nl/docs/vakken/gont/diktaat.pdf

(Ignore the Dutch foreword, the rest is in English).  Chapter 2
answers the questions asked above, with copious examples and
exercises.

Hope this helps,

-Andy

-- 
Andy Gimblett
Computer Science Department
University of Wales Swansea
http://www.cs.swan.ac.uk/~csandy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Explaining monads

2007-08-15 Thread Andy Gimblett
On Tue, Aug 14, 2007 at 05:53:05PM -0700, Michael Vanier wrote:

 For what it's worth, the nature of Haskell is such that you do (at
 least currently) have to spend a lot of time reading research papers
 to understand what's going on.  Maybe that will change sometime, but
 probably not soon.  This ties in to the open-endedness of Haskell; I
 sometimes think that really understanding all of Haskell is like
 really understanding all of mathematics.  This is frustrating, but
 it's also what makes the language so rewarding.  I guess what I'm
 saying is: get used to it, it's not so bad.

At AngloHaskell, one of Phillipa's slides referred to Haskell as a
programming language theory gateway drug - and was clearly of the
opinion that this was A Good Thing.

-- 
Andy Gimblett
Computer Science Department
University of Wales Swansea
http://www.cs.swan.ac.uk/~csandy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Re[2]: Why monad tutorials don't work

2007-08-15 Thread Andy Gimblett
On Wed, Aug 15, 2007 at 12:50:42PM +, Dominic Steinitz wrote:
 Miguel Mitrofanov miguelimo38 at yandex.ru writes:
 
   Grrr...must...hold...my...tongue...
   
   Dan, as a former student of a clone of that physics teacher, I am really
   interested in what you will say when you fail to hold your tongue.
  
  MV I have to admit I was wondering the same thing myself.
  
  So was I.
  
 I'm guessing that Dan means that thinking of tensors as things that transform 
 between co-ordinate systems in a certain way (e.g. via the Jacobian of the 
 transition maps) isn't a terribly good way of thinking about them. Vector 
 fields, co-vector fields and tensor fields are really co-ordinate independent 
 notions and the transformation laws (if I may call them that) are a 
 consequence of the way they transform under (smooth) maps. But perhaps this 
 is 
 better discussed on a differential geometry mailing list?

I assumed he was just trying not to sing the Spider Pig song.

( http://uk.youtube.com/watch?v=5XQ_GWKvDE0 )

;-)

-- 
Andy Gimblett
Computer Science Department
University of Wales Swansea
http://www.cs.swan.ac.uk/~csandy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cartesian product of a Set

2007-08-02 Thread Andy Gimblett
On Thu, Aug 02, 2007 at 04:15:35PM +1200, ok wrote:
 
 On the other hand, I've usually found that it pays to avoid
 explicitly constructing things like Cartesian products.  Could that
 be the case here?

Quite possibly, though for my purposes I don't _think_ it's worth
routing around it.

I'm using it in a naive (and intentionally so) algorithm to search for
local top elements in a partial order.  That is, we require that the
PO satisfies the property:

for all a,b,c in PO . a = b and a = c
=
 exists d in PO . b = d and c = d

where a is a local bottom element for b and c, and d is the
corresponding local top element.  Given a PO, for every such a, I
want the set of corresponding d's.  If any such set is empty, a big
red NO lights up elsewhere in the program.

My algorithm is the simplest thing I could think of that works:
represent the PO as a Set of (a,a), then simply search its cartesian
product, a Set of ((a,a),(a,a)), for elements of the right shape.  It
works, in only a few lines of code, and really looks a lot like the
definition given above.

It also seems to be fast enough for reasonably sized examples - for a
PO with ~40 elements it's instantaneous.  That's at the bottom end of
realistic for my application, and I need to check it for ~100
elements (which is more like my reality), but I think it ought to be
fine/usable.

If, with real data, it turns out to be too slow then yes, I'll ditch
this naive method and look at graph algorithms, which is of course the
Smart thing to do.  However, it's beautiful (to me) code right now,
which strongly reflects the definition of the problem, so I'd be happy
not to.  :-)

Cheers,

-Andy

-- 
Andy Gimblett
Computer Science Department
University of Wales Swansea
http://www.cs.swan.ac.uk/~csandy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Cartesian product of a Set

2007-08-01 Thread Andy Gimblett
Hi all,

Is this a reasonable way to compute the cartesian product of a Set?

 cartesian :: Ord a = S.Set a - S.Set (a,a)
 cartesian x = S.fromList [(i,j) | i - xs, j - xs]
 where xs = S.toList x

It's a fairly obvious way to do it, but I wondered if there were any
hidden gotchas.  I'm particularly concerned by toList (O(n)) fromList
(O(n log n)) - but for other reasons I'd really like to be using Set
rather than List for this (I think).

Many thanks for any thoughts,

-Andy

-- 
Andy Gimblett
Computer Science Department
University of Wales Swansea
http://www.cs.swan.ac.uk/~csandy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cartesian product of a Set

2007-08-01 Thread Andy Gimblett
On Wed, Aug 01, 2007 at 01:42:52PM -0700, Dan Weston wrote:

 Andy Gimblett wrote:
 
 cartesian :: Ord a = S.Set a - S.Set (a,a)
 cartesian x = S.fromList [(i,j) | i - xs, j - xs]
 where xs = S.toList x
 
 Your list comprehension always generates a sorted list, so changing
 S.fromList to its unsafe version (but guarateed by you)
 S.fromDistinctAscList should get you back to O(n).

That'll do it: with that change, my program runs eight times faster;
according to the profiler, it's gone from spending ~85% of its time in
cartesian to ~0%.  :-)

I don't see why my list comprehension always generates a sorted list,
however: toList generates a sorted list?  It doesn't claim to in the
docs.  Do I perhaps need to use toAscList instead?

I happen to have put my data into the Set in order in this example, so
maybe I just lucked out?  Or am I missing something?

 Of course the order of the generators was key (i before j).

Lucky me.  :-)

Thanks!

-Andy

-- 
Andy Gimblett
Computer Science Department
University of Wales Swansea
http://www.cs.swan.ac.uk/~csandy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ghc for sunos

2005-09-09 Thread Andy Gimblett
On Fri, Sep 09, 2005 at 01:54:20PM +0200, Stephane Bortzmeyer wrote:
 
  I'm surrounded by Sun boxes here.
 
 One solution is to install Debian/GNU Linux on these, ghc runs fine
 on it :-)

Or NetBSD - very good on older hardware, in particular.

-Andy

-- 
Andy Gimblett
Computer Science Department
University of Wales Swansea
http://www.cs.swan.ac.uk/~csandy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem linking against Data.Graph

2005-07-15 Thread Andy Gimblett
On Fri, Jul 15, 2005 at 10:42:11AM -0700, Josh Hoyt wrote:

 I'm pretty new myself, but I ran into a similar problem using a
 different library. The problem is that some parts of the library are
 hidden by default, and you have to tell ghc to include them. To
 solve your immediate problem, add -package fgl to your compilation
 line.

*slaps forehead*

Of course!  I remember reading this now, but I had forgotten about it.
And I've already come across this requirement in the past with Parsec,
so I really should have thought of it...

Many thanks for your help!

-Andy

-- 
Andy Gimblett
Computer Science Department
University of Wales Swansea
http://www.cs.swan.ac.uk/~csandy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe