Re: [Haskell-cafe] Why does this program eat RAM?

2006-09-05 Thread Bertram Felgenhauer
Donald Bruce Stewart wrote:
> A quick hack up to use Data.ByteString uses a lot less ram, though
> profiling still shows 95% of time spent in the building the Map.

Nice!

>   k n w = Map.insertWith f w 1 n
>   f _ x = let y = x + 1 in y `seq` y

y `seq` y is semantically equivalent to y though. The strictness
would have to be built into insertWith to make this work.

regards,

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


[Haskell-cafe] Re: Quantification in free theorems

2006-09-05 Thread Janis Voigtlaender

Hello all,

[EMAIL PROTECTED] wrote:

For this, you produce the following theorem:

  g x = h (f x)
  =>
  $map f . filter g = filter h . $map f



It now produces:

filter (f . g) . $map f = $map f . filter g


... which is also wrong. Consider the following:

  f = const False
  g = id

Then, with the standard filter function:

filter (f . g) (map f [True])
  = []
 /= [False]
  = map f (filter g [True])

Maybe it is just an accidental swapping of the arguments to (.) in your
implementation. For if one would swap all such arguments above, one
would get:

  $map f . filter (g . f) = filter g . $map f

which would be correct.

Regarding Lennart's suggestion: I am pretty sure that it would be easy
to adapt Sascha's system to omit top level quantifiers. All that should
be needed would be an extra pass prior to prettyprinting, to strip off
any outermost quantifiers from the data type representing free theorems.

That wouldn't really be a mix of the two systems, however, because they
follow different strategies for output. This can be seen, for example,
for the following type:

  zip :: [a] -> [b] -> [(a, b)]

Here, Andrew's system now produces:

  (forall x y. ( f ($fst x) = $fst y
 &&
 g ($snd x) = $snd y
   )
  =>
   h x = y)
  =>
  $map h (zip xs ys) = zip ($map f xs) ($map g ys)

Whereas Sascha's system produces (minus top level quantifiers):

  (zip x1 x2, zip (map h1 x1) (map h2 x2)) in
  lift_{[]}(lift_{(2)}(h1, h2))

  lift_{[]}(lift_{(2)}(h1, h2))
  = {([], [])}
  u {(x : xs, y : ys) | ((x, y) in lift_{(2)}(h1, h2))
/\ ((xs, ys) in lift_{[]}(lift_{(2)}(h1, h2)))}

  lift_{(2)}(h1, h2)
  = {((x1, x2), (y1, y2)) | (h1 x1 = y1) /\ (h2 x2 = y2)}

The latter approach has advantages when it comes to producing free
theorems that are faithful to the presence of _|_ and general recursion
in Haskell, which is not supported by Andrew's system, as far as I can
see. Also, some of Andrew's tricks for making the output look more
pointfree would not work when producing the more general "relational"
free theorem (prior to the specialization to functions), which is also
supported in Sascha's system.

Ciao, Janis.

--
Dr. Janis Voigtlaender
http://wwwtcs.inf.tu-dresden.de/~voigt/
mailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: practice problems?

2006-09-05 Thread Neil Mitchell

Hi


This, and especially publishing solutions on the Wiki, could be against
the spirit of SPOJ.  Here is a relevant piece from the FAQ:


I was going to put coordination information on the wiki - which
problems don't have a Haskell solution etc - not actual solutions.

If people have a particular problem getting a challenge to run inside
the time limit, going on to #haskell and asking for advice is probably
a good solution to learning things.

Thanks

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


Re[2]: [Haskell-cafe] Why does this program eat RAM?

2006-09-05 Thread Bulat Ziganshin
Hello Bertram,

Tuesday, September 5, 2006, 12:24:57 PM, you wrote:

>> A quick hack up to use Data.ByteString uses a lot less ram, though
>> profiling still shows 95% of time spent in the building the Map.

Data.HashTable may be a faster alternative for Map (if ordering isn't
required)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Why does this program eat RAM?

2006-09-05 Thread Udo Stenzel
John Goerzen wrote:
> I have the below program, and I'm trying to run it on an input of about
> 90MB.  It eats RAM like crazy, and I can't figure out why.
> 
> wordfreq inp = Map.toList $ foldl' updatemap (Map.empty::Map.Map String Int) 
> inp
> where updatemap nm word = Map.insertWith updatefunc word 1 nm
>   updatefunc _ x = x + 1

The culprit is insertWith, it inserts unevaluated thunks into your map
where you want a simple value.  To avoid a space leak, you want a strict
update function (yours is strict enough) and insertWith must be strict
in the newly inserted value (the result of applying updatefunc).  Since
you cannot influence the strictness of insertWith, no matter how many
seqs you sprinkle through your code, you need insertWith', which is
missing.  You can simulate it, however:

insertWith' f k v m = case Map.lookup k m of
Nothing -> Map.insert k v m
Just w  -> (Map.insert k $! f w v) m

IMHO all accumulating functions, especially foldl, State.update,
Map.insertWith, accumArray, absolutely need a strict version, because
the strictness cannot be recovered by the library's user.  If the
clutter of too many primed names is unbearable, leave out the _lazy_
version.  It's useless IME and lazyness can be recovered if the need
arises.


Udo.
-- 
Wo die Macht geistlos ist, ist der Geist machtlos.
-- aus einem Gipfelbuch


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


Re: [Haskell-cafe] Why does this program eat RAM?

2006-09-05 Thread Chris Kuklewicz

Bulat Ziganshin wrote:

Hello Bertram,

Tuesday, September 5, 2006, 12:24:57 PM, you wrote:


A quick hack up to use Data.ByteString uses a lot less ram, though
profiling still shows 95% of time spent in the building the Map.


Data.HashTable may be a faster alternative for Map (if ordering isn't
required)




I found Data.HashTable a bit slow (ghc 6.4).  Perhaps HsJudy (see 
http://cmarcelo.blogspot.com/ and http://judy.sourceforge.net/ and 
http://www.mail-archive.com/haskell@haskell.org/msg18766.html )

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


[Haskell-cafe] User data type with operator contructors only

2006-09-05 Thread Dušan Kolář

Hello all,

 my question probably comes from not reading manual properly. But, why 
is it not possible to have something like:


infixr 5 :>

data Stack a
 = a :> (Stack a)
 | :||

And if yes, how can I do that? I know that lists are a hack in Haskell, 
but anyway. Having:


infixr 5 :>

data Stack a
 = a :> (Stack a)
 | Bottom

is not what I would like to have. :-(

Thanks for any reference to/or explanation,

 Dusan



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


Re: [Haskell-cafe] User data type with operator contructors only

2006-09-05 Thread Donald Bruce Stewart
kolar:
> Hello all,
> 
>  my question probably comes from not reading manual properly. But, why 
> is it not possible to have something like:
> 
> infixr 5 :>
> 
> data Stack a
>  = a :> (Stack a)
>  | :||
> 
> And if yes, how can I do that? I know that lists are a hack in Haskell, 

infixr 5 :>

data Stack a = a :> (Stack a) | (:||)

test = 7 :> 8 :> 2 :> (:||)

Not ideal, though, I suppose.

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


Re: Re[2]: [Haskell-cafe] Why does this program eat RAM?

2006-09-05 Thread Udo Stenzel
Bulat Ziganshin wrote:
> Data.HashTable may be a faster alternative for Map (if ordering isn't
> required)

Or it may not.  Finding a good hash function for the words John is
counting, is a challenge itself.  Finding a good one that doesn't look
at each character at least once, might be outright impossible.  That
means, a hash table cannot do significantly less work than the
appropriate data structure, which is a trie, aka Data.StringMap.


Udo.
-- 
Q:  Why do mountain climbers rope themselves together?
A:  To prevent the sensible ones from going home.


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


Re: [Haskell-cafe] User data type with operator contructors only

2006-09-05 Thread Dušan Kolář

Donald Bruce Stewart wrote:

kolar:
  

Hello all,

 my question probably comes from not reading manual properly. But, why 
is it not possible to have something like:


infixr 5 :>

data Stack a
 = a :> (Stack a)
 | :||

And if yes, how can I do that? I know that lists are a hack in Haskell, 



infixr 5 :>

data Stack a = a :> (Stack a) | (:||)

test = 7 :> 8 :> 2 :> (:||)

Not ideal, though, I suppose.

-- Don
  
Hmm, I see, ghci works, but hugs not. That was my problem. Sorry for 
asking. I've thought this would work in both. :-(


Dusan


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


[Haskell-cafe] [Parsec] No identEnd in ParsecToken?

2006-09-05 Thread Stephane Bortzmeyer
I'm trying to use Parsec for a language which have identifiers where
the '-' character is allowed only inside identifiers, not at the start
or the end.

ParsecToken has identStart to tell that the '-' is not allowed at the
start but I find no equivalent identEnd?

I tried also to express the same rule with ordinary combinators,
without ParsecToken but this fails:

identifier = do
start <- letter
rest <- many (alphaNum <|> char '-') 
end <- letter   
return ([start] ++ rest ++ [end])
   "characters authorized for identifiers"

because the parser created by "many" is greedy: it consumes
everything, including the final letter.

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


Re: [Haskell-cafe] [Parsec] No identEnd in ParsecToken?

2006-09-05 Thread Malcolm Wallace
Stephane Bortzmeyer <[EMAIL PROTECTED]> wrote:

> identifier = do
> start <- letter
> rest <- many (alphaNum <|> char '-') 
> end <- letter   
> return ([start] ++ rest ++ [end])
>"characters authorized for identifiers"
> 
> because the parser created by "many" is greedy: it consumes
> everything, including the final letter.

How about eating chunks of alphaNum, then chunks of '-', in alternation.
You just need to flatten the returned list of words to a single word.

identifier = do
  init <- many alphaNum
  rest <- many ( do dash <- many1 (char '-')
alfa <- many1 alphaNum
return (dash++alfa) )
  return (concat (init:rest))

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


Re: [Haskell-cafe] [Parsec] No identEnd in ParsecToken?

2006-09-05 Thread Chris Kuklewicz

Stephane Bortzmeyer wrote:

I'm trying to use Parsec for a language which have identifiers where
the '-' character is allowed only inside identifiers, not at the start
or the end.

ParsecToken has identStart to tell that the '-' is not allowed at the
start but I find no equivalent identEnd?


I have not used ParsecToken



I tried also to express the same rule with ordinary combinators,
without ParsecToken but this fails:

identifier = do
start <- letter
rest <- many (alphaNum <|> char '-') 
end <- letter   
return ([start] ++ rest ++ [end])

   "characters authorized for identifiers"

because the parser created by "many" is greedy: it consumes
everything, including the final letter.

Any idea?


The hard thing about using Parsec is to know how to combine <|> with 'try'.

Fixing this may be as simple as

> identifier = try $ do
> start <- letter
> rest <- many (alphaNum <|> char '-')
> end <- letter
> return ([start] ++ rest ++ [end])
>"characters authorized for identifiers"

Alternatively, if the first character being a letter commits you to an 
identifier or a syntax error, then you could move the try after the first letter 
has been read and committed to:



identifier = do
start <- letter
try $ do
  rest <- many (alphaNum <|> char '-') 
  end <- letter

  return (start:(rest ++ [end]))
   "characters authorized for identifiers"


(Both untested)

And can the last letter be an alphaNum instead of only a letter?

You can also make the test more explicit:

> import Data.Char; import Control.Monad;
>

identifier = try $ do
  start <- letter
  rest <- many (satisfy (\c -> alphaNum c || (c=='-')))
  when (not (null rest) && '-' == last rest) (unexpected "Identifier cannot end in 
-")
  return (start:rest)

or

identifier = do
  start <- letter  "Identifiers must start with a letter"
  try $ do
rest <- many (satisfy (\c -> alphaNum c || (c=='-')))  "valid identifier 
character"
when (not (null rest) && '-' == last rest) (unexpected "identifier cannot end in 
-")
return (start:rest)

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


[Haskell-cafe] Re: Why does this program eat RAM?

2006-09-05 Thread John Goerzen
On 2006-09-05, Udo Stenzel <[EMAIL PROTECTED]> wrote:
> The culprit is insertWith, it inserts unevaluated thunks into your map

This turned out to be the answer -- thanks!

I posted a new version of the code here:

http://changelog.complete.org/posts/536-Another-Haskell-Solution-to-Lars-Problem.html

This particular test set was a few hundred copies of the GPL.  So the
Map was fairly small, since each word occured many, many times -- but
there weren't a whole lot of words.  So the problem was not the
inefficiency of Data.Map, nor the inefficiency of Strings (though that
inefficiency does explain why the Python solution is faster, I'm sure).

-- John


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


[Haskell-cafe] Re: Re[2]: Why does this program eat RAM?

2006-09-05 Thread John Goerzen
On 2006-09-05, Bulat Ziganshin <[EMAIL PROTECTED]> wrote:
> Hello Bertram,
>
> Tuesday, September 5, 2006, 12:24:57 PM, you wrote:
>
>>> A quick hack up to use Data.ByteString uses a lot less ram, though
>>> profiling still shows 95% of time spent in the building the Map.
>
> Data.HashTable may be a faster alternative for Map (if ordering isn't
> required)

Indeed ordering wasn't required, but as HashTable lives in the IO monad,
it's not, well, very "Haskellish".

-- John

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


Re: [Haskell-cafe] [Parsec] No identEnd in ParsecToken?

2006-09-05 Thread Udo Stenzel
Stephane Bortzmeyer wrote:
> I'm trying to use Parsec for a language which have identifiers where
> the '-' character is allowed only inside identifiers, not at the start
> or the end.
> 
> identifier = do
> start <- letter
> rest <- many (alphaNum <|> char '-') 
> end <- letter   
> return ([start] ++ rest ++ [end])
>"characters authorized for identifiers"

identifier = do
start <- letter
rest <- many (alphaNum <|> try inner_minus)
return $ start : rest
where
inner_minus = do 
char '-' 
lookAhead alphaNum
return '-'


> because the parser created by "many" is greedy: it consumes
> everything, including the final letter.

Yes, it does.  You could implement you own non-greedy many combinator,
but you get the associated inefficiency.  Or you could use ReadP, which
doesn't have this problem (but replaces it with other surprises).  


Udo.
-- 
Eagles may soar but weasels don't get sucked into jet engines.
-- Steven Wright 


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


[Haskell-cafe] Re: [Parsec] No identEnd in ParsecToken?

2006-09-05 Thread Stephane Bortzmeyer
On Tue, Sep 05, 2006 at 03:46:16PM +0100,
 Chris Kuklewicz <[EMAIL PROTECTED]> wrote 
 a message of 69 lines which said:

> Fixing this may be as simple as
> 
> > identifier = try $ do
> > start <- letter
> > rest <- many (alphaNum <|> char '-')
> > end <- letter
> > return ([start] ++ rest ++ [end])
> >"characters authorized for identifiers"

It does not work for me (and neither does the second). The "try"
argument always fails, probably because the term "many" on the "rest"
line is greedy and swallows the ending letter.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Parsec] No identEnd in ParsecToken?

2006-09-05 Thread Stephane Bortzmeyer
On Tue, Sep 05, 2006 at 04:17:41PM +0200,
 Stephane Bortzmeyer <[EMAIL PROTECTED]> wrote 
 a message of 25 lines which said:

> I'm trying to use Parsec for a language which have identifiers where
> the '-' character is allowed only inside identifiers, not at the
> start or the end.

[My grammar was underspecified, I also want to disallow two
consecutive dashes.]

Many thanks to Malcolm Wallace, Chris Kuklewicz and Udo Stenzel for
their help and ideas. It seems there is no solution for ParsecToken
(so I have to drop it). Among the two solutions which work for me
(Malcolm Wallace's and Udo Stenzel's), I choosed the one by Udo
because it is the one I understand the best.

Here is my final version (rewritten in my style, errors are mine and
not Udo's), thanks again:

import Text.ParserCombinators.Parsec hiding (spaces)

spaces = many1 (char ' ')

inner_minus = do
char '-'
lookAhead alphaNum
return '-'

identifier = do
start <- letter
rest <- many (alphaNum <|> try inner_minus)
return (start:rest)
"identifier"

identifiers = do
   result <- identifier `sepBy` spaces
   eof
   return result

main = do
   -- Legal
   parseTest identifiers "foo bar"
   parseTest identifiers "foo-bar baz go-to"
   parseTest identifiers "a b3 c56 e56-y7 gag-3456"
   -- Illegal
   parseTest identifiers "1llegal"
   parseTest identifiers "illegal- more"
   parseTest identifiers "ill--egal more"
   parseTest identifiers "illegal -more"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does this program eat RAM?

2006-09-05 Thread Ross Paterson
On Tue, Sep 05, 2006 at 12:55:48PM +0200, Udo Stenzel wrote:
> IMHO all accumulating functions, especially foldl, State.update,
> Map.insertWith, accumArray, absolutely need a strict version, because
> the strictness cannot be recovered by the library's user.

We already have foldl'.  Here's a strict version of fmap:

import Control.Applicative
import Data.Traversable

newtype Strict a = Strict a
getStrict (Strict x) = x

instance Functor Strict where
fmap f (Strict x) = Strict (f x)

-- doesn't quite satisfy the Applicative laws
instance Applicative Strict where
pure x = Strict x
Strict f <*> Strict x = Strict (f $! x)

fmap' :: Traversable f => (a -> b) -> f a -> f b
fmap' f t = getStrict (traverse (Strict . f) t)

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


[Haskell-cafe] Re: Quantification in free theorems

2006-09-05 Thread ajb
G'day all.

Quoting Janis Voigtlaender <[EMAIL PROTECTED]>:

> Maybe it is just an accidental swapping of the arguments to (.) in your
> implementation.

That was it, yes.  Thanks for debugging my code for me. :-)

(For those keeping score, it was actually the incorrect unzipping of
a zipper data structure.  If only I could scrap my boilerplate...)

> Regarding Lennart's suggestion: I am pretty sure that it would be easy
> to adapt Sascha's system to omit top level quantifiers. All that should
> be needed would be an extra pass prior to prettyprinting, to strip off
> any outermost quantifiers from the data type representing free theorems.

In my case, the approach taken was to pass a Bool around the pretty
printer which says whether or not to include quantifiers.  (It's okay
to strip quantifiers off the right-hand side of an implication if it's
okay to strip quantifiers off the implication itself.)

> The latter approach has advantages when it comes to producing free
> theorems that are faithful to the presence of _|_ and general recursion
> in Haskell, which is not supported by Andrew's system, as far as I can
> see.

That's correct.  Once again, different design criteria apply.  IRC has
anti-flooding rules which encourage brevity rather than full-featuredness.

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


[Haskell-cafe] Re: [Parsec] No identEnd in ParsecToken?

2006-09-05 Thread Jón Fairbairn
Stephane Bortzmeyer <[EMAIL PROTECTED]> writes:

> On Tue, Sep 05, 2006 at 04:17:41PM +0200,
>  Stephane Bortzmeyer <[EMAIL PROTECTED]> wrote 
>  a message of 25 lines which said:
> 
> > I'm trying to use Parsec for a language which have identifiers where
> > the '-' character is allowed only inside identifiers, not at the
> > start or the end.

I'm not really familiar with Parsec (I wrote my own limited
backtrack parser years ago, and haven't quite got round to
updating my brain), and while (judging by threads like this
one) it seems to be harder to use than one would hope, this
particular problem doesn't look as hard to me as all that.

> [My grammar was underspecified, I also want to disallow two
> consecutive dashes.]

[...]

> Here is my final version (rewritten in my style, errors are mine and
> not Udo's), thanks again:
> 
> inner_minus = do
> char '-'
> lookAhead alphaNum
> return '-'
>
> identifier = do
> start <- letter
> rest <- many (alphaNum <|> try inner_minus)
> return (start:rest)
> "identifier"


I'd have thought something like the following was the
'obvious' way of doing it:

chThen c r = do a <- c; as <- r; return (a:as)
identifier = do
start <- letter `chThen` many alphaNum;
rest <- many (char '-' `chThen` many1 alphaNum) 
return (start++concat rest)
"identifier"

ie, your identifiers are an initial sequence of non-minuses
beginning with a letter, and then an optional sequence of
non-minuses preceded by a minus. Or have I lost the plot
somewhere?

Aside: 
Is there already name for `chThen`? ie (liftM2 (:)); I had a
feeling we were avoiding liftM & friends for some reason.

-- 
Jón Fairbairn [EMAIL PROTECTED]
http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html  (updated 2006-07-14)

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