Re: [Haskell-cafe] How do you rewrite your code?

2010-03-02 Thread Ryan Ingram
On Tue, Mar 2, 2010 at 11:20 AM, Sean Leather  wrote:
> For all x, f:
>
> x >>= return . f
> -->
> fmap f x
> or
> f <$> x -- requires importing Control.Applicative
>
> I think the right-hand side (RHS) is more concise and simpler. The types
> here do change: the type constructor has a Monad constraint in the left-hand
> side and a Functor constraint in the RHS. Types that are Monad instances are
> generally also Functor instances, so this is often possible. I'm convinced
> the semantics are preserved, though I haven't proven it.

(Hand-wavy part of proof)

I believe that by parametricity, any two functions of the type:

 mapX :: forall a b. (a -> b) -> (X a -> X b)

that satisfy the functor laws:

 mapX f . mapX g = mapX (f . g)
 mapX id = id

must be equal to one another, and therefore equal to fmap.

(formal part of proof):

given any monad M, let mapM f m = m >>= return . f

mapM id m
-- apply mapM
= m >>= return . id
-- apply (.)
= m >>= (\x -> return (id x))
-- apply id
= m >>= (\x -> return x)
-- eta reduce
= m >>= return
-- monad right identity
= m
-- un-apply id
= id m

(mapM f . mapM g) m
-- apply (.)
= mapM f (mapM g m)
-- apply mapM twice
= (m >>= return . g) >>= return . f
-- apply (.) twice
= (m >>= \x -> return (g x)) >>= \y -> return (f y)
-- monad associativity
= m >>= (\x -> return (g x) >>= \y -> return (f y))
-- monad left identity
= m >>= (\x -> (\y -> return (f y)) (g x))
-- beta reduce
= m >>= (\x -> return (f (g x)))
-- unapply (.)
= m >>= (\x -> return ((f . g) x))
-- unapply (.)
= m >>= (\x -> (return . (f . g)) x)
-- eta reduce
= m >>= return (f . g)
-- un-apply mapM
= mapM (f . g) m

So, we have
  mapM id m = id m
  (mapM f . mapM g) m = mapM (f . g) m
and by extensionality
  mapM id = id
  mapM f . mapM g = mapM (f . g)

So, if the handwavy part of the proof at the beginning holds, mapM =
fmap, and your translation is sound.

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


Re: [Haskell-cafe] Prelude.undefined

2010-03-02 Thread Alexander Dunlap
On Tue, Mar 2, 2010 at 9:06 PM, Tom Hawkins  wrote:
> How do I track down an reference to an undefined value?  My program
> must not be using a library correctly because the program makes no
> direct use of 'undefined'.  Running with +RTS -xc yields:
>
> Test: Prelude.undefined
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

While the debugger, etc., are very useful tools, I find that often the
easiest way to track down this sort of bug is to test your code
function-by-function. Make sure each function does what you want it to
when run in isolation; this will quickly lead to tracking down the
caller of "undefined". (If your code is not structured in a way that
allows this sort of testing, you might consider restructuring it to
make it more modular.)

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


Re: [Haskell-cafe] Prelude.undefined

2010-03-02 Thread Ivan Miljenovic
On 3 March 2010 16:11, Tom Hawkins  wrote:
> -Wall only complains about shadow bindings, defined but not used, and
> no type signature.  But no unmatched patterns.

Yes it does: one of the options it brings in is
-fwarn-incomplete-patterns which tells you if you've missed a pattern
match.

http://www.haskell.org/ghc/docs/latest/html/users_guide/options-sanity.html

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Prelude.undefined

2010-03-02 Thread Alex MDC
2010/3/3 Tom Hawkins 

> On Wed, Mar 3, 2010 at 6:07 AM, Ivan Miljenovic
>
> -Wall only complains about shadow bindings, defined but not used, and
> no type signature.  But no unmatched patterns.
>

If you can run your code through the ghc debugger you can get it to break
when an undefined exception is raised.

The options are :set -fbreak-on-exception or -fbreak-on-error. More info in
the documentation at
http://www.haskell.org/ghc/docs/latest/html/users_guide/ghci-debugger.html#ghci-debugger-exceptions

Hope that helps,
Alex MDC
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Prelude.undefined

2010-03-02 Thread Tom Hawkins
On Wed, Mar 3, 2010 at 6:11 AM, Tom Hawkins  wrote:
> On Wed, Mar 3, 2010 at 6:07 AM, Ivan Miljenovic
>  wrote:
>> On 3 March 2010 16:06, Tom Hawkins  wrote:
>>> How do I track down an reference to an undefined value?  My program
>>> must not be using a library correctly because the program makes no
>>> direct use of 'undefined'.  Running with +RTS -xc yields:
>>>
>>> Test: Prelude.undefined
>>
>> Are you matching all patterns?  When compiling with -Wall does it make
>> any complaints?
>
> -Wall only complains about shadow bindings, defined but not used, and
> no type signature.  But no unmatched patterns.

BTW, I'm using:

GHC 6.12.1
bytestring 0.9.1.5
containers 0.3.0.0
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Prelude.undefined

2010-03-02 Thread Tom Hawkins
On Wed, Mar 3, 2010 at 6:07 AM, Ivan Miljenovic
 wrote:
> On 3 March 2010 16:06, Tom Hawkins  wrote:
>> How do I track down an reference to an undefined value?  My program
>> must not be using a library correctly because the program makes no
>> direct use of 'undefined'.  Running with +RTS -xc yields:
>>
>> Test: Prelude.undefined
>
> Are you matching all patterns?  When compiling with -Wall does it make
> any complaints?

-Wall only complains about shadow bindings, defined but not used, and
no type signature.  But no unmatched patterns.



>
> --
> Ivan Lazar Miljenovic
> ivan.miljeno...@gmail.com
> IvanMiljenovic.wordpress.com
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Prelude.undefined

2010-03-02 Thread Ivan Miljenovic
On 3 March 2010 16:06, Tom Hawkins  wrote:
> How do I track down an reference to an undefined value?  My program
> must not be using a library correctly because the program makes no
> direct use of 'undefined'.  Running with +RTS -xc yields:
>
> Test: Prelude.undefined

Are you matching all patterns?  When compiling with -Wall does it make
any complaints?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Prelude.undefined

2010-03-02 Thread Tom Hawkins
How do I track down an reference to an undefined value?  My program
must not be using a library correctly because the program makes no
direct use of 'undefined'.  Running with +RTS -xc yields:

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


[Haskell-cafe] Re: Monad laws

2010-03-02 Thread Maciej Piechotka

> 
> 
> In GHC 6.12.1 both expressions reduce to True, but it doesn't happen
> in GHC 6.10.4. Any ideas why the behaviour is different?
> 

Maybe (I'm guessing) GHC 6.12.1 is smart enough to figure out that f a
is not needed to evaluate True?

In docs it was said that seq states that 'it may be beneficial but
details are up to compiler.

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


[Haskell-cafe] Re: FFI and lists?

2010-03-02 Thread Maciej Piechotka
On Tue, 2010-03-02 at 13:19 -0800, Kimberly Wallmark wrote:
> I'm working with FFI to make a Haskell DLL that's called by C# code.   
> I understand how to share simple types.  I've found reasonable  
> documentation for struct-equivalents.  Is there a clean way to share  
> lists, or should I make a linked-list struct and do it manually?
> 
> In other words, if I have
>adder :: CInt -> CInt -> CInt
>adder x y = (x+y)
> 
> then I can use
>foreign export stdcall adder :: CInt -> CInt -> CInt
> 
> and on the other side it behaves like
>int adder(int a, int b);
> 
> I'd like to know what to do if I have
>squares :: [CInt] -> [CInt]
>squares = map (^2)
> 
> Advice?
> 
> --Kim

You have to marshal it from/into C array so:

foreign export stdcall squares :: Int -> Ptr CInt -> Ptr CInt -> IO ()

squares n f t = pokeArray t =<< map (^2) `fmap` peekArray n f

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] Evolving Faster Haskell Programs (now with LLVM!)

2010-03-02 Thread Don Stewart
I hope to turn it all into a tool.

vanenkj:
> What's the chance you have generational graphs for the rest of your examples
> like you do with the first? I'd be interested to see those.
> 
> On Mon, Mar 1, 2010 at 3:02 AM, Don Stewart  wrote:
> 
> 
> http://donsbot.wordpress.com/2010/03/01/
> evolving-faster-haskell-programs-now-with-llvm/
> 
>   In which I use genetic algorithms to search for optimal LLVM optimizer
> passes to make Haskell programs faster  
> 
> LLVM + GHC is a lot of fun.
> 
> -- Don
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad laws

2010-03-02 Thread Luke Palmer
On Tue, Mar 2, 2010 at 4:37 PM, Yitzchak Gale  wrote:
> For this reason, I consider it a bug in GHC that return :: IO a
> is lazy.

Wait a minute...

   return undefined >>= const (return 42)
= const (return 42) undefined
= return 42

But if return undefined = undefined, then that equals;

  undefined >>= const (return 42)

Which, if IO is allowed to have effects (i.e. if putStrLn "Hello,
World" >>= const (return 42)  is to be different than return 42), must
be undefined.

Or does the former not hold in your version of the laws with strict composition?

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


Re: [Haskell-cafe] Real-time garbage collection for Haskell

2010-03-02 Thread Jason Dusek
2010/02/28 Neil Davies :
> I've never observed ones that size. I have an application that runs in 'rate
> equivalent real-time' (i.e. there may be some jitter in the exact time of
> events but it does not accumulate). It does have some visibility of likely
> time of future events and uses that to perform some speculative garbage
> collection.

  Do you have information on how it behaves without speculative
  GC?

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


Re: [Haskell-cafe] Monad laws

2010-03-02 Thread Yitzchak Gale
David Sabel wrote:
>> when checking the first monad law (left unit) for the IO-monad (and also for
>> the ST monad):
>> I figured out that there is the "distinguishing" context (seq [] True) which
>> falsifies the law...

It's worse than that - Haskell types and functions do not
even form a category under Haskell composition:

Prelude> seq (id . undefined) 42
42
Prelude> seq undefined 42
*** Exception: Prelude.undefined

So (id . undefined) /= undefined, violating one of the category laws.

This is not just a problem with IO - it's a problem with Haskell
itself.

Luke Palmer wrote:
> No, IO just doesn't obey the laws.  However, I believe it does in the
> seq-free variant of Haskell, which is nicer for reasoning.

Ignoring the existence of seq does solve both problems.
This seems like a messy solution, because seq really
*does* exist, and it seems essential. But it's not as bad as it
sounds. Even without the built-in seq, you can define seq
manually for most common types:

class Seq a where seq :: a -> b -> b

instance Seq Int where
  seq 0 x = x
  seq _ x = x

etc. You just wouldn't have seq for function types.

There is another way around this problem in which we
don't need to ignore seq. Let's define strict composition:

f .! g = f `seq` g `seq` f . g

This is "true" function composition in the mathematical
sense - it doesn't have the extra layer of laziness that
Haskell usually imposes. With strict composition,
Haskell types and functions do form a category even
when we include seq.

Unfortunately, IO still does not satisfy the monad laws.
But that could easily be fixed by making return strict,
so that return undefined == undefined. (Note also that
by "monad laws" here I mean the points-free version of the
laws, with strict composition. That is the version of the
laws we get if take the mathematical monad laws
in the category we have just defined and translate them
into Haskell monad notation.)

Category theorists tend not to like this method of resolving
the problem as much. The category we get this way is lacking
some important basic properties, so it is harder for them to
work with. But I think it better reflects the reality of Haskell,
which does in fact include seq.

For this reason, I consider it a bug in GHC that return :: IO a
is lazy.

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


Re: [Haskell-cafe] Monad laws

2010-03-02 Thread Andrés Sicard-Ramírez
On 2 March 2010 15:44, Luke Palmer  wrote:

> On Tue, Mar 2, 2010 at 1:17 PM, David Sabel
>  wrote:
> > Hi,
> > when checking the first monad law (left unit) for the IO-monad (and also
> for
> > the ST monad):
> >
> > return a >>= f ≡ f a
> >
> > I figured out that there is the "distinguishing" context (seq [] True)
> which
> > falsifies the law
> > for a and f defined below
> >
> >
> >> let a = True
> >> let f = \x -> (undefined::IO Bool)
> >> seq (return a >>= f) True
> > True
> >> seq (f a) True
> > *** Exception: Prelude.undefined
> >
> > Is there a side-condition of the law I missed?
>
> No, IO just doesn't obey the laws.  However, I believe it does in the
> seq-free variant of Haskell, which is nicer for reasoning.  In fact,
> this difference is precisely what you have observed: the
> distinguishing characteristic of seq-free Haskell is that (\x ->
> undefined) == undefined, whereas in Haskell + seq, (\x -> undefined)
> is defined.
>
>
In GHC 6.12.1 both expressions reduce to True, but it doesn't happen in GHC
6.10.4. Any ideas why the behaviour is different?

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


Re: [Haskell-cafe] minimal interface

2010-03-02 Thread Ivan Miljenovic
On 3 March 2010 08:25, Sean McLaughlin  wrote:
> For instance, if module A exports f, but A.f is never used in my compiled 
>program,
> I would like to be warned of this fact.

My SourceGraph program (
http://hackage.haskell.org/package/SourceGraph ) does this, but you'll
have to look through the generated report to find it.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Real-time garbage collection for Haskell

2010-03-02 Thread Simon Marlow

On 02/03/10 20:37, Luke Palmer wrote:

On Tue, Mar 2, 2010 at 7:17 AM, Simon Marlow  wrote:

For games,
though, we have a very good point that occurs regularly where we know
that all/most short-lived objects will no longer be referenced - at the
start of a fresh frame.


System.Mem.performGC is your friend, but if you're unlucky it might do a
major GC and then you'll get more pause than you bargained for.


Some fine-grained control might be nice here.  Eg. I could do a major
GC as a player is opening a menu, on a loading screen, when the game
is paused, or some other key points, and it might still be annoying,
but at least it wouldn't interfere with gameplay.  There is of course
the question of what happens if one of these key points doesn't happen
when we need to do an allocation, but... oh well.  Perhaps that could
be mitigated by saying "I would rather you allocate than major GC
right now".  Are any of these options impossible, or be unreasonably
difficult to implement (I don't suspect so)?


Actually that's one thing we can do relatively easily, i.e. defer major 
GC for a while.  Due to the way GHC has a two-layer memory manager, the 
heap is a list of discontiguous blocks, so we can always allocate some 
more memory.


So it would be pretty easy to provide something like

  disableMajorGC, enableMajorGC :: IO ()

Of course leaving it disabled too long could be bad, but that's your 
responsibility.


Oh, I just checked and System.Mem.performGC actually performs a major 
GC, here's its implementation:


foreign import ccall {-safe-} "performMajorGC" performGC :: IO ()

to perform a minor GC (or possibly a major GC if one is due), you want this:

foreign import ccall {-safe-} "performGC" performMinorGC :: IO ()

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


Fwd: [Haskell-cafe] minimal interface

2010-03-02 Thread Sean McLaughlin
Hi Don,

  This doesn't tell me what is extraneous in the exports.  For instance

If I have two modules A and Main

module A (f, g) where

f :: a -> a
f = id

g :: a -> a
g = id


module Main (main) where

import qualified A

main :: IO ()
main = do
  let a = A.f 7
  putStrLn $ show a

I'd like something to tell me that A.g is not used in the program.

Thanks,

Sean


On Tue, Mar 2, 2010 at 4:28 PM, Don Stewart  wrote:

> seanmcl:
> > Hello,
> >
> >   I have a midsize program, and would like to simplify the module
> interfaces
> > for my own sanity.  I know there are tools to check for extraneous
> imports, but
> > is there something similar for exports?  For instance, if module A
> exports f,
> > but A.f is never used in my compiled program, I would like to be warned
> of this
> > fact.
>
> ghc -ddump-minimal-imports
>
> I think that's the flag.
>
> -- Dump
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] A few ideas about FRP and arbitrary access in time

2010-03-02 Thread Phil Jones
...Are hereby presented at:
http://www.ee.bgu.ac.il/~noamle/_downloads/gaccum.pdf

Comments are more than welcome.
(P.S Thanks to a whole bunch of people at #haskell for educating me about
this, but most notably Conal Elliott)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] minimal interface

2010-03-02 Thread Don Stewart
seanmcl:
> Hello,
> 
>   I have a midsize program, and would like to simplify the module interfaces
> for my own sanity.  I know there are tools to check for extraneous imports, 
> but
> is there something similar for exports?  For instance, if module A exports f,
> but A.f is never used in my compiled program, I would like to be warned of 
> this
> fact.

ghc -ddump-minimal-imports

I think that's the flag.

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


[Haskell-cafe] minimal interface

2010-03-02 Thread Sean McLaughlin
Hello,

  I have a midsize program, and would like to simplify the module interfaces
for my own sanity.  I know there are tools to check for extraneous imports,
but is there something similar for exports?  For instance, if module A
exports f, but A.f is never used in my compiled program, I would like to be
warned of this fact.

Thanks,

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


[Haskell-cafe] FFI and lists?

2010-03-02 Thread Kimberly Wallmark
I'm working with FFI to make a Haskell DLL that's called by C# code.   
I understand how to share simple types.  I've found reasonable  
documentation for struct-equivalents.  Is there a clean way to share  
lists, or should I make a linked-list struct and do it manually?


In other words, if I have
  adder :: CInt -> CInt -> CInt
  adder x y = (x+y)

then I can use
  foreign export stdcall adder :: CInt -> CInt -> CInt

and on the other side it behaves like
  int adder(int a, int b);

I'd like to know what to do if I have
  squares :: [CInt] -> [CInt]
  squares = map (^2)

Advice?

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


Re: [Haskell-cafe] Re: lhs2TeX \eval{} problem

2010-03-02 Thread Tom Lokhorst
Yes, this time I did copy/paste your code.

ghci loads the file correctly and `x` is in scope.

lhs2TeX just hangs on the \eval{4} line.

On 2 March 2010 21:46, Andres Loeh  wrote:
>> Oh, well that teaches me not to type myself... Copy-and-paste is way better!
>>
>> Now lhs2TeX no longer crashes, unfortunately it still doesn't work correctly.
>>
>> It now simply hangs after printing the line "Two".
>> It doesn't crash, or eat memory or cpu. It just sits there, doing
>> nothing, until I kill the process.
>
> Are you sure you added the extra line at the end? Try to call ghci
> on the source file. If it manages to load it without errors, then
> lhs2TeX should succeed as well.
>
> Cheers,
>  Andres
>
> --
>
> Andres Loeh, Universiteit Utrecht
>
> mailto:and...@cs.uu.nl     mailto:m...@andres-loeh.de
> http://www.andres-loeh.de
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: lhs2TeX \eval{} problem

2010-03-02 Thread Andres Loeh
> Oh, well that teaches me not to type myself... Copy-and-paste is way better!
> 
> Now lhs2TeX no longer crashes, unfortunately it still doesn't work correctly.
> 
> It now simply hangs after printing the line "Two".
> It doesn't crash, or eat memory or cpu. It just sits there, doing
> nothing, until I kill the process.

Are you sure you added the extra line at the end? Try to call ghci
on the source file. If it manages to load it without errors, then
lhs2TeX should succeed as well.

Cheers,
  Andres

-- 

Andres Loeh, Universiteit Utrecht

mailto:and...@cs.uu.nl mailto:m...@andres-loeh.de
http://www.andres-loeh.de
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad laws

2010-03-02 Thread Luke Palmer
On Tue, Mar 2, 2010 at 1:17 PM, David Sabel
 wrote:
> Hi,
> when checking the first monad law (left unit) for the IO-monad (and also for
> the ST monad):
>
> return a >>= f ≡ f a
>
> I figured out that there is the "distinguishing" context (seq [] True) which
> falsifies the law
> for a and f defined below
>
>
>> let a = True
>> let f = \x -> (undefined::IO Bool)
>> seq (return a >>= f) True
> True
>> seq (f a) True
> *** Exception: Prelude.undefined
>
> Is there a side-condition of the law I missed?

No, IO just doesn't obey the laws.  However, I believe it does in the
seq-free variant of Haskell, which is nicer for reasoning.  In fact,
this difference is precisely what you have observed: the
distinguishing characteristic of seq-free Haskell is that (\x ->
undefined) == undefined, whereas in Haskell + seq, (\x -> undefined)
is defined.

Operationally speaking, GHC cannot normalize an expression with IO
without executing the IO, because of the evaluation model.

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


[Haskell-cafe] Re: Real-time garbage collection for Haskell

2010-03-02 Thread Luke Palmer
On Tue, Mar 2, 2010 at 7:17 AM, Simon Marlow  wrote:
>> For games,
>> though, we have a very good point that occurs regularly where we know
>> that all/most short-lived objects will no longer be referenced - at the
>> start of a fresh frame.
>
> System.Mem.performGC is your friend, but if you're unlucky it might do a
> major GC and then you'll get more pause than you bargained for.

Some fine-grained control might be nice here.  Eg. I could do a major
GC as a player is opening a menu, on a loading screen, when the game
is paused, or some other key points, and it might still be annoying,
but at least it wouldn't interfere with gameplay.  There is of course
the question of what happens if one of these key points doesn't happen
when we need to do an allocation, but... oh well.  Perhaps that could
be mitigated by saying "I would rather you allocate than major GC
right now".  Are any of these options impossible, or be unreasonably
difficult to implement (I don't suspect so)?

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


[Haskell-cafe] Re: lhs2TeX \eval{} problem

2010-03-02 Thread Tom Lokhorst
> First, it's
>
> %options ghci

Oh, well that teaches me not to type myself... Copy-and-paste is way better!

Now lhs2TeX no longer crashes, unfortunately it still doesn't work correctly.

It now simply hangs after printing the line "Two".
It doesn't crash, or eat memory or cpu. It just sits there, doing
nothing, until I kill the process.

- Tom

On 2 March 2010 21:10, Andres Loeh  wrote:
> Hi.
>
>> I'm having a problem with lhs2Tex and \eval{}. It doesn't work.
>>
>> I have the following in a file test.lhs:
>>
>> 
>> %include polycode.fmt
>>
>> One
>> %option ghci
>> Two
>> \eval{4}
>> Three
>> 
>>
>> When I try to run this file through lhs2Tex, it crashes:
>>
>> > lhs2Tex test.lhs
>> ... polycode junk removed ...
>>
>> One
>> %option ghci
>> Two
>> lhs2TeX: fd:7: hGetLine: end of file
>>
>> 
>>
>> Has someone encountered this problem before, or knows how to solve this?
>
> Two issues:
>
> First, it's
>
> %options ghci
>
> and not
>
> %option ghci
>
> Second, the \eval is executed in the context of the current file,
> i.e., the source must be a valid literate Haskell file. An empty
> literate file causes the literate preprocessor to fail. This
> works for me:
>
> 
> %include polycode.fmt
>
> One
> %options ghci
> Two
> \eval{4}
> Three
>
>> x = 0
> 
>
> HTH,
>  Andres
>
> --
>
> Andres Loeh, Universiteit Utrecht
>
> mailto:and...@cs.uu.nl     mailto:m...@andres-loeh.de
> http://www.andres-loeh.de
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How do you rewrite your code?

2010-03-02 Thread Daniel Fischer
Am Dienstag 02 März 2010 21:00:56 schrieb Felipe Lessa:
> > I think the right-hand side (RHS) is more concise and simpler. The
> > types here do change: the type constructor has a Monad constraint in
> > the left-hand side and a Functor constraint in the RHS. Types that are
> > Monad instances are generally also Functor instances, so this is often
> > possible. I'm convinced the semantics are preserved, though I haven't
> > proven it.
>
> Yes, they are the same, always.
>

Provided the instances obey the monad/functor laws.

> --
> Felipe.

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


Re: [Haskell-cafe] How do you rewrite your code?

2010-03-02 Thread Andrey Sisoyev

Speaking about macrorewriting, I do prefer to break big modules (prototypes)
into smaller ones, then step by step separate them into a set of minimally
dependent and highly general cabal packages.

As for microrewriting I find it to be a good practice to explicate all
possible (programmable or Real World) errors into dedicated ADT
constructions. This draws enough attention to every error to guarantee that
there is no missed risks and protection is good enough.

Regards, Andrey
-- 
View this message in context: 
http://old.nabble.com/How-do-you-rewrite-your-code--tp27760033p27760681.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


[Haskell-cafe] Monad laws

2010-03-02 Thread David Sabel

Hi,
when checking the first monad law (left unit) for the IO-monad (and also 
for the ST monad):


return a >>= f ≡ f a

I figured out that there is the "distinguishing" context (seq [] True) 
which falsifies the law

for a and f defined below


> let a = True
> let f = \x -> (undefined::IO Bool)
> seq (return a >>= f) True
True
> seq (f a) True
*** Exception: Prelude.undefined

Is there a side-condition of the law I missed?

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


[Haskell-cafe] Re: lhs2TeX \eval{} problem

2010-03-02 Thread Andres Loeh
Hi.

> I'm having a problem with lhs2Tex and \eval{}. It doesn't work.
> 
> I have the following in a file test.lhs:
> 
> 
> %include polycode.fmt
> 
> One
> %option ghci
> Two
> \eval{4}
> Three
> 
> 
> When I try to run this file through lhs2Tex, it crashes:
> 
> > lhs2Tex test.lhs
> ... polycode junk removed ...
> 
> One
> %option ghci
> Two
> lhs2TeX: fd:7: hGetLine: end of file
> 
> 
> 
> Has someone encountered this problem before, or knows how to solve this?

Two issues:

First, it's

%options ghci

and not

%option ghci

Second, the \eval is executed in the context of the current file,
i.e., the source must be a valid literate Haskell file. An empty
literate file causes the literate preprocessor to fail. This
works for me:


%include polycode.fmt

One
%options ghci
Two
\eval{4}
Three

> x = 0


HTH,
  Andres

-- 

Andres Loeh, Universiteit Utrecht

mailto:and...@cs.uu.nl mailto:m...@andres-loeh.de
http://www.andres-loeh.de
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Where is HEAD?

2010-03-02 Thread Alp Mestanogullari
Download that tarball :
http://darcs.haskell.org/ghc-HEAD-2009-10-23-ghc-corelibs-testsuite.tar.gz
And then uncompress it, enter the directory, and execute : ./darcs-all pull
-a  (it may need you to chmod +x it)
And then you will have ghc HEAD.

On Tue, Mar 2, 2010 at 9:01 PM, Louis Wasserman
wrote:

> Where is GHC 6.13 head?  I can find sources of 6.13, and darcs for 6.12,
> but not darcs for 6.13...I'm trying to play with the LLVM backend, and this
> is the one question it seems to presuppose that you know the answer to.
> Heh.
>
> Louis Wasserman
> wasserman.lo...@gmail.com
> http://profiles.google.com/wasserman.louis
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


-- 
Alp Mestanogullari
http://alpmestan.wordpress.com/
http://alp.developpez.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Where is HEAD?

2010-03-02 Thread Louis Wasserman
Where is GHC 6.13 head?  I can find sources of 6.13, and darcs for 6.12, but
not darcs for 6.13...I'm trying to play with the LLVM backend, and this is
the one question it seems to presuppose that you know the answer to.  Heh.

Louis Wasserman
wasserman.lo...@gmail.com
http://profiles.google.com/wasserman.louis
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How do you rewrite your code?

2010-03-02 Thread Felipe Lessa
On Tue, Mar 02, 2010 at 08:20:30PM +0100, Sean Leather wrote:
> There are numerous threads on the Haskell Café involving rewriting,
> refactoring, refining, and in general improving code (for some definition of
> improve). I am interested in seeing examples of how Haskell code can be
> rewritten to make it better. Some general examples are:

One handy manual transformation is trying to do more checks on
the typechecker.  GADT's + phantom types are very useful!

> x >>= return . f
> -->
> fmap f x
> or
> f <$> x -- requires importing Control.Applicative
>
> I think the right-hand side (RHS) is more concise and simpler. The types
> here do change: the type constructor has a Monad constraint in the left-hand
> side and a Functor constraint in the RHS. Types that are Monad instances are
> generally also Functor instances, so this is often possible. I'm convinced
> the semantics are preserved, though I haven't proven it.

Yes, they are the same, always.

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


[Haskell-cafe] lhs2TeX \eval{} problem

2010-03-02 Thread Tom Lokhorst
Hello,

I'm having a problem with lhs2Tex and \eval{}. It doesn't work.

I have the following in a file test.lhs:


%include polycode.fmt

One
%option ghci
Two
\eval{4}
Three


When I try to run this file through lhs2Tex, it crashes:

> lhs2Tex test.lhs
... polycode junk removed ...

One
%option ghci
Two
lhs2TeX: fd:7: hGetLine: end of file



Has someone encountered this problem before, or knows how to solve this?

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


[Haskell-cafe] ANN: Progression-0.3 (supporting benchmarking in Haskell)

2010-03-02 Thread Neil Brown

Hi all,

I've just uploaded the new version of my Progression benchmarking 
library to Hackage (http://hackage.haskell.org/package/progression).  
Progression is a utility built on top of Criterion that helps you record 
benchmark times for several different versions of your code and then 
draw graphs to compare them.  The latest version adds: support for 
normalisation of benchmark times, support for drawing bar charts, and 
allows for more detailed configuration of how the data is arranged 
before plotting.


I've written in more detail about the changes in a blog post 
(http://chplib.wordpress.com/2010/03/02/progression-0-3-bar-charts-and-normalisation/), 
which also has an example of a normalised bar chart generated with the 
new version.


Thanks,

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


[Haskell-cafe] Re: Multiple Interpretations for a monad?

2010-03-02 Thread Heinrich Apfelmus
Ryan Ingram wrote:
> To take this a step further, there is the DSL:
> 
>  get :: m S
>  put :: S -> m ()
> 
> and the concrete implementation
> 
>   m = State S
> 
> Of course, there are other monads which implement this DSL as well:
> 
>   m = StateT S IO
> 
>   m = Prompt StatePrompt
> with
>   data StatePrompt a where
>Get :: StatePrompt S
>Put :: S -> StatePrompt ()

Elaborating on that, the DSL consists of two specific functions

   get, put

and two general function

   (>>=), return

Every combination of those is a program in the DSL. Example programs:

   get >>= put
   get >>= \x -> return (x,x)
   put 1 >>= \() -> get >>= \x -> return (2*x)

This is the *syntactic* part of the DSL.


Of course, we also need *semantics*, and those are given by an
interpreter function. Examples:

   interpret :: m a -> (S -> a)
   interpret :: m a -> (S -> (a,S))
   interpret :: m a -> StateT S IO a

When the state monad is implemented as

   m a = S -> (a,S)

this function is just the identity

   interpret :: (S -> (a,S)) -> (S -> (a,S))
   interpret = id

but as the  MonadPrompt  or  operational  packages show, this does not
need to be the case; it is, in fact, beneficial to use a generic
representation for the syntax and make the  interpret  function do all
the work.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: haskelldb problem

2010-03-02 Thread Christian Maeder
Documentation should be:
http://hackage.haskell.org/packages/archive/haskelldb/0.12/doc/html/Database-HaskellDB-DBSpec.html
http://hackage.haskell.org/packages/archive/haskelldb/0.12/doc/html/Database-HaskellDB-DBSpec-PPHelpers.html

assuming you have the haskelldb-0.12 package installed.

HTH Christian

Immanuel Normann schrieb:
> Hi,
> 
> I have problems with the usage of the DBSpec module. The following used
> to work a year ago:
> 
> testDB :: DBInfo
> testDB = makeDBSpec "testDB" (DBOptions False) [t1]
> 
> t1 :: TInfo
> t1 = makeTInfo "t1" [c1,c2]
> 
> c1 :: CInfo
> c1 = makeCInfo "c1" (IntT,False)
> c2 :: CInfo
> c2 = makeCInfo "c2" (StringT,False)
> 
> Now the problem is type error in (DBOptions False):
> 
> Couldn't match expected type `DBOptions'
>against inferred type `Database.HaskellDB.DBSpec.
> PPHelpers.MakeIdentifiers
> 
> So my precise problem is the usage of that "MakeIdentifiers":
> 
> MakeIdentifiers   
>   moduleName :: String -> String   
>   identifier :: String -> String   
>   toType :: String -> String
> 
> Could someone please demonstrate how to use MakeIdentifiers reasonably
> e.g. for the above testDB? And more general: I cannot find uptodate
> documentation on haskelldb. Is there something around?
> 
> Thanks
> Immanuel
> 
> 
> 
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How do you rewrite your code?

2010-03-02 Thread Alp Mestanogullari
For the style part, I recommend hlint [1].

Regarding the testing, QuickCheck is excellent and I have been happy with it
so far.

>From a more general point of view, I agree with a point of view that many
haskellers seem to share, but that Cale Gibbard put in words on #haskell
regularly. It consists in looking at your code from a higher point of view
and trying to express what you wrote in a "sublanguage" of primitives and
combinators. He pointed to [2] for more details and examples.

Hope it helps.

[1] http://community.haskell.org/~ndm/hlint/
[2] http://contracts.scheming.org/

On Tue, Mar 2, 2010 at 8:20 PM, Sean Leather  wrote:

> There are numerous threads on the Haskell Café involving rewriting,
> refactoring, refining, and in general improving code (for some definition of
> improve). I am interested in seeing examples of how Haskell code can be
> rewritten to make it better. Some general examples are:
>
>- Eta-reduce
>- Make more pointfree
>- Introduce monadic operators or do-notation
>   - e.g. for Maybe, lists, State
>   - Eliminate monadic operators or do-notation
>- Generalize types
>   - e.g. change map to fmap, (++) to mappend
>   - Use instances of Functor, Applicative, Alternative, Category,
>Arrow, Monoid, Traversable, etc.
>- Use library functions from Data.List, Data.Map, Data.Set, etc.
>- Use some form of generic programming (e.g. SYB, Uniplate, EMGM,
>Alloy)
>- Use other libraries not included in the Platform
>
>
> My question is simple:
>
>*How do you rewrite your code to improve it?*
>
> You can answer this in any way you like, but I think the most useful answer
> is to show a reasonably small, concrete example of what your code looked
> like before and after. Also, please describe how you think the rewrite
> improves such code.
>
>- Is it better style? More useful? More efficient?
>- Are the types (before and after) the same?
>- Are the semantics the same?
>- How did you prove or test equivalence? (e.g. Can you use equational
>reasoning to confirm the rewrite is valid? Did you use QuickCheck?)
>
>
> Here is an example that I find myself doing occasionally.
>
> For all x, f:
>
> x >>= return . f
> -->
> fmap f x
> or
> f <$> x -- requires importing Control.Applicative
>
> I think the right-hand side (RHS) is more concise and simpler. The types
> here do change: the type constructor has a Monad constraint in the left-hand
> side and a Functor constraint in the RHS. Types that are Monad instances are
> generally also Functor instances, so this is often possible. I'm convinced
> the semantics are preserved, though I haven't proven it.
>
> What's an example of a rewrite that you've encountered?
>
> Thanks,
> Sean
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


-- 
Alp Mestanogullari
http://alpmestan.wordpress.com/
http://alp.developpez.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: How do you rewrite your code?

2010-03-02 Thread Johannes Waldmann
Not exactly answering your question, but here's the top refactorings
that I'd like to see in a Haskell IDE:

* rename identifier (aware of scopes, modules, qualified imports etc.)
* move definition from one module to another (aware of ...)

* change "type" to "newtype" or "data"
* change positional to named record notation

* introduce parameter (to function) 
  (with a default value that is plugged in at each call site)
* change order of parameters
* introduce parameter object

That's the kind of basic rewriting that is really really awkward to do
with a plain text editor (because you really need the annotated AST,
with names resolved, and types attached) - so it's usually avoided (well, by me)
and the result is code that is a nightmare to maintain.



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


[Haskell-cafe] How do you rewrite your code?

2010-03-02 Thread Sean Leather
There are numerous threads on the Haskell Café involving rewriting,
refactoring, refining, and in general improving code (for some definition of
improve). I am interested in seeing examples of how Haskell code can be
rewritten to make it better. Some general examples are:

   - Eta-reduce
   - Make more pointfree
   - Introduce monadic operators or do-notation
  - e.g. for Maybe, lists, State
  - Eliminate monadic operators or do-notation
   - Generalize types
  - e.g. change map to fmap, (++) to mappend
  - Use instances of Functor, Applicative, Alternative, Category, Arrow,
   Monoid, Traversable, etc.
   - Use library functions from Data.List, Data.Map, Data.Set, etc.
   - Use some form of generic programming (e.g. SYB, Uniplate, EMGM, Alloy)
   - Use other libraries not included in the Platform


My question is simple:

   *How do you rewrite your code to improve it?*

You can answer this in any way you like, but I think the most useful answer
is to show a reasonably small, concrete example of what your code looked
like before and after. Also, please describe how you think the rewrite
improves such code.

   - Is it better style? More useful? More efficient?
   - Are the types (before and after) the same?
   - Are the semantics the same?
   - How did you prove or test equivalence? (e.g. Can you use equational
   reasoning to confirm the rewrite is valid? Did you use QuickCheck?)


Here is an example that I find myself doing occasionally.

For all x, f:

x >>= return . f
-->
fmap f x
or
f <$> x -- requires importing Control.Applicative

I think the right-hand side (RHS) is more concise and simpler. The types
here do change: the type constructor has a Monad constraint in the left-hand
side and a Functor constraint in the RHS. Types that are Monad instances are
generally also Functor instances, so this is often possible. I'm convinced
the semantics are preserved, though I haven't proven it.

What's an example of a rewrite that you've encountered?

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


Re: [Haskell-cafe] references for compiler optimizations for functional languages

2010-03-02 Thread Andrew Coppin

Don Stewart wrote:

mvanier42:
  

Hi everyone,

I'm interested in collecting good references for compiler optimizations  
for functional languages (lazy, strict, statically-typed or not).  Any  
suggestions?





There's lots for what GHC implements on SimonPJ's site:

http://www.research.microsoft.com/~simonpj/Papers/inlining/index.htm

http://research.microsoft.com/en-us/um/people/simonpj/papers/cpr/index.htm


http://research.microsoft.com/en-us/um/people/simonpj/papers/usage-types/usage.htm


http://research.microsoft.com/en-us/um/people/simonpj/papers/comp-by-trans-scp.ps.gz


http://research.microsoft.com/en-us/um/people/simonpj/papers/andy-thesis.ps.gz


http://research.microsoft.com/en-us/um/people/simonpj/papers/deforestation-short-cut.ps.Z

http://www.cse.unsw.edu.au/~dons/papers/CLS07.html :)

I've collected many of them here:

http://haskell.org/haskellwiki/Research_papers/Compilation#Compiler_Analyses
  


Is there anywhere that documents the current Core language used by GHC? 
(I gather there are slight variations of it; I'm interested in what 
-ddump-simpl emits.)


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


[Haskell-cafe] haskelldb problem

2010-03-02 Thread Immanuel Normann
Hi,

I have problems with the usage of the DBSpec module. The following used to
work a year ago:

testDB :: DBInfo
testDB = makeDBSpec "testDB" (DBOptions False) [t1]

t1 :: TInfo
t1 = makeTInfo "t1" [c1,c2]

c1 :: CInfo
c1 = makeCInfo "c1" (IntT,False)
c2 :: CInfo
c2 = makeCInfo "c2" (StringT,False)

Now the problem is type error in (DBOptions False):

Couldn't match expected type `DBOptions'
   against inferred type `Database.HaskellDB.DBSpec.
PPHelpers.MakeIdentifiers

So my precise problem is the usage of that "MakeIdentifiers":

MakeIdentifiers
  moduleName :: String -> String
  identifier :: String -> String
  toType :: String -> String

Could someone please demonstrate how to use MakeIdentifiers reasonably e.g.
for the above testDB? And more general: I cannot find uptodate documentation
on haskelldb. Is there something around?

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


[Haskell-cafe] Re: Real-time garbage collection for Haskell

2010-03-02 Thread Simon Marlow

On 02/03/2010 14:11, Malcolm Wallace wrote:

Both concurrent GC and incremental GC tend to add overheads to the
mutator, because they need a read barrier. There was an incremental GC
for GHC once [1], taking advantage of the built-in read barrier that
we have whereby most closures are "entered"


Was there a specific reason why that GC implementation chose to use a
read barrier rather than a write barrier? I would have thought that in
general, a write barrier is cheaper to implement. Doesn't ghc update
fewer thunks than it enters?


If the GC wants to move objects, then a read barrier is needed in order 
to figure out whether you're looking at an object that has moved or not. 
 If you don't move objects, then you can get away with only a write 
barrier - the write barrier is needed so that you can remember which 
objects or fields might need to be re-scanned because they were mutated.


The choice made in the Non-stop Haskell paper was to take advantage of 
the existing read barrier so that we could move objects.


Some schemes copy objects rather than move them, and then you can get 
away without a read barrier, but then your write barrier has to keep the 
two copies in sync.  Tradeoffs are everywhere, GC is a tricky business!


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


[Haskell-cafe] Re: Real-time garbage collection for Haskell

2010-03-02 Thread Simon Marlow

On 01/03/2010 17:16, Sebastian Sylvan wrote:



On Sun, Feb 28, 2010 at 5:20 AM, Luke Palmer mailto:lrpal...@gmail.com>> wrote:

I have seen some proposals around here for SoC projects and other
things to try to improve the latency of GHC's garbage collector.  I'm
currently developing a game in Haskell, and even 100ms pauses are
unacceptable for a real-time game.  I'm calling out to people who have
seen or made such proposals, because I would be willing to contribute
funding and/or mentor a project that would contribute to this goal.
Also any ideas for reducing this latency in other ways would be very
appreciated.


Since we're talking games here (my profession), I'd point out that it
would be cool to be able to supply "hints" to the GC about when might be
a good time to do a GC (without unconditionally forcing it), games in
particular have some pretty specific properties that may be exploitable.

Presumably a non-trivial portion of the objects copied from the
nursery/G0 are actually short-lived objects that just happened to have
their short life-span overlap with the collection. So really, copying
them to the next generation is a "mistake" in some sense.


There's a technique we use, that mitigates the effect of this to some 
extent, called "aging".  The idea is that an object is only promoted if 
it survives at least N GCs in the young generation.  Typically N=2 is a 
good value, so an object that is allocated just before a minor GC will 
be copied, but probably not promoted unless it survives all the way to 
the next GC. You can also use fractional values of N and in fact you 
should measure N in terms of bytes allocated rather than GCs.  In GHC 
6.12.1 you can tune the amount of aging with +RTS -T, but I removed 
the option in 6.14 in order to make the GC implementation simpler, we 
now have a fixed aging -T2 aging policy. In practice other values were 
very rarely any better, in fact.



For games,
though, we have a very good point that occurs regularly where we know
that all/most short-lived objects will no longer be referenced - at the
start of a fresh frame.


System.Mem.performGC is your friend, but if you're unlucky it might do a 
major GC and then you'll get more pause than you bargained for.


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


Re: [Haskell-cafe] Re: Real-time garbage collection for Haskell

2010-03-02 Thread Malcolm Wallace
Both concurrent GC and incremental GC tend to add overheads to the  
mutator, because they need a read barrier.  There was an incremental  
GC for GHC once [1], taking advantage of the built-in read barrier  
that we have whereby most closures are "entered"


Was there a specific reason why that GC implementation chose to use a  
read barrier rather than a write barrier?  I would have thought that  
in general, a write barrier is cheaper to implement.  Doesn't ghc  
update fewer thunks than it enters?


Regards,
Malcolm




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


[Haskell-cafe] Re: Real-time garbage collection for Haskell

2010-03-02 Thread Simon Marlow

On 01/03/2010 14:53, Thomas Schilling wrote:

On 28 February 2010 05:20, Luke Palmer  wrote:

I have seen some proposals around here for SoC projects and other
things to try to improve the latency of GHC's garbage collector.  I'm
currently developing a game in Haskell, and even 100ms pauses are
unacceptable for a real-time game.  I'm calling out to people who have
seen or made such proposals, because I would be willing to contribute
funding and/or mentor a project that would contribute to this goal.
Also any ideas for reducing this latency in other ways would be very
appreciated.


There is a SoC project suggestion to implement Immix's ideas [1] in
GHC's GC.  Both already use similar overall designs.  Both split the
heap into regions which may employ different collection strategies.
However, Immix does not address real-time issues.

The main difficulty with real-time GC is that, while first-generation
collection is usually very fast, eventually you just have to collect
the old generation and you have to do it all at once.  Sun's new
Garbage-First ("G1") [2] collector therefore tracks pointers between
regions, as opposed to just pointers from older two newer generations.
  This allows collecting regions independently (and in parallel).  G1
is still stop-the-world, although marking phase is concurrent.
Tracking pointers between all regions can result in quite substantial
space overheads, however, so G1 uses some heuristics to discover
"popular objects" and treats them specially.  In a personal
conversation Simon Marlow expressed to me that he intends to go
further into this direction, but I don't know how high-priority it is.
  In general I don't think true real-time is the goal in any case, but
rather a general effort to keep GC-pauses short.

Truly concurrent garbage collection is a whole different beast.
Concurrent marking can be implemented efficiently with a write
barrier.  I don't know of any fully concurrent GC scheme that gets by
without a read barrier and significant space overhead, however.  There
are certainly no plans from the GC HQ to implement a fully concurrent
GC.


A good summary of concurrent GC techniques used successfully in industry 
was posted to the GC mailing list recently by Erez Petrank:


http://permalink.gmane.org/gmane.comp.programming.garbage-collection.general/388

Several of those we could do in GHC, for example mostly-concurrent 
collection uses only a write barrier, and piggybacks on the generational 
write-barrier we already have, but it does require two stop-the-world 
phases per GC.  I think you'd want to do it in conjunction with 
Immix-style region sweeping in the old generation, so implementing Immix 
would be a good first step.


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


[Haskell-cafe] Re: Real-time garbage collection for Haskell

2010-03-02 Thread Simon Marlow

On 01/03/2010 14:16, Sönke Hahn wrote:

On Monday 01 March 2010 01:04:37 am Luke Palmer wrote:

On Sun, Feb 28, 2010 at 2:06 AM, Pavel Perikov  wrote:

Did you really seen 100ms pauses?! I never did extensive research on this
but my numbers are rather in microseconds range (below 1ms). What causes
such a long garbage collection? Lots of allocated and long-living
objects?


This is all hypothetical right now.  I heard some horror stories in
which people had to switch to the main game loop in C++ and only do
the AI logic in Haskell because of pauses.  I would rather not do
that, especially because this project is *about* proving Haskell as a
viable game development platform.  So I am trying to be prepared if I
do see something like that, so that it doesn't put the show on hold
for a few months.

Presumably large, long-living objects would cause the generation 0
collections to take a long time.  I am not sure if we will have any
said objects, but we can't rule it out...

Thanks for the positive reassurances, at least.  I'd like to hear from
people with the opposite experience, if there are any.


Yes there are. I am working on a game with Haskell using OpenGL rendering.
I've done some frame time measurements lately and encountered single frames
needing more than 100ms to be rendered. I am currently trying to gather
information on what is going on in these 100ms and why. From what i
understand, the GC is running very often and just some (very few) of its runs
are very slow.

BTW: switching to parallel GC (either with -N1 or -N2 (on a dual core
machine)) made the behavior MUCH worse, for some reason.


Probably due to cache effects - shipping the data off to a different 
core in the GC can far outweigh any benefits you would have got by 
traversing the heap in parallel.  For a single-threaded program, 
parallel GC tends to only help when the heap gets large (over 50MB at a 
guess).  For parallel programs, parallel GC helps by keeping the data in 
the right cache.


I'm finding that for parallel programs turning off load-balancing with 
+RTS -qb often helps, because load-balancing is bad for locality. 
Again, if the heap gets large, then collecting it in parallel is 
probably more important than keeping it in the cache.


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


[Haskell-cafe] Re: Real-time garbage collection for Haskell

2010-03-02 Thread Simon Marlow

On 01/03/2010 00:04, Luke Palmer wrote:

On Sun, Feb 28, 2010 at 2:06 AM, Pavel Perikov  wrote:

Did you really seen 100ms pauses?! I never did extensive research on this but 
my numbers are rather in microseconds range (below 1ms). What causes such a 
long garbage collection? Lots of allocated and long-living objects?


This is all hypothetical right now.  I heard some horror stories in
which people had to switch to the main game loop in C++ and only do
the AI logic in Haskell because of pauses.  I would rather not do
that, especially because this project is *about* proving Haskell as a
viable game development platform.  So I am trying to be prepared if I
do see something like that, so that it doesn't put the show on hold
for a few months.

Presumably large, long-living objects would cause the generation 0
collections to take a long time.  I am not sure if we will have any
said objects, but we can't rule it out...

Thanks for the positive reassurances, at least.  I'd like to hear from
people with the opposite experience, if there are any.


By default GHC uses a generational GC with a 512KB nursery size, which 
means that most GC pauses will be very short but just occasionally you 
have to do a major GC and there's no upper bound on the pause time for 
that collection, because the whole live heap is traversed.  The pause 
time for a major collection is proportional to the amount of live data, 
so the people who are experiencing very short pauses probably have 
little live data and/or have allocation patterns that means the old 
generation is collected very infrequently.


Monolithic major GC is a big stinking scalability problem, and the only 
solutions are to do concurrent GC, incremental GC, or region-based GC.


Both concurrent GC and incremental GC tend to add overheads to the 
mutator, because they need a read barrier.  There was an incremental GC 
for GHC once [1], taking advantage of the built-in read barrier that we 
have whereby most closures are "entered", and it more-or-less worked but 
was quite complicated and had some code-size overhead.  Nowadays part of 
this built-in read barrier has been eroded by pointer tagging, which 
makes things a bit more tricky.


Region-based GC is a generalisation of generational GC, where you divide 
the heap into regions and track all pointers between regions, so a given 
collection can collect any subset of the regions.  This basic idea is 
quite popular amongst the Java people these days, Thomas mentioned the 
G1 collector which does this and uses a concurrent mark phase to 
identify which regions to collect.  Regardless of how you figure out 
which regions to collect, the basic idea of breaking up the old 
generation like this is a good way to reduce pause times.


At the moment I'm focussed on something different: making individual 
processors able to collect their own heaps independently, so removing 
the stop-the-world requirement from minor GCs.  This should help 
parallel throughput a lot, but won't fix the major GC pause times.  I am 
slightly worried that the GC can't bear the extra complexity of adding 
both processor-independent GC *and* region-based GC or some other 
pause-time-reducing technique. But we'll see.  I'll happily 
supervise/mentor anyone who wants to tackle this.


Cheers,
Simon

[1] 
http://delivery.acm.org/10.1145/36/351265/p257-cheadle.pdf?key1=351265&key2=8540457621&coll=GUIDE&dl=GUIDE&CFID=80115628&CFTOKEN=59704548

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


Re: [Haskell-cafe] Has anybody translated Douglas Hofstadter's Scientific American articles introducting Scheme to a general audience into Haskell?

2010-03-02 Thread Gwern Branwen
On Tue, Mar 2, 2010 at 1:04 AM, Benjamin L. Russell
 wrote:
> There is an interesting, if somewhat dated, suggestion on "Lambda the
> Ultimate" (see http://lambda-the-ultimate.org/node/1748) that "someone
> translate Doug Hofstadter's Scientific American columns introducing
> Scheme to a general audience into Haskell."
>
> (I came across this link while adding full titles and links to the
> HaskellWiki "Books and tutorials" page (see
> http://www.haskell.org/haskellwiki/Books_and_tutorials), where I clicked
> on the link to "Tutorials" (see
> http://www.haskell.org/haskellwiki/Tutorials), which contained a link to
> a "Haskell vs. Scheme" (see http://www.reddit.com/r/programming/tb/nq1k)
> article, which described the post containing the suggestion.)
>
> According to a comment by Ehud Lamm (see
> http://lambda-the-ultimate.org/node/1748#comment-21292) on the above
> post, the columns are in Hoftstadter's book _Metamagical Themas:
> Questing For The Essence Of Mind And Pattern_ [1] (see
> http://www.amazon.com/Metamagical-Themas-Questing-Essence-Pattern/dp/0465045669).
>
> Has anybody translated Hofstadter's articles from Scheme into Haskell?
>
> -- Benjamin L. Russell

I have scans of the column and have meant to translate them; but you
know how it is...

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


[Haskell-cafe] Gtk2hs on Snow Leopard: "Failed to load interface for `System.Glib.UTFString'"

2010-03-02 Thread Michael Goy
Hi,

I am very close to suicide or similar acts of pure desperation... 

Since weeks, I am trying different approaches to get gtk2hs running on my Snow 
Leopard MacBook Pro... no success, you guess it...

My current GHC is 6.10.4 (but I also tried 6.10.3 before) when I try to make 
GTK2HS from Source GTK2HS-0.10.1 I get the following error:

Failed to load interface for `System.Glib.UTFString'

It seems to be a glib problem; I attached a log of make with everything 
disabled except glib. 

BTW: I am interested in ANY hints how to get gtk2hs running on Snow Leopard: Is 
there any known solution for this problem that i wasn't able to find via google?

Best regards
Mitch


make.log
Description: Binary data


smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] haskelldb problem

2010-03-02 Thread Immanuel Normann
Hi,

I have problems with the usage of the DBSpec module. The following used to
work a year ago:

testDB :: DBInfo
testDB = makeDBSpec "testDB" (DBOptions False) [t1]

t1 :: TInfo
t1 = makeTInfo "t1" [c1,c2]

c1 :: CInfo
c1 = makeCInfo "c1" (IntT,False)
c2 :: CInfo
c2 = makeCInfo "c2" (StringT,False)

Now the problem is type error in (DBOptions False):

Couldn't match expected type `DBOptions'
   against inferred type
`Database.HaskellDB.DBSpec.PPHelpers.MakeIdentifiers

So my precise problem is the usage of that "MakeIdentifiers":

MakeIdentifiers
  moduleName :: String -> String
  identifier :: String -> String
  toType :: String -> String

Could someone please demonstrate how to use MakeIdentifiers reasonably e.g.
for the above testDB? And more general: I cannot find uptodate documentation
on haskelldb. Is there something around?

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


[Haskell-cafe] segmentation fault with ghc-6.10.4 on linux-x86_x64

2010-03-02 Thread Wim Vanderbauwhede
Hello,

I'm writing a compiler and it segfaults when compiled with  ghc-6.10.4
on linux-x86_x64.
It runs fine when compiled with ghc-6.10.4 on Mac OS X 10.5 (64-bit
Intel) and with ghc-6.8.2 on Mac OS X 10.4 (32-bit PPC).
I use the Haskell platform, the ghc -v output is

Glasgow Haskell Compiler, Version 6.10.4, for Haskell 98, stage 2
booted by GHC version 6.8.2
Using package config file: /usr/local/lib/ghc-6.10.4/./package.conf
Using package config file: /users/wim/.ghc/x86_64-linux-6.10.4/package.conf
hiding package base-3.0.3.1 to avoid conflict with later version base-4.1.0.0
hiding package network-2.2.1.2 to avoid conflict with later version
network-2.2.1.4
hiding package time-1.1.2.4 to avoid conflict with later version time-1.1.4
wired-in package ghc-prim mapped to ghc-prim-0.1.0.0
wired-in package integer mapped to integer-0.1.0.1
wired-in package base mapped to base-4.1.0.0
wired-in package rts mapped to rts-1.0
wired-in package haskell98 mapped to haskell98-1.0.1.0
wired-in package syb mapped to syb-0.1.0.1
wired-in package template-haskell mapped to template-haskell-2.3.0.1
wired-in package dph-seq mapped to dph-seq-0.3
wired-in package dph-par mapped to dph-par-0.3



The offending code is (simplified)

    mapM emit (sc_args sc)

with

sc::ServiceCall
data ServiceCall = MkServiceCall { sc_args::[Expr], ... }
data Expr = PureE (PString String) | ...

and emit defined via a type class EmitG:

emitExpr (PureE e) = emit e
   instance EmitG Expr where emit = emitExpr

emitPureExpr (PString s) = return $ show s
instance EmitG PureExpr where emit = emitPureExpr

So it actually maps "show" over a list of strings.

The compiler parses a test program, the segfault occurs when emitting
code for lines like
  ImgBlock() img1 = img.in("img.raw");
(a "service call" in my language)
Replacing the string by a number of any other type of the AST makes no
difference.

It looks like a bug in ghc's memory allocation. Any suggestions on how
to debug this?


Thanks!

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


Re: [Haskell-cafe] What are "free" Monads?

2010-03-02 Thread Sebastian Fischer


On Mar 2, 2010, at 5:59 AM, Dan Doel wrote:


 http://haskell.org/haskellwiki/Free_monad
 http://haskell.org/haskellwiki/Free_structure


Nice, thank you for writing this.


Feel free to make suggestions/changes.



I enjoyed reading it although Section 3 is challenging for people  
(like me) who know algebra but do not know the exact meaning of the  
mentioned terminology from CT even if they have read about it before.  
It would be helpful to add intuitive explanations. For example, after


"Simplest" (in the sense we want) structures in that category  
will then
either be initial or terminal, and thus, freeness can be defined  
in terms

of such universal constructions.

I missed sentences

Intuitively, "initial" means that ... and thus relates to the  
informal

description because ...

Final means ... and expresses the informal idea of ...

Similarly, subsequent uses of CT terminology (like 'forgetful functor'  
and 'natural transformation') could be related to intuitions given  
before (or new ones).


Sebastian


--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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