[Haskell-cafe] following up on space leak

2009-07-04 Thread Uwe Hollerbach
Good evening, all, following up on my question regarding space leaks,
I seem to have stumbled across something very promising. I said I was
using this tiny function "lastOrNil" to get the last value in a list,
or the empty (scheme) list if the haskell list was empty. The uses of
it were all of the form

lastOrNil (mapM  )

so I wrote a different function mapML to do this directly:

> mapML fn lst = mapMLA (List []) fn lst
>   where mapMLA r _ [] = return r
> mapMLA ro fn (x:xs) =
>do rn <- fn x
>   mapMLA rn fn xs

This isn't an accumulator, it's a replacer (or, if you like, the
"accumulation" is "drop the old one on the floor"), it starts out with
the scheme empty list that I want as the default, and it never even
builds the list which it'll just dump an instant later. Shazam! Memory
usage dropped by roughly an order of magnitude in my little Collatz
benchmark, and incidentally runtime improved by 25% or so as well. The
horror! :-)

Having tasted blood, I will of course be continuing to benchmark...
but not tonight.

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


Re: [Haskell-cafe] Cabal fun [Half-integer]

2009-07-04 Thread Andrew Coppin

Antoine Latter wrote:

Personally, I've never used "runhaskell Setup sdist" and I've only
ever used "cabal sdist". But I'm not sure where I learned that.

I think cabal-install is a pretty standard util for people to have,
and it ships with the Haskell platform now. So the big hurdle is
documentation.

Andrew - where does it state that "Setup sdist" is the recommended way
of doing this? If it's a wiki you could go and edit it yourself.
  


Start from the Hackage homepage:

 http://hackage.haskell.org/packages/hackage.html

Click on "how to create a Haskell package", takes you to

 http://www.haskell.org/haskellwiki/How_to_write_a_Haskell_program

Section 2.10.1.1 shows you how to create a tarball - using setup sdist 
rather than cabal sdist. Indeed, I don't think cabal-install is 
mentioned anywhere.


If people seriously want this to become the preferred way to do things, 
it needs to be much more prominently documented.


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


Re: [Haskell-cafe] following up on space leak

2009-07-04 Thread Marcin Kosiba
On Saturday 04 July 2009, Uwe Hollerbach wrote:
> Good evening, all, following up on my question regarding space leaks,
> I seem to have stumbled across something very promising. I said I was
> using this tiny function "lastOrNil" to get the last value in a list,
> or the empty (scheme) list if the haskell list was empty. The uses of
> it were all of the form
>
> lastOrNil (mapM  )
>
> so I wrote a different function mapML to do this directly:
> > mapML fn lst = mapMLA (List []) fn lst
> >   where mapMLA r _ [] = return r
> > mapMLA ro fn (x:xs) =
> >do rn <- fn x
> >   mapMLA rn fn xs
>
> This isn't an accumulator, it's a replacer (or, if you like, the
> "accumulation" is "drop the old one on the floor"), it starts out with
> the scheme empty list that I want as the default, and it never even
> builds the list which it'll just dump an instant later. Shazam! Memory
> usage dropped by roughly an order of magnitude in my little Collatz
> benchmark, and incidentally runtime improved by 25% or so as well. The
> horror! :-)

Hi,
IMHO expressing mapML using StateT would be a bit cleaner ;)

mapML :: (Monad m) => (a -> m List) -> [a] -> m List
mapML fn lst = execStateT mapMLAs (List [])
  where
mapMLAs  = sequence_ $ map mapMLA lst
mapMLA x = (lift $ fn x) >>= put

-- 
Marcin Kosiba


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


Re: [Haskell-cafe] ORM for haskell?

2009-07-04 Thread Alberto G. Corona
 And I realize that you are not trying to replace RDBs, just building a
> nicer interface to them. I am just concerned that some of the nice
> properties are lost in the process. I think my main concern comes from
> seeing people create databases, by automatically generating tables from
> OO-classes. They invariably ends up with something not nearly as nice,
> as if they had constructed the database in a more traditional fashion.
>

for web applications in the Internet, due to security reasons, 99% of the
databases are handled exlusively by te web application. This increases the
arguments in favor of spending less time in database design. Moreover, since
there are no concurrent updates from different applications, (communication
with other applications are done trough the middle tier of the web
application rather than trough the database), the database just provides
transaction coherence (for  the single application) and storage. Then it is
much faster to perform transactions in the application trough STM and leave
the database for storage purposes. At this time the database can be
substituted with advantage  by files.

All of this gives credit to ORM solutions and HappStack or SQLalchemy,
Database design and maintenance don't worth the pain in this scenario. My
package  TCache http://hackage.haskell.org/package/TCache is made also
around this philosophy.

If the ORM has an interface such is SQLalchemy, it would be nice to have two
"drivers" one for pure SQL databases, where all the primitives would be
executed in the database, and other pure Haskell where the primitives are
executed in memory. For example, the transactions would be executed trough
STM. This driver would have configurable persistence (either in files,
manualy designed databases or whatever) . Perhaps mixed drivers can be added
later. This would unite the best of both worlds. It would be flexible enough
to permit the change of scenario without breaking the code. This would be
nice for prototyping for example.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: HalfInteger-1.1.1

2009-07-04 Thread Andrew Coppin

Andrew Coppin wrote:
I just wrote a small module for dealing with half-integers. (That is, 
any number I/2 where I is an integer. Note that the set of integers is 
a subset of this; Wikipedia seems to reserve "half-integer" for such 
numbers that are *not* integers.)


Now, the question is... Is this useful enough to be worth putting on 
Hackage?


It's on Hackage:

  http://hackage.haskell.org/package/AC-HalfInteger-1.1.1

It'll be interesting to see if I uploaded it right... o_O

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


Re: [Haskell-cafe] ANN: HalfInteger-1.1.1

2009-07-04 Thread Felipe Lessa
On Sat, Jul 04, 2009 at 12:37:21PM +0100, Andrew Coppin wrote:
> It's on Hackage:
>
>   http://hackage.haskell.org/package/AC-HalfInteger-1.1.1
>
> It'll be interesting to see if I uploaded it right... o_O

I guess you did, congrats! :)

...on the Haddock comments of halve and double, it should be
"halve . double" and not "half . double", right?  You'll see that
after the first upload it is easy to do another one (hopefully).

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


Re: [Haskell-cafe] ANN: HalfInteger-1.1.1

2009-07-04 Thread Andrew Coppin

Felipe Lessa wrote:

On Sat, Jul 04, 2009 at 12:37:21PM +0100, Andrew Coppin wrote:
  

It's on Hackage:

  http://hackage.haskell.org/package/AC-HalfInteger-1.1.1

It'll be interesting to see if I uploaded it right... o_O



I guess you did, congrats! :)

...on the Haddock comments of halve and double, it should be
"halve . double" and not "half . double", right?  You'll see that
after the first upload it is easy to do another one (hopefully).
  


Well that's a good start. Already somebody has found a bug to be fixed. 
And in such a trivial package... o_O


Still, at least it's an easy fix. ;-) I don't think I'll bother making 
another upload just for this; the fix is applied to my local copy, but 
I'll wait until I have something more substantial to upload for the next 
version.


"Thanks for the report."

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


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-04 Thread Brandon S. Allbery KF8NH

On Jul 4, 2009, at 01:17 , Jason Dusek wrote:

 What is the proper name for the operation on functions of a
 functor, anyway? The name `fmap` seems to driven by an analogy
 with `map`.



 (.) 

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




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


[Haskell-cafe] Small Haddock question

2009-07-04 Thread Andrew Coppin

This is irritating me now... Suppose I have something like the following:

zero = 0 :: Int
one = 1 :: Int
two = 2 :: Int
three = 3 :: Int

How do I add Haddock comments to the end of each line? For some reason, 
Haddock doesn't like either of


zero = 0 :: Int -- | Zero
zero = 0 :: Int -- ^ Zero

Either way it whinges about parse errors. How do I make it shut up and 
stop being so dense at me? :-} It's damned obvious what I want it to do...



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


Re: [Haskell-cafe] Cont, ContT and IO()

2009-07-04 Thread Matthias Görgens
> process [] = return ()
> process (file:files) = do x <- doit file
>                          if x>0 then process files
>                                 else return ()

Or use a fold:

> process' = foldl op True files
> op True file = doit file
> op False _ = False
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cont, ContT and IO()

2009-07-04 Thread Matthias Görgens
>> process' = foldl op True files
>> op True file = doit file
>> op False _ = False

Please pardon me.  'doit' should surely be able to do some IO:

> import Data.Foldable
> import System.IO
> process' = foldlM op True files
> op True file = doit file
> op False _ = return False

were DoIt has the type FilePath -> IO Bool
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Cont, ContT and IO()

2009-07-04 Thread Bulat Ziganshin
Hello Matthias,

Saturday, July 4, 2009, 6:39:30 PM, you wrote:

> Or use a fold:

>> process' = foldl op True files
>> op True file = doit file
>> op False _ = False

foldM, probably, otherwise you will need to execute all actions before
running fold

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


[Haskell-cafe] Re: Cont, ContT and IO() - Code on hpaste

2009-07-04 Thread Günther Schmidt

Hi,

I've put the code that I wish to transform from using exceptions to using  
continuations on hpaste:


?http://hpaste.org/fastcgi/hpaste.fcgi/view?id=6515#a6515

thanks

Günther



Am 04.07.2009, 01:11 Uhr, schrieb Günther Schmidt :



Hi,

I've got an IO action, some file system IO, traversing one level only  
and iterating over files found. I wish to build in an "early" exit, ie.  
if an IO action in the loop encounters a particular value I want it to  
abort the loop.


Now so far, pls don't shoot, I have done this by throwing IO Exceptions  
and catching them. I'm trying to rewrite this using Continuatios /  
callCC but can't figure out where to place what.


I certainly don't have the intuition yet and funny enough not even in  
RWH I could find some Cont/ContT examples.


Would someone please draw me an example?

Günther




--
Erstellt mit Operas revolutionärem E-Mail-Modul: http://www.opera.com/mail/

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


Re: [Haskell-cafe] Re: Cont, ContT and IO() - Code on hpaste

2009-07-04 Thread Matthias Görgens
Hi Günther,

here is a solution with the Maybe Monad:

http://hpaste.org/fastcgi/hpaste.fcgi/view?id=6515#a6515

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


Re: [Haskell-cafe] Re: Cont, ContT and IO() - Code on hpaste

2009-07-04 Thread Matthias Görgens
P.S. See http://en.wikibooks.org/wiki/Haskell/Monad_transformers for
some documentation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Cont, ContT and IO() - Code on hpaste

2009-07-04 Thread Matthias Görgens
P.P.S. Strange it does not seem to work with the paste.  So here comes
the solution by mail:

module Consolidator.BusinessLogic.ConflictsResolved
(consolidateDuplicates) where

import System.FilePath
import System.Directory

import Control.Monad (filterM)
import Control.Exception (throwIO)

import System.Environment

import Data.Maybe
import Control.Monad
import Control.Monad.Trans

newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }

instance (Monad m) => Monad (MaybeT m) where
(>>=) tmb_v  f =
MaybeT (runMaybeT tmb_v
>>= \b_v -> case b_v of
  Nothing -> return Nothing
  Just v -> runMaybeT $ f v
   )
return = MaybeT . return . return

instance MonadTrans MaybeT where
lift mon = MaybeT (mon >>= return . Just)


abort :: String -> MaybeT IO a
abort reason = do lift . putStrLn $ reason
  MaybeT (return Nothing)

{-
The traversal is one directory deep only.
I try to find out if every immediate subdirectory contains exactly one
"*.gdr" file,
and collect the path names in a list, sgls.

Afterwards I append the contents of each such file to another file.

I want to abort the whole process as soon as I encounter a directory
that does not
include exactly one *.gdr file.

Currently I'm throwing exceptions but I'd prefer to rewrite this code
to use continuations.

-}



consolidateDuplicates :: FilePath -> MaybeT IO ()
consolidateDuplicates fp
= do dirs <- lift (getDirectoryContents fp)
 recs <- lift (filterM doesDirectoryExist $ map (fp ) $
filter (not . flip elem [".", ".."]) dirs)
 sgls <- mapM checkForSingle recs
 let cpy = fp  "Korrigiert.gdr"
 lift (copyFile (fp  "Konsolidiert.gdr") cpy)
 lift (mapM_ (\sgl -> do
str <- readFile sgl
appendFile cpy str) sgls)


checkForSingle :: FilePath -> MaybeT IO FilePath
checkForSingle fp = do
  cnt <- lift (getDirectoryContents fp)
  let fltr = filter ((== ".gdr") . takeExtension)
  case fltr cnt of
[]  -> abort ("The directory " ++ fp ++ " is empty")
[f] -> return (fp  f)
_   -> abort ("There is more than one file in the directory " ++ fp)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell Weekly News: Issue 124 - July 4, 2009

2009-07-04 Thread Brent Yorgey
---
Haskell Weekly News
http://sequence.complete.org/hwn/20090704
Issue 124 - July 04, 2009
---

   Welcome to issue 124 of HWN, a newsletter covering developments in the
   [1]Haskell community.

Announcements

   HLint 1.6. Neil Mitchell [2]announced the release of [3]HLint 1.6, a
   tool for automatically suggesting improvements to Haskell code.

   Haskell Implementers Workshop: accepted talks. Simon Marlow
   [4]announced that the list of talks at the [5]Haskell Implementers
   Workshop 2009 has now been posted.

   bloxorz clone. Patai Gergely [6]announced a [7]Haskell clone of the
   game "bloxorz", written by Viktor Devecseri.

   Fun with type functions. Simon Peyton-Jones [8]announced that he, Ken
   Shan, and Oleg have finished Version 2 of their [9]paper "Fun with Type
   Functions", which gives a programmer's tour of what type functions are
   and how they are useful. If you have a moment to look at, and wanted to
   help them improve it, leave comments on the linked wiki page.

   package Boolean: Generalized booleans. Conal Elliott [10]announced
   [11]Boolean, a new package for generalized booleans, which provides
   type classes with generalizations of Boolean values and operations,
   if-then-else, Eq and Ord.

   TernaryTrees-0.1.1.1 - An efficient ternary tree implementation of Sets
   and Maps. Alex Mason [12]announced the release of [13]TernaryTrees, a
   package that extends Data.Set ad Data.Map with some ternary tree
   structures, one of the more efficient ways of storing strings in a set.

   6.12.1 planning. Simon Marlow [14]announced plans for a release of GHC
   6.12.1, sometime around September. If you have the time and inclination
   to help with any of the listed features, please get involved!

   regular-0.1. José Pedro Magalhães [15]announced the release of the
   [16]regular library. Many generic programs require information about
   the recursive positions of a data type, such as generic fold, generic
   rewriting, and the Zipper data structure. Regular provides a fixed
   point view on data which allows these definitions for regular data
   types. It also serves as the basis for a [17]generic rewriting library.

Google Summer of Code

   Progress updates from participants in the 2008 [18]Google Summer of
   Code.

   Haddock improvements. Isaac Dupree has made it easier to generate
   Haddock documentation [19]for non-exported functions, posted an
   [20]overview of the issues involved in getting proper cross-package
   documentation working, and his current [21]plan.

   EclipseFP. Thomas Ten Cate has done a lot of work on EclipseFP,
   including some [22]cosmetic updates and getting [23]error reporting to
   work better.

   space profiling. Gergely Patai is [24]working on a network protocol for
   his profiling grapher tool, so that other tools can monitor the
   profiling information.

   haskell-src-exts. Niklas Broberg has [25]released [26]haskell-src-exts
   version 1.0.0!

   fast darcs. Petr Rockai has completed [27]quite a bit of work on darcs,
   including a [28]beta release of darcs 2.3.

Discussion

   Monoid wants a (++) equivalent. Bryan O'Sullivan [29]suggested adding a
   more concise operator to the Monoid class for 'mappend', leading to a
   long, bike-shed-ish (but hopefully still useful) discussion.

   Reflections on the ICFP 2009 programming contest. Justin Bailey began a
   [30]discussion on results and experiences from the ICFP 2009
   programming contest.

Blog noise

   [31]Haskell news from the [32]blogosphere. Blog posts from people new
   to the Haskell community are marked with >>>, be sure to welcome them!
 * Gergely Patai: [33]Playing and learning.
 * Ketil Malde: [34]A set of tools for working with 454 sequences.
 * Sebastian Fischer: [35]FP Overview.
 * Magnus Therning: [36]Making a choice from a list in Haskell, Vty
   (part 1).
 * David Amos: [37]Conjugacy classes, part 1.
 * Well-Typed.Com: [38]GHC and Windows DLLs.
 * Manuel M T Chakravarty: [39]Converting typed term representations:
   from HOAS to de Bruijn..
 * >>> Ivan Uemlianin: [40]Haskell: sort and sortBy.
 * Gregory Collins: [41]Building a website with Haskell, part 3.
 * Michael Snoyman: [42]Hack sample- chat server.
 * Luke Palmer: [43]On the By functions.
 * Magnus Therning: [44]Dataenc finally making it into Debian.
 * Thomas ten Cate: [45]New build instructions.
 * Erik de Castro Lopo: [46]Three More for the Debian New Queue.
 * >>> Yuval Kogman: [47]What Haskell did to my brain.
 * Greg Bacon: [48]FFI: calling into kernel32.dll.
 * Greg Bacon: [49]Setting up a simple test with Cabal.
 * Ketil Malde: [50]Dephd updates.
 * Bryan O'Sullivan: [51]What's in a 

Re: [Haskell-cafe] Small Haddock question

2009-07-04 Thread Denis Bueno
On Sat, Jul 4, 2009 at 08:22, Andrew Coppin wrote:
> This is irritating me now... Suppose I have something like the following:
>
> zero = 0 :: Int
> one = 1 :: Int
> two = 2 :: Int
> three = 3 :: Int
>
> How do I add Haddock comments to the end of each line? For some reason,
> Haddock doesn't like either of
>
> zero = 0 :: Int -- | Zero
> zero = 0 :: Int -- ^ Zero
>
> Either way it whinges about parse errors. How do I make it shut up and stop
> being so dense at me? :-} It's damned obvious what I want it to do...

I think top-level definitions can only be commented in one way:

-- | Emptiness and void, as an Int.
zero = 0 :: Int


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


[Haskell-cafe] Flow Graphs for Language-independent Code Representation

2009-07-04 Thread Cetin Sert
Hi *^o^*,

I'm working on a source code transformation project for numerical automatic
differentiation for Fortran and C.

I would love to know the best Haskell way/package available today to
represent procedural (non-OO) code in a language-independent manner. Any
tips or resource, paper references are most welcome!

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


Re: [Haskell-cafe] ANN: HalfInteger-1.1.1

2009-07-04 Thread Andrew Coppin

Alexander Dunlap wrote:

Couple of suggestions:

- You should put an (Integer i) => constraint on the halve function so
that it becomes impossible to create invalid HalfIntegers.
  


Right. Currently you can *make* such a HalfInteger. You just won't be 
able to *do* anything with it afterwards. It would probably be more 
sensible to just add a constraint there.



- The documentation for toHalfInteger is truncated. Also, why can't
you make the rounding more predictable?
  


...wow. OK, I'm looking at the source, and it seems I must have got 
distracted at that moment or something, because I just 100% didn't 
actually finish writing the documentation! o_O That's pretty special. ;-)


As I *should* have written, the rounding for something like 
toHalfInteger 0.25 is kind of unpredictable; but if you do toHalfInteger 
0.5, the result is *guaranteed* to be exact. All the functions are 
carefully tuned to work correctly on things which really are half 
integers, and to give plausible results otherwise. Just don't let your 
life depend on 0.25 being mapped to exactly a half or to exactly zero...



Nice work!
  


Heh, thanks.

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


[Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK

2009-07-04 Thread Andrew Coppin
OK, so having released AC-HalfInteger, I got slightly carried away and 
released three other small packages. These are packages that many 
programs I write all end up using. I'm forever copying these files, so I 
made them into actual bonafide packages.



http://hackage.haskell.org/package/AC-Vector-1.1.1

This provides two types, Vector2 and Vector3, which are unboxed vectors 
of Doubles, with arithmetic, dot product and cross product, and a few 
other useful items.



http://hackage.haskell.org/package/AC-Colour-1.1.1

This provides two types, Colour and Colour8. Both implement simple RGB 
colour types with arithmetic. Colour has unboxed Double fields, and 
Colour8 has unboxed Word8 fields. My usual workflow is to do all the 
image generation with Colour, and to convert to Colour8 just before the 
data hits the I/O channels. You can, however, do arithmetic directly on 
Colour8. (I haven't extensively tested that it works properly though...)



http://hackage.haskell.org/package/AC-EasyRaster-GTK-1.1.1

This is a layer over Gtk2hs. As you all probably know, Gtk2hs provides a 
Cairo binding that makes vector graphics wonderfully easy. However, 
*bitmapped* graphics is darned tricky. I basically had to sit in the 
#haskell channel with Duncan for a few hours trying to figure out how 
the hell to do it. This knowledge is now codified in the above package. 
Load it up and you don't need to know a thing about GTK; you can just 
create an ImageBuffer, write some pixels to it (efficiently!), save it 
to disk or display it on screen. (But you *can* access the underlying 
GTK+ resources if you wish...)



In other news, it appears that the batch job to generate the 
documentation just ran, so you can view it all online. :-D


Comments, suggestions, random flames, etc...

[I'm particularly curios to know what Duncan will make of the GTK thing...]

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


Re: [Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK

2009-07-04 Thread Felipe Lessa
On Sat, Jul 04, 2009 at 06:56:44PM +0100, Andrew Coppin wrote:
> http://hackage.haskell.org/package/AC-Colour-1.1.1

Why don't you use colour[1]?

[1] http://hackage.haskell.org/package/colour

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


Re: [Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK

2009-07-04 Thread Andrew Coppin

Felipe Lessa wrote:

On Sat, Jul 04, 2009 at 06:56:44PM +0100, Andrew Coppin wrote:
  

http://hackage.haskell.org/package/AC-Colour-1.1.1



Why don't you use colour[1]?

[1] http://hackage.haskell.org/package/colour
  


A few reasons:

1. I never knew it existed. ;-)

2. It's mind-blowingly complex.

3. It doesn't appear to provide arithmetic over colours.

4. It's parameterised over the component type; my library is hard-coded 
to specific types for speed.


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


Re: [Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK

2009-07-04 Thread Max Rabkin
On Sat, Jul 4, 2009 at 8:38 PM, Andrew
Coppin wrote:
> A few reasons:
>
> 1. I never knew it existed. ;-)

A good reason. However, it's good to do a quick search over Hackage
before uploading (or before writing) so you know what's out there.

Also, if you hadn't used an "AC-" prefix, you'd have had a name
collision. Is there a particular reason why you want your name in the
package name rather than just the author field?

> 2. It's mind-blowingly complex.

Colour *is* complex. Which is why I'm so glad Russell O'Connor did all
the hard work for me :)

> 3. It doesn't appear to provide arithmetic over colours.

It provides darken, blend and addition (though addition is called
mappend rather than (+)). signum, abs and fromInteger don't make a
huge amount of sense for colours.

> 4. It's parameterised over the component type; my library is hard-coded to
> specific types for speed.

My feeling would be to trust the specializer until it lets me down.
Has it let you down in the past?

BTW, the EasyRaster package looks useful.

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


Re: [Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK

2009-07-04 Thread Andrew Coppin

Max Rabkin wrote:

On Sat, Jul 4, 2009 at 8:38 PM, Andrew
Coppin wrote:
  

A few reasons:

1. I never knew it existed. ;-)



A good reason. However, it's good to do a quick search over Hackage
before uploading (or before writing) so you know what's out there.
  


Fair enough. ;-)


Also, if you hadn't used an "AC-" prefix, you'd have had a name
collision. Is there a particular reason why you want your name in the
package name rather than just the author field?
  


Well, for example, there's seemingly half a dozen unrelated packages all 
called "binary", which is just confusing. I wanted to make sure my 
packages had unique names. (I mean, so do the existing binary packages, 
just not very useful ones...)



2. It's mind-blowingly complex.



Colour *is* complex. Which is why I'm so glad Russell O'Connor did all
the hard work for me :)
  


Well, no, because now I'm going to have to spend a few hours trying to 
find out what CIE is before I can even use that library.


I think really it's just aimed at a different problem. It looks like 
it's trying to specify actual real-world colours. [It's news to me that 
this isn't fundamentally impossible...] I'm only trying to specify 
colours on a computer screen. And as we all know, computer screens 
aren't calibrated in any way, and the same RGB value looks different on 
each display. But then, I'm only trying to write a fractal generator, so 
CIE specifications are somewhat overkill here. ;-)



3. It doesn't appear to provide arithmetic over colours.



It provides darken, blend and addition (though addition is called
mappend rather than (+)). signum, abs and fromInteger don't make a
huge amount of sense for colours.
  


Yeah, I implemented signum and so forth for colours and vectors, but 
they're not particularly meaningful... [Insert remark here about 
Haskell's numeric class hierachy.]


So mappend gives you colour addition [with the perplexing comments about 
"gamut", presumably some kind of small mammal?], but there's no 
subtraction? No multiplication? No linear blending?



4. It's parameterised over the component type; my library is hard-coded to
specific types for speed.



My feeling would be to trust the specializer until it lets me down.
Has it let you down in the past?
  


Heh, my colour library includes a custom floor implementation that talks 
to the GHC primops directly because calling floor is too slow...


[In case that sounds like idle talk, I had a program go from 10 seconds 
to less than 1 second just by using this function. There's a few tickets 
about it on the GHC Trac.]



BTW, the EasyRaster package looks useful.
  


Well, I'd like to think so... It doesn't do anything you couldn't do 
yourself if you spend a day or two trying to grok the GTK complexity. 
But it's much easier to just import some code somebody else has already 
written. ;-) Certainly when I'm in the middle of trying to build a 
complicated bit of software, figuring out how to just write a few pixels 
onto the screen is a low priority.


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


Re: [Haskell-cafe] following up on space leak

2009-07-04 Thread Uwe Hollerbach
On 7/4/09, Marcin Kosiba  wrote:
> On Saturday 04 July 2009, Uwe Hollerbach wrote:
>> Good evening, all, following up on my question regarding space leaks,
>> I seem to have stumbled across something very promising. I said I was
>> using this tiny function "lastOrNil" to get the last value in a list,
>> or the empty (scheme) list if the haskell list was empty. The uses of
>> it were all of the form
>>
>> lastOrNil (mapM  )
>>
>> so I wrote a different function mapML to do this directly:
>> > mapML fn lst = mapMLA (List []) fn lst
>> >   where mapMLA r _ [] = return r
>> > mapMLA ro fn (x:xs) =
>> >do rn <- fn x
>> >   mapMLA rn fn xs
>>
>> This isn't an accumulator, it's a replacer (or, if you like, the
>> "accumulation" is "drop the old one on the floor"), it starts out with
>> the scheme empty list that I want as the default, and it never even
>> builds the list which it'll just dump an instant later. Shazam! Memory
>> usage dropped by roughly an order of magnitude in my little Collatz
>> benchmark, and incidentally runtime improved by 25% or so as well. The
>> horror! :-)
>
> Hi,
>   IMHO expressing mapML using StateT would be a bit cleaner ;)
>
> mapML :: (Monad m) => (a -> m List) -> [a] -> m List
> mapML fn lst = execStateT mapMLAs (List [])
>   where
> mapMLAs  = sequence_ $ map mapMLA lst
> mapMLA x = (lift $ fn x) >>= put
>
> --
> Marcin Kosiba

Yeah, I'm sure there are more-elegant ways to write this, I'm still
very much a beginner in haskell. I'm just very thrilled by the
reduction in memory usage!

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


Re: [Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK

2009-07-04 Thread Max Rabkin
On Sat, Jul 4, 2009 at 9:18 PM, Andrew
Coppin wrote:
>>> 2. It's mind-blowingly complex.
>>>
>>
>> Colour *is* complex. Which is why I'm so glad Russell O'Connor did all
>> the hard work for me :)
>>
>
> Well, no, because now I'm going to have to spend a few hours trying to find
> out what CIE is before I can even use that library.

The sRGB function makes a Colour from RGB (actually sRGB, which is a
"standardised" RGB -- basically RGB where the exact frequency and
power of each channel is specified -- but you can pretend your
monitor's RGB is sRGB.

> So mappend gives you colour addition [with the perplexing comments about
> "gamut", presumably some kind of small mammal?]

The gamut of a device is the range of representable colours (a
monitor's gamut looks something like a parabola with a flat base in
XYZ space, whereas a printer's is much more complex and variable).
This makes sense. If you double a monitor's brightest white, you don't
get a colour twice as bright: you get the same colour.

> but there's no subtraction?
> No multiplication? No linear blending?

affineCombo can do subtraction, again with the gamut warning. darken
does scalar multiplication; it probably doesn't do componentwise
multiplication, which doesn't make much sense if you're trying to work
in a coordinate-independent setting, though I admit RGB-multiplication
can be handy.

> Heh, my colour library includes a custom floor implementation that talks to
> the GHC primops directly because calling floor is too slow...
>
> [In case that sounds like idle talk, I had a program go from 10 seconds to
> less than 1 second just by using this function. There's a few tickets about
> it on the GHC Trac.]

Fair enough. Can your implementation not be turned into a patch?

BTW, I'm also working on Haskell fractals. You might be interested in
looking at my fractal package (though it's currently undocumented, and
has no GUI).

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


Re: [Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK

2009-07-04 Thread Andrew Coppin

Paul Johnson wrote:

Andrew Coppin wrote:
Well, no, because now I'm going to have to spend a few hours trying 
to find out what CIE is before I can even use that library.


I think really it's just aimed at a different problem. It looks like 
it's trying to specify actual real-world colours. [It's news to me 
that this isn't fundamentally impossible...] I'm only trying to 
specify colours on a computer screen. And as we all know, computer 
screens aren't calibrated in any way, and the same RGB value looks 
different on each display. But then, I'm only trying to write a 
fractal generator, so CIE specifications are somewhat overkill here. ;-)
Your display may not be calibrated, but those used for graphic design 
certainly are.


Indeed. And if you're in any kind of position where you *care* about 
such things, you should be using color, not AC-Colour. If, however, you 
just want to throw together pretty pictures, AC-Colour is simpler and 
easier. Different libraries for slightly different tasks. ;-)


On the package naming front: I appreciate your wish to avoid just 
having another "colour" library.  But "AC_Colour" doesn't help much.  
"Simple_colour" might be better.


Mmm, yeah. Naming everything with "AC" precludes name clashes and 
doesn't require too much thinking. Coming up with a better name requires 
thinking about what actually makes your package unique. And, of course, 
if another package comes along, that analysis may change. (E.g., I seem 
to recall there's a "newbinary" package which has actually been long 
since superceeded - so not so "new" any more!) If I name my package 
simple-colour, and then somebody else makes an even simpler one... the 
name becomes kind of meaningless. (Admitedly there's not too much danger 
of this happening...)


I just like the idea of having definitely unique, distinctive package 
names. Otherwise I'd have to come up with stuff like geovector and 
trivicolour and so on... Arguably EasyRaster-GTK should have been a 
sufficiently unique name by itself though.


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


[Haskell-cafe] Optimizing Compiler for the ICFP 09 contest's VM

2009-07-04 Thread Matthias Görgens
The byte code for the virtual machine of this years ICFP specified a
language with single assignment per simulation step.  Interestingly
most memory locations get overwritten each simulation step before they
are read.  That means, those locations don't have to be remember
between steps.  Also locations that never get overwritten (e.g.
location associated with Noops), are constant.  Thus the variables
state of the simulation is orders of magnitude smaller than the naive
2^16 * 32 bit + 1 bit.

I wrote a small program that analyses the dataflow of a byte code
program (and initial memory setup) for the VM.  After analyzing my
program emits Haskell code to run the given byte code.

If anyboby is interested, I can document my program and put it online
somewhere.  I also made pretty graphs of the dataflow with graphviz.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Optimizing Compiler for the ICFP 09 contest's VM

2009-07-04 Thread minh thu
2009/7/4 Matthias Görgens :
> The byte code for the virtual machine of this years ICFP specified a
> language with single assignment per simulation step.  Interestingly
> most memory locations get overwritten each simulation step before they
> are read.  That means, those locations don't have to be remember
> between steps.  Also locations that never get overwritten (e.g.
> location associated with Noops), are constant.  Thus the variables
> state of the simulation is orders of magnitude smaller than the naive
> 2^16 * 32 bit + 1 bit.
>
> I wrote a small program that analyses the dataflow of a byte code
> program (and initial memory setup) for the VM.  After analyzing my
> program emits Haskell code to run the given byte code.
>
> If anyboby is interested, I can document my program and put it online
> somewhere.  I also made pretty graphs of the dataflow with graphviz.

Hi Matthias,

it would be nice to blog a little post about what you found and the
pretty graphs :)

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


Re: [Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK

2009-07-04 Thread Brandon S. Allbery KF8NH

On Jul 4, 2009, at 15:01 , Max Rabkin wrote:

On Sat, Jul 4, 2009 at 8:38 PM, Andrew
Coppin wrote:

3. It doesn't appear to provide arithmetic over colours.


It provides darken, blend and addition (though addition is called
mappend rather than (+)). signum, abs and fromInteger don't make a
huge amount of sense for colours.


I don't see a good meaning for signum offhand, but fromInteger could  
take an X11-encoded RGB value and abs could produce grayscale  
brightness.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




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