Re: [Haskell-cafe] Re: Don't “accidentallyparallel ize”

2009-09-05 Thread David Menendez
On Sat, Sep 5, 2009 at 7:57 PM, Dan Doel wrote:
>
> I suppose technically, what foldl' has over foldl is that it is more readily
> subject to optimization. Each recursive call is artificially made strict in
> the accumulator, so it is legal for GHC to optimize the function by keeping
> the accumulator evaluated, instead of delaying it. When GHC is run with
> optimizations on, it does analysis on all code that tries to determine such
> things, and seq can be seen as making such analysis easier for the compiler.

It turns out, pseq limits the effectiveness of strictness analysis,
because it forces the order of evaluation. John Meacham described this
pretty well last week in the Haskell' list
.

> This is, of course, not what really happens in GHC. What really happens is
> that the first argument to seq is evaluated before the second (which is why it
> even has the intended effect when optimizations aren't on). But that doesn't
> have to be the case, strictly speaking.

It's entirely possible for optimized code to end up evaluating the
second argument to seq before the first.

-- 
Dave Menendez 

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


[Haskell-cafe] How to customize dyre recompile?

2009-09-05 Thread Andy Stewart
Hi all,

I use below params for configure dyre:

rebootParams :: Params Config
rebootParams = defaultParams
{projectName = "Main"
,realMain= manatee
,showError   = rebootShowError
,cacheDir= Just $ return "/test/Download/cache/"
,configDir   = Just getCurrentDirectory
}

There have two version of function `reboot` to reboot Master binary:

reboot :: IORefObject -> IO ()
reboot ioRefObject = do
  rs <- rebootGetState ioRefObject
  relaunchWithBinaryState rs Nothing

reboot :: IORefObject -> IO ()
reboot ioRefObject = do
  output <- customCompile rebootParams
  case output of
Just o -> putStrLn o   -- output recompile error
Nothing -> do  -- otherwise relaunch
  rs <- rebootGetState ioRefObject
  relaunchWithBinaryState rs Nothing

Becuase i setup `projectName` with `Main`, so i want `dyre` recompile
NECESSARY module when i change any module in my project.

In first version of function `reboot`, i just use
`relauncheWithBinaryState`, i found `dyre` just recompile all project when i
modified Main.hs, if i modified any others module in project, `dyre`
won't recompile those modified modules.

In second version, i use `customCompile` for recompile, but this have
another problem, `customComiple` use `-fforce-recomp` flags to remove
all object files, so function `customComiple` will recompile all modules
in project, and not just recompile NECESSARY modules.

So how to make `dyre` just recompile NECCESSARY modules whatever i
change any modules in project?

Maybe add new option "--dyre-reconf-necessary" in `dyre`?

Thanks!

  -- Andy

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


Re: [Haskell-cafe] Re: ANN: vty-4.0.0.1 released

2009-09-05 Thread Corey O'Connor
On Sat, Sep 5, 2009 at 2:30 PM, John Pybus wrote:
> Corey O'Connor  gmail.com> writes:
> Err, I haven't paid my 86 Francs to find out, but ISO-10464 appears to specify
> testing regimes for gas cylinders -- a very worthy thing to do, but seemingly
> unrelated to terminal output.
>
> http://www.iso.org/iso/catalogue_detail.htm?csnumber=34234
>
> I suspect you mean ISO-10646, if so you might want to correct its appearance 
> in
> the API.

lol. You are correct :-) I'll push out an update soon with this and a
few other small changes.

Cheers,
Corey O'Connor
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trying to reduce memory costs of String duplicates

2009-09-05 Thread wren ng thornton

Günther Schmidt wrote:

Hi all,

I'm reading in a data of 216k records into a map of Key, Values Pairs, 
the values being strings.


As it happens out of 216k String values there really are only about 6.6k 
distinct string values, so I could save a lot of RAM if I was able to 
"insert" only actually *new* string values into the map and use 
references to (string) values that already are in memory instead.


Is there a container that would, if I wanted to insert an element, 
return a pair of either the previously inserted, equal value and the 
container unchanged, or the new, previously unknown value and the new 
container amended by that element?


If by "strings" you allow ByteStrings, then you could use the 
bytestring-trie package[1]. This will be more worthwhile than other 
approaches if your 6.6k strings have a lot of repeated prefixes, since 
repeated prefixes will be shared among the unique strings.


Something like the following should work:

intern:: ByteString -> Trie ByteString
  -> (ByteString, Trie ByteString)

intern s t = (fromJust (lookup s t'), t')
where
t' = alterBy (\_ _ -> maybe (Just s) Just) s s t


[1] 
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bytestring-trie


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Don't “accidentallyparallelize”

2009-09-05 Thread Dan Doel
On Saturday 05 September 2009 9:13:50 am Gracjan Polak wrote:
> [quote]
> Indeed, if GHC was in the habit of causing the second argument of seq to be
> evaluated before the first, then a lot of people would probably be
>  surprised. eg. imagine what happens to foldl':
> 
>   foldl' f a [] = a
>   foldl' f a (x:xs) = let a' = f a x in a' `seq` foldl' f a' xs
> 
> It wouldn't do what you want at all.
> [/quote]
> 
> So... seems foldl' relies on `seq` having unstated evaluation order in GHC.
> So, what guarantees does foldl' have in turn? Semantics only or
>  operational? Shouldn't it be written using `pseq`?
> 
> Seems I have always used (this `seq` that) when I meant (this `before`
>  that). Is it time to revisit my code and use `pseq` more?
> What does Haskell' say about this?

I suppose technically, what foldl' has over foldl is that it is more readily 
subject to optimization. Each recursive call is artificially made strict in 
the accumulator, so it is legal for GHC to optimize the function by keeping 
the accumulator evaluated, instead of delaying it. When GHC is run with 
optimizations on, it does analysis on all code that tries to determine such 
things, and seq can be seen as making such analysis easier for the compiler.

This is, of course, not what really happens in GHC. What really happens is 
that the first argument to seq is evaluated before the second (which is why it 
even has the intended effect when optimizations aren't on). But that doesn't 
have to be the case, strictly speaking.

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


Re: [Haskell-cafe] Trying to reduce memory costs of String duplicates

2009-09-05 Thread Felipe Lessa
On Sun, Sep 06, 2009 at 01:35:08AM +0200, Günther Schmidt wrote:
> However so far I'm unable to tell wether this actually works or not,
> I tried it a couple of times under different settings but it showed
> to difference in memory consumption. The same mem peeks as before.

You may want to use 'vacuum', it shows how data is internally
represented on GHC, including sharing.

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


Re: [Haskell-cafe] Trying to reduce memory costs of String duplicates

2009-09-05 Thread Günther Schmidt

Hi Luke,

thanks, this is some very good advice as I find many duplicates in the  
data I have to iterate over.


However so far I'm unable to tell wether this actually works or not, I  
tried it a couple of times under different settings but it showed to  
difference in memory consumption. The same mem peeks as before.


Do you have some code that where you could see a before and after?

Günther


Am 05.09.2009, 19:38 Uhr, schrieb Luke Palmer :


2009/9/5 Günther Schmidt :

Hi all,

I'm reading in a data of 216k records into a map of Key, Values Pairs,  
the

values being strings.

As it happens out of 216k String values there really are only about 6.6k
distinct string values, so I could save a lot of RAM if I was able to
"insert" only actually *new* string values into the map and use  
references

to (string) values that already are in memory instead.

Is there a container that would, if I wanted to insert an element,  
return a

pair of either the previously inserted, equal value and the container
unchanged, or the new, previously unknown value and the new container
amended by that element?


I believe a memoization of the identity function will do what you want:

import qualified Data.MemoCombinators as Memo

share = Memo.list Memo.char id

Then pass any string through share to make/get a cached version.

You might want to limit the scope of share -- eg. put it in a where
clause for the function where you're using it -- so that it doesn't
eat memory for the lifetime of your program, only for when you need
it.

Luke


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


[Haskell-cafe] Re: [Haskell] Looking for a new HWN editor

2009-09-05 Thread Brent Yorgey
On Sat, Sep 05, 2009 at 05:26:08PM -0400, Brent Yorgey wrote:
> Executive summary:
> 
>   * I'm looking for someone to take over as HWN editor
>   * It is highly automated and doesn't take as much time as you might
> think (about 3-4 hours/week on average)
>   * You DON'T need to be a Haskell guru
>   * It is far from a thankless job and is a fun way to provide an
> appreciated service to the community!

The position has been filled!  More details to come.

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


[Haskell-cafe] ForeignFunPtr

2009-09-05 Thread Maurí­cio CA

Hi,

We have ForeignPtr. Why isn't there a
corresponding ForeignFunPtr?


Thanks,
Maurício

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


[Haskell-cafe] Re: ANN: vty-4.0.0.1 released

2009-09-05 Thread John Pybus
Corey O'Connor  gmail.com> writes:

> 
> Vty is a terminal UI library. Release 4.0.0.1 brings a number of
> important fixes,
> features, and performance enhancements.


>   - added a "utf8_string" and "string" (AKA "iso_10464_string") for UTF-8
> encoded Strings and ISO-10464 encoded Strings. String literals in GHC
> have an ISO-10464 runtime representation.

Err, I haven't paid my 86 Francs to find out, but ISO-10464 appears to specify
testing regimes for gas cylinders -- a very worthy thing to do, but seemingly
unrelated to terminal output.

http://www.iso.org/iso/catalogue_detail.htm?csnumber=34234

I suspect you mean ISO-10646, if so you might want to correct its appearance in
the API.

John

PS: Typos aside, I'm excited to see the progress in vty.  Thanks.


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


[Haskell-cafe] Looking for a new HWN editor

2009-09-05 Thread Brent Yorgey
Executive summary:

  * I'm looking for someone to take over as HWN editor
  * It is highly automated and doesn't take as much time as you might
think (about 3-4 hours/week on average)
  * You DON'T need to be a Haskell guru
  * It is far from a thankless job and is a fun way to provide an
appreciated service to the community!

Read on for more details!

-

Hi all,

As you probably know, I've been the editor of the Haskell Weekly News
for a little over a year now, and I've decided that it's time for me
to move on to other things.  So, I'm looking for someone to volunteer
to take over as HWN editor.

Why might you want to do this?  It's true that there is no concrete
reward.  But judging from the number of comments I have received from
people over the past year, the HWN provides a valuable and appreciated
service to the Haskell community: there are many who simply don't have
time to read the mailing lists, but like to know about new libraries,
compiler releases, interesting discussions, and other major goings-on
in the community.

What does the editorship entail?  Thanks to some automated tools
developed specifically for the job, it doesn't take as much time as
you might think: usually about 4 hours per week; most of that is spent
simply reading/skimming various Haskell mailing lists to pick out
items for the HWN.  The process generally goes like this:

  * pick out funny quotes from the IRC channel using an automated tool
  * pick out Haskell-related blog posts using an automated tool
  * pick out announcements and discussions from the mailing list with
an automated tool, writing a short blurb for each (usually this
just involves cutting and pasting from the announcement itself,
with a bit of editing to make it flow
  * compile text and HTML versions with an automated tool
  * post to sequence.complete.org and the mailing list.

There are much more detailed instructions written up, and of course
I'll be happy to provide detailed help and support for the first few
weeks of the new editor's tenure.

I should emphasize that the HWN editor does NOT need to be a Haskell
guru.  In fact, this could be an ideal job for someone who is
relatively new to Haskell and the community, but would like to
contribute in a tangible way.

I also want to emphasize that with the change in editorship, the HWN
need not remain exactly the same: if you have exciting ideas about
changes to make to the format or content, be my guest!  The HWN will
be whatever you make of it.

So, let me know if you are interested!  There won't be any formal
interview process; the first person to contact me who wants to do it,
gets the job.  But of course, if you are not sure and want more
information, feel free to email me with questions.

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


[Haskell-cafe] Haskell Weekly News: Issue 129 - September 5, 2009

2009-09-05 Thread Brent Yorgey
---
Haskell Weekly News
http://sequence.complete.org/hwn/20090905
Issue 129 - September 05, 2009
---

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

   The [2]Haskell Symposium was a great success, with many [3]interesting
   talks and a good discussion on the future of Haskell. Watch this space
   for links to video from the Symposium as it becomes available!

Announcements

   HStringTemplate 0.6.2. Sterling Clover [4]announced some new features
   in the [5]HStringTemplate library, including simple quasiquotation;
   proper Unicode support; creation of groups from hierarchies of
   directories; separators applied within iterated template application;
   depthwise chained iterated template application; generalized encoding
   functions; and more.

   fclabels-0.4.0 - First class accessor labels. Sebastiaan Visser
   [6]announced a new release of the [7]fclabels package, straight from
   ICFP in Edinburgh. The package provides first-class labels which act as
   fully composable, bidirectional record fields, as well as support for
   automatically generating them from record types.

   vty-4.0.0.1 released. Corey O'Connor [8]announced release 4.0.0.1 of
   [9]vty, a terminal UI library. This release brings a number of
   important fixes, features, and performance enhancements, including a
   completely rewritten output backend; efficient, "scanline
   rasterization" style output span generator; terminfo based display
   terminal implementation; improved Unicode support; 256 color support;
   and more.

   haskell-src-exts-1.1.4. Niklas Broberg [10]announced the release of
   [11]haskell-src-exts-1.1.4, a package for Haskell source code
   manipulation. The experimental code in Language.Haskell.Annotated{.*}
   has changed quite a lot, although the stable portion of the package
   interface has not changed. Significantly, the package now includes an
   exact-printer which allows round-tripping between parsing and
   pretty-printing to be the identity.

   Next BostonHaskell meeting: September 16th at MIT (32G-882).
   Ravi Nanavati [12]announced the September meeting of the Boston Area
   Haskell Users' Group, to be held Wednesday, September 16th from 7pm -
   9pm. As usual, it will be held in the MIT CSAIL Reading Room (32-G882,
   on the 8th floor of the Gates Tower of the MIT's Stata Center at 32
   Vassar St in Cambridge, MA). The featured speaker will be Edward Kmett,
   who will be presenting the second part of his monoids and parsing
   presentation: "A Parallel Parsing Trifecta: Iteratees, Parsec, and
   Monoids".

   lenses -- Simple Functional Lenses. Job Vranish [13]announced the
   release of [14]lenses, a simple but powerful implementation of function
   lenses (aka functional references/accessors). This library provides a
   convenient way to access and update the elements of a structure. It is
   very similar to Data.Accessors, but simpler, a bit more generic and has
   fewer dependencies.

   Dutch HUG: meeting next week (September 11th) in Utrecht. Tom Lokhorst
   [15]invited functional programmers in The Netherlands to the [16]Dutch
   Haskell User Group, meeting Friday, September 11 at 19:00 in the
   [17]Booth Hall of the Utrecht University Library. Thomas (noknok) will
   be talking about his system for doing propositional logic in Haskell.
   Pedro will give an introductory talk about generic programming, and
   Sean will talk about xformat, a library for extensible and type-safe
   formatting with scanf- and printf-like functions. There is also still
   space for short 5-minute lighting talk about something related to
   Haskell or functional programming; contact Tom if you're interested.

   moe html combinator. Jinjing Wang [18]announced the release of [19]moe,
   a DSL for generating HTML.

   jail-0.0.1 - Jailed IO monad. Sebastiaan Visser [20]announced the first
   release of the [21]jail package, a jailed IO monad that can restrict
   filesystem access for your code.

   scion 0.1. Thomas Schilling [22]announced the first release of
   [23]Scion, a Haskell library that aims to implement those parts of a
   Haskell IDE which are independent of a particular front-end. Scion is
   based on the GHC API and Cabal. It provides both a Haskell API and a
   server for non-Haskell clients such as Emacs and Vim.

Blog noise

   [24]Haskell news from the [25]blogosphere. Blog posts from people new
   to the Haskell community are marked with >>>, be sure to welcome them!
 * Don Stewart (dons): [26]DEFUN 2009: Multicore Programming in
   Haskell Now!.
 * Bryan O'Sullivan: [27]Slides from my CUFP 2009 keynote talk.
 * LHC Team: [28]Yet another unfair benchmark..
 * Alex McLean: [29]Hackpact documentation.
 * >>> 

Re: [Haskell-cafe] Problem on existential type.

2009-09-05 Thread Ryan Ingram
On Thu, Sep 3, 2009 at 11:05 PM, Magicloud
Magiclouds wrote:
> data GridWidget = forall widget. (WidgetClass widget) => GridWidget widget
>
> liftGW :: (GridWidget widget) -> (widget -> t) -> t
> liftGW (GridWidget label) f = f label
> liftGW (GridWidget textView) f = f textView

The type signature on liftGW is wrong.  Also, as mentioned elsewhere,
the two matches overlap; the second case never gets called.

The correct type signature for "liftGW" is:

liftGW :: GridWidget -> (forall widget. WidgetClass widget => widget -> t) -> t

Note that the "f" passed in has to accept *any* widget type, so it's
possible that existential types aren't what you want.

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


Re: [Haskell-cafe] [Long] 'Fun' with types

2009-09-05 Thread Maciej Piechotka
On Fri, 2009-09-04 at 07:13 +0100, Colin Adams wrote:
> 2009/9/4 David Menendez :
> > On Thu, Sep 3, 2009 at 6:34 PM, Maciej Piechotka 
> > wrote:
> 
> >>(df <<< dg,
> >
> > Should that be "df *** dg"?
> 

Yes

> Is swearing allowed on this mailing list?
> :-)

Well - errare humanum est...

Regards


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] Trying to reduce memory costs of String duplicates

2009-09-05 Thread Luke Palmer
2009/9/5 Günther Schmidt :
> Hi all,
>
> I'm reading in a data of 216k records into a map of Key, Values Pairs, the
> values being strings.
>
> As it happens out of 216k String values there really are only about 6.6k
> distinct string values, so I could save a lot of RAM if I was able to
> "insert" only actually *new* string values into the map and use references
> to (string) values that already are in memory instead.
>
> Is there a container that would, if I wanted to insert an element, return a
> pair of either the previously inserted, equal value and the container
> unchanged, or the new, previously unknown value and the new container
> amended by that element?

I believe a memoization of the identity function will do what you want:

import qualified Data.MemoCombinators as Memo

share = Memo.list Memo.char id

Then pass any string through share to make/get a cached version.

You might want to limit the scope of share -- eg. put it in a where
clause for the function where you're using it -- so that it doesn't
eat memory for the lifetime of your program, only for when you need
it.

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


Re: [Haskell-cafe] memoization

2009-09-05 Thread Reid Barton
On Sat, Sep 05, 2009 at 02:52:50AM -0700, staafmeister wrote:
> How would experienced haskellers solve this problem?

You could just memoize using an array, like in C.

import Data.Array

occurrences :: Num a => String -> String -> a
occurrences key buf = grid ! (0, 0)  -- grid ! (i, j) = occurrences (drop i 
key) (drop j buf)
  where grid = listArray ((0, 0), (nk, nb)) [
  if i == nk then 1
  else if j == nb then 0
   else (if key !! i == buf !! j then grid ! (i+1, j+1) else 0) + 
grid ! (i, j+1)
  | i <- [0..nk], j <- [0..nb]
  ]
nk = length key
nb = length buf

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


Re: [Haskell-cafe] memoization

2009-09-05 Thread Daniel Fischer
Am Samstag 05 September 2009 11:52:50 schrieb staafmeister:
> Hi,
>
> I participating in de google code jam this year and I want to try to use
> haskell. The following
> simple  http://code.google.com/codejam/contest/dashboard?c=90101#s=p2
> problem
> would have the beautiful haskell solution.
>
> import Data.MemoTrie
> import Data.Char
> import Data.Word
> import Text.Printf
>
> newtype ModP = ModP Integer deriving Eq
>
> p=1
>
> instance Show ModP where
>   show (ModP x) = printf "%04d" x
>
> instance Num ModP where
>   ModP x + ModP y = ModP ((x + y) `mod` p)
>   fromInteger x = ModP (x `mod` p)
>   ModP x * ModP y = ModP ((x * y) `mod` p)
>   abs = undefined
>   signum = undefined
>
> solve _ [] = 1::ModP
> solve [] _ = 0::ModP
> solve (hs:ts) t@(ht:tt) | hs==ht = solve ts tt + solve ts t
>
> | otherwise = solve ts t
>
> go (run, line) = "Case #"++show run++": "++show (solve line "welcome to
> code jam")
>
> main = interact $ unlines . map go . zip [1..] . tail . lines
>
>
> Which is unfortunately exponential.
>
> Now in earlier thread I argued for a compiler directive in the lines of {-#
> Memoize function -#},
> but this is not possible (it seems to be trivial to implement though).

Not really. Though a heck of a lot easier than automatic memoisation.

> Now I used memotrie which
> runs hopelessly out of memory. I looked at some other haskell solutions,
> which were all ugly and
> more clumsy compared to simple and concise C code. So it seems to me that
> haskell is very nice
> and beautiful until your are solving real algorithmic problems when you
> want to go back to some
> imperative language.
>
> How would experienced haskellers solve this problem?
>
> Thanks

completely unoptimised:

--
module Main (main) where

import Text.Printf
import Data.List

out :: Integer -> String
out n = printf "%04d" (n `mod` 1)

update :: [(String,Integer)] -> Char -> [(String,Integer)]
update ((p@((h:_),n)):tl) c
= case update tl c of
((x,m):more)
| c == h-> p:(x,m+n):more
other -> p:other
update xs _ = xs

solve pattern = snd . last . foldl' update (zip (tails pattern) (1:repeat 0))

solveLine :: String -> (Integer,String) -> String
solveLine pattern (i,str) = "Case# " ++ show i ++ ": " ++ out (solve pattern 
str)

main :: IO ()
main = interact $ unlines . map (solveLine "welcome to code jam")
. zip [1 .. ] . tail . lines
--

./codeJam +RTS -sstderr -RTS < C-large-practice.in

Case# 98: 4048  
   
Case# 99: 8125  
   
Case# 100: 0807 
   
  15,022,840 bytes allocated in the heap
   
 789,028 bytes copied during GC 
   
 130,212 bytes maximum residency (1 sample(s))  
   
  31,972 bytes maximum slop 
   
   1 MB total memory in use (0 MB lost due to fragmentation)
   

  Generation 0:28 collections, 0 parallel,  0.00s,  0.00s elapsed
  Generation 1: 1 collections, 0 parallel,  0.00s,  0.00s elapsed

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.04s  (  0.03s elapsed)
  GCtime0.00s  (  0.01s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time0.04s  (  0.04s elapsed)

  %GC time   0.0%  (13.8% elapsed)

  Alloc rate417,277,929 bytes per MUT second

  Productivity 100.0% of total user, 98.6% of total elapsed


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


Re: [Haskell-cafe] Trying to reduce memory costs of String duplicates

2009-09-05 Thread Eugene Kirpichov
2009/9/5 Eugene Kirpichov :
> Should be easy to implement one. Something like this:
>
> class (Monad m) => MonadIntern e m | e -> m where
>  intern :: e -> m e
>
> instance (Ord e) => MonadIntern e (State (M.Map e e)) where
>  intern = modify . insertWith (\old new -> old))

I mean, intern e = (modify . insertWith const $ e) >> (fromJust .
(`lookup`e)) `fmap` get.
However, that probably also won't compile, but I think you get the idea.

>
> 2009/9/5 Günther Schmidt :
>> Hi all,
>>
>> I'm reading in a data of 216k records into a map of Key, Values Pairs, the
>> values being strings.
>>
>> As it happens out of 216k String values there really are only about 6.6k
>> distinct string values, so I could save a lot of RAM if I was able to
>> "insert" only actually *new* string values into the map and use references
>> to (string) values that already are in memory instead.
>>
>> Is there a container that would, if I wanted to insert an element, return a
>> pair of either the previously inserted, equal value and the container
>> unchanged, or the new, previously unknown value and the new container
>> amended by that element?
>>
>> Günther
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
>
> --
> Eugene Kirpichov
> Web IR developer, market.yandex.ru
>



-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trying to reduce memory costs of String duplicates

2009-09-05 Thread Eugene Kirpichov
Should be easy to implement one. Something like this:

class (Monad m) => MonadIntern e m | e -> m where
  intern :: e -> m e

instance (Ord e) => MonadIntern e (State (M.Map e e)) where
  intern = modify . insertWith (\old new -> old))

2009/9/5 Günther Schmidt :
> Hi all,
>
> I'm reading in a data of 216k records into a map of Key, Values Pairs, the
> values being strings.
>
> As it happens out of 216k String values there really are only about 6.6k
> distinct string values, so I could save a lot of RAM if I was able to
> "insert" only actually *new* string values into the map and use references
> to (string) values that already are in memory instead.
>
> Is there a container that would, if I wanted to insert an element, return a
> pair of either the previously inserted, equal value and the container
> unchanged, or the new, previously unknown value and the new container
> amended by that element?
>
> Günther
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Don't “accidentallyparallelize”

2009-09-05 Thread Gracjan Polak

Thanks for great response!

Brent Yorgey  seas.upenn.edu> writes:
> 
> x `pseq` y guarantees to evaluate x before y.  There is no such
> guarantee with x `seq` y; the only guarantee with `seq` is that x
> `seq` y will be _|_ if x is.
> 


I found an old thread here
http://www.mail-archive.com/glasgow-haskell-us...@haskell.org/msg11022.html

where Simon states

[quote]
Indeed, if GHC was in the habit of causing the second argument of seq to be
evaluated before the first, then a lot of people would probably be surprised.
eg. imagine what happens to foldl':

  foldl' f a [] = a
  foldl' f a (x:xs) = let a' = f a x in a' `seq` foldl' f a' xs

It wouldn't do what you want at all.
[/quote]

So... seems foldl' relies on `seq` having unstated evaluation order in GHC. 
So, what guarantees does foldl' have in turn? Semantics only or operational?
Shouldn't it be written using `pseq`?

Seems I have always used (this `seq` that) when I meant (this `before` that).
Is it time to revisit my code and use `pseq` more? 
What does Haskell' say about this?

-- 
Gracjan




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


Re: [Haskell-cafe] Don't “accidentallyparalle lize”

2009-09-05 Thread Sjoerd Visscher
This could be a way to parallelize code (which would prevent such  
mistakes):


newtype Par a = Par { doPar :: a }

instance Functor Par where
  fmap = liftA

instance Applicative Par where
  pure = Par
  Par f <*> Par x = Par $ f `par` x `pseq` f x

then instead of:

fun `par` arg1 `par` arg2 `pseq` fun arg1 arg2

you can write:

doPar $ fun <$> pure arg1 <*> pure arg2

Sjoerd

On Sep 5, 2009, at 2:39 PM, Brent Yorgey wrote:


On Sat, Sep 05, 2009 at 11:18:24AM +, Gracjan Polak wrote:


Hi all,

In "DEFUN 2009: Multicore Programming in Haskell Now!"
(http://donsbot.wordpress.com/2009/09/05/defun-2009-multicore-programming-in-haskell-now/ 
),

slide 30 I see:

Don't “accidentally parallelize”:
– f `par` f + e


This creates a spark (potential speculative execution) to evaluate
'f', but whether this actually gets instantiated in another thread
depends on the order in which the main thread evaluates (f + e): if we
get lucky and it decides to work on evaluating 'e' first, then another
thread may get a chance to evaluate 'f' in parallel.  But if the main
thread decides to work on 'f' first then the spark to evaluate 'f'
will never get run and we end up with a sequential computation.



and that the correct way of achieving parallelism is:
– f `par` e `pseq` f + e


This means: create a spark to evaluate 'f', then evaluate 'e', and
then finally evaluate f + e.  This ensures that the main thread will
work on 'e' first so that the spark for 'f' has a chance to run in
parallel.



As a bonus question: what is the difference between `seq` and `pseq`?


x `pseq` y guarantees to evaluate x before y.  There is no such
guarantee with x `seq` y; the only guarantee with `seq` is that x
`seq` y will be _|_ if x is.

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


--
Sjoerd Visscher
sjo...@w3future.com



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


[Haskell-cafe] Trying to reduce memory costs of String duplicates

2009-09-05 Thread Günther Schmidt

Hi all,

I'm reading in a data of 216k records into a map of Key, Values Pairs, the  
values being strings.


As it happens out of 216k String values there really are only about 6.6k  
distinct string values, so I could save a lot of RAM if I was able to  
"insert" only actually *new* string values into the map and use references  
to (string) values that already are in memory instead.


Is there a container that would, if I wanted to insert an element, return  
a pair of either the previously inserted, equal value and the container  
unchanged, or the new, previously unknown value and the new container  
amended by that element?


Günther

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


Re: [Haskell-cafe] Don't “ accidentallyparallelize”

2009-09-05 Thread Brent Yorgey
On Sat, Sep 05, 2009 at 11:18:24AM +, Gracjan Polak wrote:
> 
> Hi all,
> 
> In "DEFUN 2009: Multicore Programming in Haskell Now!"
> (http://donsbot.wordpress.com/2009/09/05/defun-2009-multicore-programming-in-haskell-now/),
> slide 30 I see:
> 
> Don't “accidentally parallelize”:
> – f `par` f + e

This creates a spark (potential speculative execution) to evaluate
'f', but whether this actually gets instantiated in another thread
depends on the order in which the main thread evaluates (f + e): if we
get lucky and it decides to work on evaluating 'e' first, then another
thread may get a chance to evaluate 'f' in parallel.  But if the main
thread decides to work on 'f' first then the spark to evaluate 'f'
will never get run and we end up with a sequential computation.

> 
> and that the correct way of achieving parallelism is:
> – f `par` e `pseq` f + e

This means: create a spark to evaluate 'f', then evaluate 'e', and
then finally evaluate f + e.  This ensures that the main thread will
work on 'e' first so that the spark for 'f' has a chance to run in
parallel.

> 
> As a bonus question: what is the difference between `seq` and `pseq`?

x `pseq` y guarantees to evaluate x before y.  There is no such
guarantee with x `seq` y; the only guarantee with `seq` is that x
`seq` y will be _|_ if x is.

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


[Haskell-cafe] Re: Problem on existential type.

2009-09-05 Thread John Lato
Also, the two definitions for liftGW are exactly equivalent.  You have:

liftGW (GridWidget label) f = f label
liftGW (GridWidget textView) f = f textView

The only difference between the two is name to which the data
parameter to GridWidget is bound, which doesn't change the meaning at
all.  You should properly have

liftGW (GridWidget widget) f = f widget

There's no way to determine if that widget is a label or textView,
which is the whole point of existential types.

Cheers,
John

> From: Miguel Mitrofanov 
> Subject: Re: [Haskell-cafe] Problem on existential type.
> To: Magicloud Magiclouds 
>
> Your data type GridWidget doesn't have a parameter, yet you use it
> like it has one.
>
>> data GridWidget = forall widget. (WidgetClass widget) => GridWidget
>> widget
>                 ^
>                 |
> NB:-+
>
>> liftGW :: (GridWidget widget) -> (widget -> t) -> t
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Don't “accidentallyparallelize”

2009-09-05 Thread Gracjan Polak

Hi all,

In "DEFUN 2009: Multicore Programming in Haskell Now!"
(http://donsbot.wordpress.com/2009/09/05/defun-2009-multicore-programming-in-haskell-now/),
slide 30 I see:

Don't “accidentally parallelize”:
– f `par` f + e

and that the correct way of achieving parallelism is:
– f `par` e `pseq` f + e

Actually I don't understand the difference between these two forms. Could any
brave soul explain it to me, please?

As a bonus question: what is the difference between `seq` and `pseq`?

-- 
Gracjan


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


[Haskell-cafe] memoization

2009-09-05 Thread staafmeister


Hi,

I participating in de google code jam this year and I want to try to use
haskell. The following 
simple  http://code.google.com/codejam/contest/dashboard?c=90101#s=p2
problem 
would have the beautiful haskell solution. 

import Data.MemoTrie
import Data.Char
import Data.Word
import Text.Printf

newtype ModP = ModP Integer deriving Eq

p=1

instance Show ModP where
  show (ModP x) = printf "%04d" x

instance Num ModP where
  ModP x + ModP y = ModP ((x + y) `mod` p)
  fromInteger x = ModP (x `mod` p)
  ModP x * ModP y = ModP ((x * y) `mod` p)
  abs = undefined
  signum = undefined

solve _ [] = 1::ModP
solve [] _ = 0::ModP
solve (hs:ts) t@(ht:tt) | hs==ht = solve ts tt + solve ts t
| otherwise = solve ts t

go (run, line) = "Case #"++show run++": "++show (solve line "welcome to code
jam")

main = interact $ unlines . map go . zip [1..] . tail . lines


Which is unfortunately exponential.

Now in earlier thread I argued for a compiler directive in the lines of {-#
Memoize function -#},
but this is not possible (it seems to be trivial to implement though). Now I
used memotrie which
runs hopelessly out of memory. I looked at some other haskell solutions,
which were all ugly and
more clumsy compared to simple and concise C code. So it seems to me that
haskell is very nice
and beautiful until your are solving real algorithmic problems when you want
to go back to some
imperative language.

How would experienced haskellers solve this problem?

Thanks
-- 
View this message in context: 
http://www.nabble.com/memoization-tp25306687p25306687.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] haskelldb + sqlite problem.

2009-09-05 Thread Colin Paul Adams
> "Colin" == Colin Paul Adams  writes:

> "Magicloud" == Magicloud Magiclouds  
> writes:
Magicloud> Hi, I am using haskelldb and
Magicloud> haskelldb-hdbc-sqlite3. Well, I finally got the source
Magicloud> compiled and ran, I got this error: App: user error
Magicloud> (SQL error: SqlError {seState = "", seNativeError = 21,
Magicloud> seErrorMsg = "prepare 74: SELECT subject,\n
Magicloud> timestamp\nFROM notes as T1\nORDER BY timestamp DESC:
Magicloud> library routine called out of sequence"}) Any clue what
Magicloud> I should check?

Colin> Did you get this working? If so, what was the problem and
Colin> how did you go about resolving it.

Colin> I have the identical problem. I had the database code
Colin> working fine, but then I added a state monad into the monad
Colin> stack for the program, and now I get this problem.  I see
Colin> that John Goerzen suggested it might be a result of reading
Colin> the data lazily.  So I tried changing my import statements
Colin> from import Control.Monad.State to import
Colin> Control.Monad.State.Strict

Colin> in case the StateT was indirectly causing the problem, but
Colin> that doesn't make any difference.

As I suspected, the problem is something to do with my putting the
Database.HaskellDB.Database.Database into the state monad, and getting
it from there, rather than passing it around explicitly. So I guess I
have too much laziness in:

ApplicationState db _ <- lift get

How do I force db in this situation?
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe