Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution

2012-01-29 Thread Donn Cave
On 28/01/2012 13:00, Paul R wrote:
...
> All this dot syntax magic frankly frightens me. Haskell, as a pure
> functionnal language, requires (and allows !) a programming style that
> just does not mix well with object oriented practices. Stretching the
> syntax to have the dot feel a-bit-but-not-really like object oriented
> programming, mainly to have IDE autocompletion on some cases, does not
> make much sens.

In the glasgow-haskell-users discussion, it has been pointed out (to 
little apparent effect) that the current notation for access by field
name, `field record', is naturally functional and is easier to read
for a functionally trained eye than a postfix `record.field' alternative.
It isn't so much of an issue for OO programmers because the languages
are also procedural and the expressions tend to be simpler.  In a
language like Haskell, an expression could switch back and forth several
times between pre-fix (functional) and post-fix (dot) notation.  Like,
`yolk (separate (crack (largeEnd egg)))' becomes
`(separate (crack (egg.smallEnd))).yolk'

That elementary example doesn't give me much trouble, but it sure
doesn't seem to be much of an improvement in notational elegance.
See how natural the transformation with function composition -

yolk (separate (crack (largeEnd egg)))
yolk ((separate . crack . largeEnd) egg)
yolk (f egg) where f = separate . crack . largeEnd

... compared to the re-shuffing necessary with post-fix dot notation
(assuming for the sake of discussion a functional dot notation
 .field = \ r -> r.field)

(separate (crack (egg.smallEnd))).yolk
((separate . crack . .smallEnd) egg).yolk
(f egg).yolk where f = separate . crack . .smallEnd

Donn

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


Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution

2012-01-29 Thread Steve Horne

On 30/01/2012 04:23, Steve Horne wrote:

On 28/01/2012 13:00, Paul R wrote:

AntC>  Steve, I think that proposal has been rather superseeded by
AntC>  
http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields, 
which
AntC>  draws on TDNR. But SORF is best seen as an evolving design 
space, with precise
AntC>  details yet to be clarified/agreed. I've put my own variation 
into the ring:

AntC>  http://www.haskell.org/pipermail/glasgow-haskell-users/2011-
AntC>  December/021298.html -- which seems to have fallen into a 
black hole :-(


AntC>  One of the aspects of TDNR that wasn't so popular was that its 
type-directed
AntC>  resolution was very similar to instance resolution, but subtly 
and confusingly

AntC>  different.

AntC>  I guess we have to be very careful about the dot. It seems to 
be in a
AntC>  very 'crowded' syntax space, so if we implement the wrong way, 
we could end up

AntC>  shutting the door with the keys left inside.

AntC>  (...)

All this dot syntax magic frankly frightens me. Haskell, as a pure
functionnal language, requires (and allows !) a programming style that
just does not mix well with object oriented practices. Stretching the
syntax to have the dot feel a-bit-but-not-really like object oriented
programming, mainly to have IDE autocompletion on some cases, does not
make much sens.
That's a benefit of my idea. Modular programming used the dot long 
before OOP became popular - OOP stole the dot from modular 
programming! If a record is a module, that only means that one thing 
can be both a module and a type (or value) at the same time. It takes 
little from OOP that OOP didn't already take from the more fundamental 
modular programming - and Haskell already has modules.



Sorry for replying to myself - I just thought I could explain this better.

I'm basically asserting that a record in standard Pascal (without any of 
that OOP Turbo Pascal 5.5+/Delphi stuff) is a module. It doesn't matter 
that the only names that can be held in that module are field names - 
it's still a container of named items and therefore a special case of a 
module.


In the Pascal case (like C structs), the content of the module doesn't 
include functions or methods or whatever, it only includes fields. And 
the module is only accessible via the record instances, not via the 
record type (there's nothing like C++ member pointers).


Converting this to Haskell - well, we already use field-access 
functions, so why not move those to the record-instance module instead 
of having them pollute some existing namespace?


Since naming the same thing twice (once to identify the module, once to 
specify the instance parameter) would be annoying, why not auto-curry 
that parameter? The result is still a function living in a module.


And rather than lose the original function, why not move that to another 
scope - a module that's associated with the record type rather than the 
record instance? If you don't specify an instance, you can't curry that 
parameter - it still makes sense.


There's no inheritance here, no virtual functions, no OOP features at 
all - just Pascal-like records adapted for immutability by supplying a 
field access function rather than e.g. a field offset. The function 
placed in the record-type module would be the exact same function we get 
now, just in a different scope.


However, once you have the idea that a record is a module, maybe it 
makes sense to put some other functions in there too? As a minimal 
solution no, but it's nice to know there's room for future expansion.


There's nothing OOP about this at all - it's really just adapting and 
extending what standard Pascal does. You could extend it to include OOP 
if you really wanted to, but the minimal solution just moves the 
existing Haskell access functions to another scope, and adds a 
pre-curried version in a further scope, associating those scopes with 
the record type and record instances respectively.



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


Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution

2012-01-29 Thread Steve Horne

On 28/01/2012 13:00, Paul R wrote:

AntC>  Steve, I think that proposal has been rather superseeded by
AntC>  http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields, 
which
AntC>  draws on TDNR. But SORF is best seen as an evolving design space, with 
precise
AntC>  details yet to be clarified/agreed. I've put my own variation into the 
ring:
AntC>  http://www.haskell.org/pipermail/glasgow-haskell-users/2011-
AntC>  December/021298.html -- which seems to have fallen into a black hole 
:-(

AntC>  One of the aspects of TDNR that wasn't so popular was that its 
type-directed
AntC>  resolution was very similar to instance resolution, but subtly and 
confusingly
AntC>  different.

AntC>  I guess we have to be very careful about the dot. It seems to be in a
AntC>  very 'crowded' syntax space, so if we implement the wrong way, we could 
end up
AntC>  shutting the door with the keys left inside.

AntC>  (...)

All this dot syntax magic frankly frightens me. Haskell, as a pure
functionnal language, requires (and allows !) a programming style that
just does not mix well with object oriented practices. Stretching the
syntax to have the dot feel a-bit-but-not-really like object oriented
programming, mainly to have IDE autocompletion on some cases, does not
make much sens.
That's a benefit of my idea. Modular programming used the dot long 
before OOP became popular - OOP stole the dot from modular programming! 
If a record is a module, that only means that one thing can be both a 
module and a type (or value) at the same time. It takes little from OOP 
that OOP didn't already take from the more fundamental modular 
programming - and Haskell already has modules.



If the editor matters - and it probably does -, we could rather take
a more ambitious path, and work on a real semantic editor, as opposed to
a plain left-to-right text editor, with hacked semantic goodies to
alleviate the pain.
Every programmer has their own favorite editor, usually using the same 
one to work in many different languages. For the moment, you'd have a 
hard job separating me from Notepad++.


If you really want a "semantic editor", I'd argue a rich visual language 
with a file format that isn't intended to be read directly. Something 
more like writing in Word than writing in TeX. But I don't think most 
programmers are ready for this, for various reasons. Version control 
tools and readable differences get a place near the top of that list.



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


Re: [Haskell-cafe] space leak when repeatedly calling Control.Monad.State.Strict.modify

2012-01-29 Thread Joey Hess
Claude Heiland-Allen wrote:
> Control.Monad.State.Strict is strict in the actions, but the state
> itself is still lazy, so you end up building a huge thunk in the
> state containing all the updates that ever took place to the initial
> state.
> 
> Using this should fix it:
> 
> modify' :: MonadState s m => (s -> s) -> m ()
> modify' f = do
>   x <- get
>   put $! f x  -- force the new state when storing it

Thanks! 

So, why does Control.Monad.State.Strict.modify not do that?

And, I still don't quite understand why this only happened
when the updated value is obtained using IO.

-- 
see shy jo


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


Re: [Haskell-cafe] space leak when repeatedly calling Control.Monad.State.Strict.modify

2012-01-29 Thread Claude Heiland-Allen

Hi,

On 30/01/12 01:07, Joey Hess wrote:

The attached test case quickly chews up hundreds of MB of memory.
If modified to call work' instead, it runs in constant space.

Somehow the value repeatedly read in from the file and stored in
the state is leaking. Can anyone help me understand why?


Control.Monad.State.Strict is strict in the actions, but the state 
itself is still lazy, so you end up building a huge thunk in the state 
containing all the updates that ever took place to the initial state.


Using this should fix it:

modify' :: MonadState s m => (s -> s) -> m ()
modify' f = do
  x <- get
  put $! f x  -- force the new state when storing it

With the attached code, the first case (using modify) prints out a trace 
like:


test
work:1
modify
work:2
modify
work:3
modify
work:4
modify
work:5
modify
work:6
modify
work:7
modify
work:8
modify
work:9
modify
work:10
modify
update:vnbz
update:dzgd
update:hzla
update:nudd
update:bzfl
update:muht
update:hims
update:jakj
update:lvrt
update:qdxo
initial
MyState {val = "vnbz"}

Notice how the state updates are only evaluated right at the end, when 
the value is forced - note also that this means that all the data needs 
to hang around until then.


The second case (using modify') forces the state as it goes along:

test'
work:1
modify'
update:zwre
initial
work:2
modify'
update:fefg
work:3
modify'
update:eoqa
work:4
modify'
update:xtak
work:5
modify'
update:tekd
work:6
modify'
update:qrsz
work:7
modify'
update:fdgj
work:8
modify'
update:alwj
work:9
modify'
update:kqsp
work:10
modify'
update:lazz
MyState {val = "lazz"}



Claude
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Main where

import Debug.Trace
import System.Random

import Control.Monad.State.Strict

modify' :: MonadState s m => (s -> s) -> m ()
modify' f = do
  x <- get
  put $! f x

data MyState = MyState { val :: String } deriving Show

newtype Foo a = Foo { run :: StateT MyState IO a }
	deriving (
		Monad,
		MonadState MyState,
		MonadIO
	)

main :: IO ()
main = do
  print =<< execStateT (run test) (trace "initial" $ MyState "")
  print =<< execStateT (run test') (trace "initial" $ MyState "")
	
test :: Foo ()
test = trace "test" $ mapM_ work [1..10]-- massive memory leak

test' :: Foo ()
test' = trace "test'" $ mapM_ work' [1..10]

work :: Integer -> Foo ()
work n = trace ("work:"++show n) $ do
  v <- readSomeFile
  trace "modify" modify $ trace ("update:"++v) (\s -> s { val = v })

work' :: Integer -> Foo ()
work' n = trace ("work:"++show n) $ do
  v <- readSomeFile
  trace "modify'" modify' $ trace ("update:"++v) (\s -> s { val = v })

readSomeFile :: Foo String
readSomeFile = liftIO $ replicateM 4 (randomRIO ('a', 'z'))
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] space leak when repeatedly calling Control.Monad.State.Strict.modify

2012-01-29 Thread Joey Hess
The attached test case quickly chews up hundreds of MB of memory.
If modified to call work' instead, it runs in constant space.

Somehow the value repeatedly read in from the file and stored in
the state is leaking. Can anyone help me understand why?

(ghc 7.0.4)

-- 
see shy jo
{-# LANGUAGE GeneralizedNewtypeDeriving, BangPatterns #-}

module Main where

import Control.Monad.State.Strict

data MyState = MyState { val :: String }

newtype Foo a = Foo { run :: StateT MyState IO a }
	deriving (
		Monad,
		MonadState MyState,
		MonadIO
	)

main :: IO ()
main = evalStateT (run test) (MyState "")
	
test :: Foo ()
test = mapM_ work [1..10]-- massive memory leak
--test = mapM_ work' [1..10] -- constant space

readSomeFile :: Foo String
readSomeFile = liftIO $ readFileStrict "/etc/passwd"

work :: Integer -> Foo ()
work _ = do
	v <- readSomeFile
	modify $ \s -> s { val = v }

work' :: Integer -> Foo ()
work' n = do
	_ <- readSomeFile
	modify $ \s -> s { val = show n }

readFileStrict :: FilePath -> IO String
readFileStrict file = do
	s <- readFile file
	length s `seq` return s


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


Re: [Haskell-cafe] strict version of Haskell - does it exist?

2012-01-29 Thread Marc Weber
Excerpts from Don Stewart's message of Sun Jan 29 22:55:08 +0100 2012:
> Summary; -fstrict wouldn't magically make your code good.
No. you're right. I don't expect that to happen. I agree on it being
always the programmers fault using wrong tools or not knowing the tools
well enough to get a job done.

The PHP code looks like this:

foreach(glob('*.txt') as $file){
  foreach(split(file_get_contents($file)) => $line){
$parsed_line = json_decode($line);
// get some unix timestamps, keep some hashes of seen clients
// (cookie ids) and such
// check how many minutes before a checkout the customer visited
// the site - and whether he did so for a couple of days.
  }
}

// print result

The files are about 300 MB in size. However memory usage grew and grew
and grew - I had to kill it or limit amount of files.
The PHP code runs in a couple of seconds (parsing json and loading
files).. the Haskell app took much longer. That PHP is fast is no
surprise: I expect json_decode and split to be implemented in C.

So yes - I used lazy lists. However 8GB of RAM should have been enough
to keep things in RAM. So maybe also the JSON parsing library kept too
many unevaluated things in memory. So I could start either writing my
own JSON parsing library (being more strict) or profile the application
many times - but I don't want to.
Ignoring the json parsing I also gave conduits a try - only counting
lines. I know its experimental - but from its description I concluded it
would prevent me being a stupid Haskell programmer from taking too much
memory even using bad Haskell code.
However it looked like splitting the lines only counting them (recognizing
utf-8 chars) took a lot longer than also doing the json parsing in PHP.
Then the conduit implementation looked funny: hGetLine is used to feed
a line each time ... (luckily - because the utf8-libraries don't provide
nice ways to parse incomplete chunks of utf-8 bytes such as returning
Either IncompleteMissingByte UTF8Chunk)..

Probably the split(,"\n") in PHP doesn't parse utf-8 chars - and luckily
it doesn't seem to matter because \n only uses one byte.

I know that I'm not an Haskell expert. I still got the impression that
getting nice performance would be a small challenge and require much
more time than I spend on the PHP version.

That's why I'm wondering why there is no -fstrict option for such simple
use cases because Haskell has so many optimizations other languages
dream about.

I mean lot's of "non lazy" language still get their jobs done. So it
always depends on the use case.

Isn't it easy to add a compiler flag to GHC adding those ! strictness 
annotations
everywhere possible? Then simple use case like this would not be a huge
challenge.

Maybe you're right: I should just prepare some dummy files and ask the
community to help. However optimizing the JSON parser and my code just
seemed to be too much effort ..

Marc Weber

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


Re: [Haskell-cafe] strict version of Haskell - does it exist?

2012-01-29 Thread Austin Seipp
The strict-ghc-plugin (under my maintenance) is just a continuation of
one of the original demos Max had for plugin support in the compiler.
The idea is fairly simple: 'let' and 'case' are the forms for creating
lazy/strict bindings in Core. It just systematically replaces all
occurrences of 'let' in Core with 'case'. So 'let b = e1 in e2'
becomes 'case e1 of { b -> e2 }', making 'b' strict. It also replaces
all applications of the form 'App e1 e2' (which is also lazy, as e2 is
evaluated on demand) with an equivalent binding like 'case e2 of { x
-> App e1 x }'. Pretty simple, and results in a totally strict
program.

The idea is just a proof of concept; in particular, I (and likely Max
although I cannot speak for him) am not using it as a position to say
that sometimes you want everything strict. You don't; at some point,
you're not even using Haskell anymore I suppose (remember: non-strict
semantics.) I can't think of any instance in which I would need or
want to use this plugin, honestly. But maybe someone else would - I
did refactor it to where you can strictify individual functions, as
opposed to full-blown modules, via annotations. So you could
selectively strictify things if you found it beneficial on certain
identifiers. But then there's the question of what affect that has on
the rest of GHC's optimizers, which I cant answer: the strictifier
modifies the pipeline to be the *first* pass, and the remaining ones
run afterwords. Compilers are built on heuristics and built for
'average' code. Sometimes these heuristics interact in odd ways,
especially with code that may deviate from 'the norm.' Once you're
fighting the optimizer, it can become a very difficult battle to win.
Careful analysis and selective optimization is probably going to take
you farther than hitting it with a giant hammer.

Having lazy and strict data structures and knowing when/where to use
them is crucial for good performance, and both have their merits (same
with every other thing under the sun, like by-ref/by-val semantics in
`data` types, which you can control with UNPACK etc.) I think we could
most certainly use better tools for analyzing low-level performance
details and the tradeoff between strictness/laziness and (especially
in large codebases,) but I don't think systematically making
everything strict is going to be the right idea in a vast majority of
situations.

On Sun, Jan 29, 2012 at 4:12 PM, Chris Wong
 wrote:
> On Mon, Jan 30, 2012 at 10:13 AM, Marc Weber  wrote:
>> A lot of work has been gone into GHC and its libraries.
>> However for some use cases C is still preferred, for obvious speed
>> reasons - because optimizing an Haskell application can take much time.
>
> As much as any other high-level language, I guess. Don't compare
> apples to oranges and complain oranges aren't crunchy enough ;)
>
>> Is there any document describing why there is no ghc --strict flag
>> making all code strict by default?
>
> Yes -- it's called the Haskell Report :)
>
> GHC does a lot of optimization already. If making something strict
> won't change how it behaves, it will, using a process called
> strictness analysis.
>
> The reason why there is no --strict flag is that strictness isn't just
> something you turn on and off willy-nilly: it changes how the whole
> language works. Structures such as infinite lists and Don Stewart's
> lazy bytestrings *depend* on laziness for their performance.
>
>> Wouldn't this make it easier to apply Haskell to some additional fields
>> such as video processing etc?
>>
>> Wouldn't such a '--strict' flag turn Haskell/GHC into a better C/gcc
>> compiler?
>
> See above.
>
>> Projects like this: https://github.com/thoughtpolice/strict-ghc-plugin
>> show that the idea is not new.
>
> Not sure what that does, but I'll have a look at it.
>
>> Eg some time ago I had to do some logfile analysis. I ended doing it in
>> PHP because optimizing the Haskell code took too much time.
>
> That probably because you're using linked lists for strings. For
> intensive text processing, it's better to use the text package instead
> [1]
>
> Chris
>
> [1] http://hackage.haskell.org/package/text
>
>> Marc Weber
>>
>> ___
>> 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



-- 
Regards,
Austin

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


Re: [Haskell-cafe] ANN: combinatorics

2012-01-29 Thread wren ng thornton

On 1/29/12 5:48 AM, Roman Cheplyaka wrote:

* wren ng thornton  [2012-01-28 23:06:08-0500]

* Math.Combinatorics.Primes: provides the prime numbers via
Runciman's lazy wheel sieve algorithm. Provided here since efficient
algorithms for combinatorial functions often require prime numbers.
The current version memoizes the primes as an infinite list CAF,
which could lead to memory leaks in long-running programs with
irregular access to large primes. I'm looking into a GHC patch to
allow resetting individual CAFs from within compiled programs so that
you can explicitly decide when to un-memoize the primes. (In GHCi
when you reload a module all the CAFs are reset. However, there's no
way to access this feature from within compiled programs as yet.)


Why not to make it more pure? That is, return a lazy list of Ints (but
not a CAF), which user can throw away by the usual GC means?

The functions from the other modules that use primes would have to be
put in a Reader monad. That would make it a little bit more awkward to
use, but personally I'd prefer that over memory leaks.


I'd also prefer a more pure solution, but I don't think that the Reader 
monad is the right tool here. I played around with that approach, but it 
requires extremely invasive changes to client code, obfuscating what 
should be simple mathematical formulae. And, it's too fragile, exposing 
the implementation in a way that breaks client code should I change a 
non-prime-using algorithm to a prime-using one, or vice versa. The 
fragility could be partially avoided by providing both prime-using and 
non-prime-using algorithms, but then that forces users to decide which 
one they want--- and if their only concern is performance, then they'd 
have to go through the code-breaking refactoring anyways, just to 
determine which is faster for their application.


One alternative I'm exploring is, rather than (only) making the primes 
not a CAF, instead make the prime-using functions non-CAFs as well. That 
is, provide a makePrimeUsingFunctions function which returns a 
record/tuple of all the functions, sharing a stream of primes. This way, 
after allocating the functions, they can be used purely just as in the 
current model; and when the client wants the primes to be GCed, they can 
drop their references to the allocated functions which use those primes 
(allocating new functions later, if necessary).


I've used that pattern before for similar resource issues, and it worked 
nicely. But how well it works depends a lot on the structure of the 
program needing those resources. In particular it can lead to needing to 
use the Reader monad (or similar) in order to pass around the functions, 
even though the functions themselves can be used purely. Unfortunately I 
don't have any large combinatorial programs on hand to assess whether 
this would be problematic in practice or not.


--
Live well,
~wren

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


Re: [Haskell-cafe] strict version of Haskell - does it exist?

2012-01-29 Thread Ertugrul Söylemez
Marc Weber  wrote:

> A lot of work has been gone into GHC and its libraries.
> However for some use cases C is still preferred, for obvious speed
> reasons - because optimizing an Haskell application can take much
> time.
>
> Is there any document describing why there is no ghc --strict flag
> making all code strict by default?
> Wouldn't this make it easier to apply Haskell to some additional
> fields such as video processing etc?
>
> Wouldn't such a '--strict' flag turn Haskell/GHC into a better C/gcc
> compiler?
>
> Projects like this: https://github.com/thoughtpolice/strict-ghc-plugin
> show that the idea is not new.
>
> Eg some time ago I had to do some logfile analysis. I ended doing it
> in PHP because optimizing the Haskell code took too much time.

First of all, /learning/ to optimize Haskell can be difficult.  The
optimizing itself is actually fairly easy in my experience, once you
understand how the language works.

Usually the nonstrictness is no bottleneck.  However, you have to know
that you are in a nonstrict language.  In fact, I find myself having
difficulties writing efficient code in a strict language.

Now to answer your question:  A strict-by-default Haskell comes with the
implication that you can throw away most of the libraries, including the
base library.  So yes, a strict-by-default Haskell is very well
possible, but the question is whether you actually want that.  I
wouldn't, because a lot of my code relies on the standard semantics.  I
would also expect problems with the way Haskell performs I/O, because it
would mean that

forever (putStrLn "Hello world")

would cause a heap overflow, if Haskell were strict.  Note that we don't
have control structures.  We have combinators, and their nonstrictness
is essential.  The flag you are proposing would turn Haskell into a
language that is different enough that you couldn't do many useful
things with it.

If you want to save the time to learn how to write efficient Haskell
programs, you may want to have a look into the Disciple language.  You
will find that it has a different type system, which captures side
effects explicitly to make a pure strict language even possible.


Greets,
Ertugrul

-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/


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


Re: [Haskell-cafe] strict version of Haskell - does it exist?

2012-01-29 Thread Chris Wong
On Mon, Jan 30, 2012 at 10:13 AM, Marc Weber  wrote:
> A lot of work has been gone into GHC and its libraries.
> However for some use cases C is still preferred, for obvious speed
> reasons - because optimizing an Haskell application can take much time.

As much as any other high-level language, I guess. Don't compare
apples to oranges and complain oranges aren't crunchy enough ;)

> Is there any document describing why there is no ghc --strict flag
> making all code strict by default?

Yes -- it's called the Haskell Report :)

GHC does a lot of optimization already. If making something strict
won't change how it behaves, it will, using a process called
strictness analysis.

The reason why there is no --strict flag is that strictness isn't just
something you turn on and off willy-nilly: it changes how the whole
language works. Structures such as infinite lists and Don Stewart's
lazy bytestrings *depend* on laziness for their performance.

> Wouldn't this make it easier to apply Haskell to some additional fields
> such as video processing etc?
>
> Wouldn't such a '--strict' flag turn Haskell/GHC into a better C/gcc
> compiler?

See above.

> Projects like this: https://github.com/thoughtpolice/strict-ghc-plugin
> show that the idea is not new.

Not sure what that does, but I'll have a look at it.

> Eg some time ago I had to do some logfile analysis. I ended doing it in
> PHP because optimizing the Haskell code took too much time.

That probably because you're using linked lists for strings. For
intensive text processing, it's better to use the text package instead
[1]

Chris

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

> Marc Weber
>
> ___
> 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] ANN: bytestring-lexing 0.3.0

2012-01-29 Thread wren ng thornton

On 1/29/12 3:43 AM, Erik de Castro Lopo wrote:

Would you consider a function with the following signature in
bytestring-lexing?

 readDecimalX :: Integral a =>  ByteString ->  a

The idea is that it gives something faster for applications like Warp
where reading an valid decimal should be as fast as possible, but if
the string isn't valid it doesn't really matter what the result is.


If I can figure out a way to do so without too much code duplication I 
will. Another option would be to use the trick that's used by the pack* 
functions which causes the initial checks to be inlined ---and hence 
easily optimized away when used with fst.fromMaybe(0,"")--- without 
inlining the whole thing.


I'll keep you informed.

--
Live well,
~wren

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


Re: [Haskell-cafe] strict version of Haskell - does it exist?

2012-01-29 Thread Don Stewart
Generally strict Haskell means using strict data types - vectors, arrays,
bytestrings, intmaps where required.

However, you usually don't want all code and data strict, all the time,
since laziness/on-demand eval is critical for deferring non-essential work.

Summary; -fstrict wouldn't magically make your code good. Using the right
balance of strict and lazy code, via the right choice of strict and lazy
types, however, often does.

Id be interested to know what choices were made in your log file case led
you into problems -- using something excessively lazy (like lazy lists) or
something excessively strict (like strict bytestrings) would both be
suboptimal for log analysis. A hybrid type like a lazy bytestring, would be
more appropriate.

On Sunday, January 29, 2012, Marc Weber  wrote:
> A lot of work has been gone into GHC and its libraries.
> However for some use cases C is still preferred, for obvious speed
> reasons - because optimizing an Haskell application can take much time.
>
> Is there any document describing why there is no ghc --strict flag
> making all code strict by default?
> Wouldn't this make it easier to apply Haskell to some additional fields
> such as video processing etc?
>
> Wouldn't such a '--strict' flag turn Haskell/GHC into a better C/gcc
> compiler?
>
> Projects like this: https://github.com/thoughtpolice/strict-ghc-plugin
> show that the idea is not new.
>
> Eg some time ago I had to do some logfile analysis. I ended doing it in
> PHP because optimizing the Haskell code took too much time.
>
> Marc Weber
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] strict version of Haskell - does it exist?

2012-01-29 Thread Marc Weber
A lot of work has been gone into GHC and its libraries.
However for some use cases C is still preferred, for obvious speed
reasons - because optimizing an Haskell application can take much time.

Is there any document describing why there is no ghc --strict flag
making all code strict by default?
Wouldn't this make it easier to apply Haskell to some additional fields
such as video processing etc?

Wouldn't such a '--strict' flag turn Haskell/GHC into a better C/gcc
compiler?

Projects like this: https://github.com/thoughtpolice/strict-ghc-plugin
show that the idea is not new.

Eg some time ago I had to do some logfile analysis. I ended doing it in
PHP because optimizing the Haskell code took too much time.

Marc Weber

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


Re: [Haskell-cafe] TCP Server

2012-01-29 Thread Michael Snoyman
On Sun, Jan 29, 2012 at 2:21 PM, Felipe Almeida Lessa
 wrote:
> On Sun, Jan 29, 2012 at 10:14 AM, Jean-Marie Gaillourdet
>  wrote:
>> But it does try to solve the problem, doesn't it? Obviously conduit is an 
>> alternative to the iteratee-like packages. Why else would Yesod replace 
>> enumerator by conduit? That is the reason why I added it into my list of 
>> iteratee-like packages.
>
> I'm sorry if I misunderstood your message. I read your e-mail as
> though you were saying that the choice between these libraries has
> only to do with your taste, and your taste will decide the other
> libraries with which yours may interoperate.  This may be true between
> iteratee, enumerator and iterIO (module some specific features of each
> one of them), but that's not true for pipes (since it doesn't handle
> IO at all right now) and conduit (since it has a different concept
> despite having the same goal).

In case anyone's looking for comparisons between conduit and
enumerator, I wrote up my most recent thoughts on Reddit[1].

Michael

[1] 
http://www.reddit.com/r/haskell/comments/p1iu0/exciting_changes_coming_to_conduit_02/

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


Re: [Haskell-cafe] Monad-control rant

2012-01-29 Thread Edward Z. Yang
Excerpts from Mikhail Vorozhtsov's message of Sun Jan 29 05:34:17 -0500 2012:
> You are trying to make bottoms a new null pointers. Sometimes it just 
> doesn't worth the effort (or depends on the interpreter you use). I want 
> to have the option to say: sorry, in this particular case (monad) I 
> don't distinguish `error` from non-termination, so `catch ⊥ h = ⊥`.

This is a longstanding complaint that Robert Harper has with lazy languages
(the "paucity of types" complaint.)

http://existentialtype.wordpress.com/2011/04/24/the-real-point-of-laziness/

There's not much I can say here, except that:

- There really is no difference: GHC can sometimes detect nontermination
  and will throw an exception (for example, the deadlocked exception), and

- The user will sometimes act as a termination checker, and ^C a program
  that is taking too long.

> I think it is one of the simplest layouts one can some up with. I'll try 
> to explain the motivation behind each inclusion.
> 
> ABORTS(μ) ⊆ RECOVERABLE_ZEROS(μ)

I'm sorry, I cannot understand the discussion below because you haven't
defined precisely what ABORTS means.  (See also below; I think it's
time to write something up.)

> Why are they not equal? After all we can always write `recover weird $ 
> \e → abort e`, right? But zeros from `RECOVERABLE_ZEROES \ ABORTS` may 
> have additional effects. For example, recoverable interruptions could 
> permanently disable blocking operations (you can close a socket but you 
> can't read/write from it). Why the inclusion is not the other way 
> around? Well, I find the possibility of `abort e1` and `abort e2` having 
> different semantics (vs `recover` or `finally`) terrifying. If you can 
> throw unrecoverable exceptions, you should have a different function for 
> that.
> 
> RECOVERABLE_ZEROS(μ) ⊆ FINALIZABLE_ZEROS(μ)
> 
> If a zero is recoverable, we can always "finalize" it (by 
> catch-and-rethrow).
>
> FINALIZABLE_ZEROS(μ) ⊆ ZEROS(μ)
> 
> This one is pretty obvious. One example of non-finalizable zeros is 
> bottoms in a non-MonadUnbottom monad (e.g. my X monad). Another would be 
> `System.Posix.Process.exitImmediately`.

Ugh, don't talk to me about the exit() syscall ;-)

> > If we can unify the semantics in a sensible way, I have no objection
> > (the choice of exceptions or pure values is merely an implementation
> > detail.)  But it's not obvious that this is the case, especially when
> > you want to vary the semantics in interesting ways.
> That's why I'm trying to make things like MonadUnbottom optional.

Well, I haven't actually checked if this works or not!

> >  - If the semantics are different, OK, now you need to write two catch
> >functions, but you are handling each type of exception separately
> >already, right?
> You have to handle IO exceptions only if you "leak" them from your 
> implementation. For transformer stacks it is always so, for some 
> interpreters it is not. The `ErrorT e IO` problem is related to another 
> can of worms: operation lifting through transformers.

OK.

> > IO has effects, so if I have mplus (effect>>  mzero) a, this equals
> > effect>>  a, not a.  Same applies for MaybeT IO.  I have to be very
> > careful to preserve the monoid property.  STM, on the other hand,
> > by definition has the ability to rollback. This is what makes it so nice!
> Should STM/`MaybeT IO` have MonadException instances? How `catch` and 
> `finally` will interact with `retry`/`MaybeT (return Nothing)`?

I don't see why not, as long as they obey the semantics.  But someone
should do the legwork here.

> >>> I also think that unrecoverable/recoverable exceptions is a legitimate 
> >>> idea.  I
> >>> think it could get its own typeclass, let's call it
> >>> MonadUnrecoverableException.  I don't think any MonadException is 
> >>> automatically
> >>> a MonadUnrecoverableException, by appealing to the laws of MonadException.
> >> I'm confused. What methods/laws would MonadUnrecoverableException contain?
> >
> > They'd be very simple! Unrecoverable exceptions always cause program 
> > execution
> > to "get stuck." There are no contexts (like catch) which affect them.
> So you are suggesting something like
> 
> class MonadUnrecoverableException μ where
>throwUnrecoverable ∷ Exception e ⇒ e → μ α
> 
> But I'm not interested in throwing such exceptions! It may not even be 
> possible (allowed) to do that from within the monad itself (e.g. 
> external interruptions in my X monad). All I care about is that 
> unrecoverable zeros (not necessarily tied with Exception) exist, which 
> means that I cannot implement `finally` on top of `catch`.

Yes, but in that case, your semantics would have to change to add a case
for finally; you'd need to unwind the stack, etc etc.  You're talking about
finalizable, but unrecoverable exceptions.

> > Yes, I think for some this is the crux of the issue. Indeed, it is why
> > monad-control is so appealing, it dangles in front of us the 

Re: [Haskell-cafe] TCP Server

2012-01-29 Thread Felipe Almeida Lessa
On Sun, Jan 29, 2012 at 10:14 AM, Jean-Marie Gaillourdet
 wrote:
> But it does try to solve the problem, doesn't it? Obviously conduit is an 
> alternative to the iteratee-like packages. Why else would Yesod replace 
> enumerator by conduit? That is the reason why I added it into my list of 
> iteratee-like packages.

I'm sorry if I misunderstood your message. I read your e-mail as
though you were saying that the choice between these libraries has
only to do with your taste, and your taste will decide the other
libraries with which yours may interoperate.  This may be true between
iteratee, enumerator and iterIO (module some specific features of each
one of them), but that's not true for pipes (since it doesn't handle
IO at all right now) and conduit (since it has a different concept
despite having the same goal).

Cheers, =)

-- 
Felipe.

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


Re: [Haskell-cafe] TCP Server

2012-01-29 Thread Jean-Marie Gaillourdet

On 28.01.2012, at 12:56, Felipe Almeida Lessa wrote:
> I find it funny that conduit is said to be an iteratee library since
> it has no iteratees!  We've had more than one iteratee library since
> at least 1.5 years with the iteratee (Mar 2009) and enumerator (Aug
> 2010) packages, and AFAIK now we have four iteratee libraries: those
> two, iterIO (May 2011) and pipes (Jan 2012).  However, conduit is not
> the fifth since it has no iteratees, no enumerators, no enumeratees...
> it's a different concept, not a different implementation.

But it does try to solve the problem, doesn't it? Obviously conduit is an 
alternative to the iteratee-like packages. Why else would Yesod replace 
enumerator by conduit? That is the reason why I added it into my list of 
iteratee-like packages.


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


Re: [Haskell-cafe] ANN: pointless fun

2012-01-29 Thread wren ng thornton

On 1/29/12 12:03 AM, Joachim Breitner wrote:

Maybe you mean:

 foo:: A ->  B ->  C

 albert :: X ->  A
 beth   :: Y ->  B
 carol  :: C ->  Z

 bar :: X ->  Y ->  Z
 bar = foo $:: albert ~>  beth ~>  carol


Er, yes, of course. Silly me. Fixing the documentation now.

--
Live well,
~wren

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


Re: [Haskell-cafe] ANN: combinatorics

2012-01-29 Thread Roman Cheplyaka
* wren ng thornton  [2012-01-28 23:06:08-0500]
> * Math.Combinatorics.Primes: provides the prime numbers via
> Runciman's lazy wheel sieve algorithm. Provided here since efficient
> algorithms for combinatorial functions often require prime numbers.
> The current version memoizes the primes as an infinite list CAF,
> which could lead to memory leaks in long-running programs with
> irregular access to large primes. I'm looking into a GHC patch to
> allow resetting individual CAFs from within compiled programs so that
> you can explicitly decide when to un-memoize the primes. (In GHCi
> when you reload a module all the CAFs are reset. However, there's no
> way to access this feature from within compiled programs as yet.)

Why not to make it more pure? That is, return a lazy list of Ints (but
not a CAF), which user can throw away by the usual GC means?

The functions from the other modules that use primes would have to be
put in a Reader monad. That would make it a little bit more awkward to
use, but personally I'd prefer that over memory leaks.

-- 
Roman I. Cheplyaka :: http://ro-che.info/

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


Re: [Haskell-cafe] Monad-control rant

2012-01-29 Thread Mikhail Vorozhtsov

On 01/24/2012 10:56 PM, Edward Z. Yang wrote:

Excerpts from Mikhail Vorozhtsov's message of Tue Jan 24 07:26:35 -0500 2012:

Sure, but note that evaluate for IO is implemented with seq# under the hood,
so as long as you actually get ordering in your monad it's fairly 
straightforward
to implement evaluate.  (Remember that the ability to /catch/ an error
thrown by evaluate is separate from the ability to /evaluate/ a thunk which
might throw an error.)

Yes, of course. The purpose of MonadUnbottom is to guarantee that
`Control.Exception.throw e ∷ μ α = abort (toException e)`. The choice of
a class method is somewhat arbitrary here (one could go with 'α → μ
(Either SomeException α)` or with no methods at all).


I want to highlight the strangeness of "exception-like" monads that don't have
a MonadUnbottom instance (for concreteness, let's assume that there are no
methods associated with it.  What would you expect this code to do?

 catch (throw (UserError "Foo")) (putStrLn "caught")>>  putStrLn "ignored 
result"

If we don't have ordering, the monad is permitted to entirely ignore the thrown
exception. (In fact, you can see this with the lazy state monad, so long as you
don't force the state value.) Just like in lazy IO, exceptions can move around
to places you don't expect them.
You are trying to make bottoms a new null pointers. Sometimes it just 
doesn't worth the effort (or depends on the interpreter you use). I want 
to have the option to say: sorry, in this particular case (monad) I 
don't distinguish `error` from non-termination, so `catch ⊥ h = ⊥`.


[snip]

Stepping back for a moment, I think the conversation here would be helped if we
dropped loaded terms like "general" and "precise" and talked about concrete
properties:

  - A typeclass has more/less laws (equivalently, the typeclass constrains
what else an object can do, outside of an instance),
  - A typeclass requires an instance to support more/less operations,
  - A typeclass can be implemented for more/less objects

One important point is that "general" is not necessarily "good".  For example,
imagine I have a monad typeclass that has the "referential transparency" law
(why are you using a monad?! Well, never mind that for now.)  Obviously, the IO
monad cannot be validly be an instance of this typeclass. But despite only
admitting instances for a subset of monads, being "less general", I think most
people who've bought into Haskell agree, referentially transparent code
is good code!  This is the essential tension of generality and specificity:
if it's too general, "anything goes", but if it's too specific, it lacks 
elegance.

So, there is a definitive and tangible difference between "all bottoms are 
recoverable"
and "some bottoms are recoverable."  The former corresponds to an extra law
along the lines of "I can always catch exceptions."  This makes reduces the
number of objects the typeclass can be implemented for (or, if you may,
it reduces the number of admissible implementations for the typeclass), but
I would like to defend this as good, much like referential transparency
is a good restriction.

OK, what MonadUnrecoverableException exactly do you have in mind?


I don't know, I've never needed one! :^)


I was thinking about something like (no asynchronous exceptions for now):

-- ABORTS(μ) ⊆ RECOVERABLE_ZEROS(μ) ⊆ FINALIZABLE_ZEROS(μ) ⊆ ZEROS(μ)


Do you have a motivation behind this division?  Are there non-finalizable
but recoverable zeros? Why can't I use aborts to throw non-recoverable
or non-finalizable zeros? Maybe there should be a hierarchy of recoverability,
since I might have a top-level controller which can "kill and spawn" processes?
Maybe we actually want a lattice structure?
I think it is one of the simplest layouts one can some up with. I'll try 
to explain the motivation behind each inclusion.


ABORTS(μ) ⊆ RECOVERABLE_ZEROS(μ)

Why are they not equal? After all we can always write `recover weird $ 
\e → abort e`, right? But zeros from `RECOVERABLE_ZEROES \ ABORTS` may 
have additional effects. For example, recoverable interruptions could 
permanently disable blocking operations (you can close a socket but you 
can't read/write from it). Why the inclusion is not the other way 
around? Well, I find the possibility of `abort e1` and `abort e2` having 
different semantics (vs `recover` or `finally`) terrifying. If you can 
throw unrecoverable exceptions, you should have a different function for 
that.


RECOVERABLE_ZEROS(μ) ⊆ FINALIZABLE_ZEROS(μ)

If a zero is recoverable, we can always "finalize" it (by 
catch-and-rethrow).


FINALIZABLE_ZEROS(μ) ⊆ ZEROS(μ)

This one is pretty obvious. One example of non-finalizable zeros is 
bottoms in a non-MonadUnbottom monad (e.g. my X monad). Another would be 
`System.Posix.Process.exitImmediately`.



Someone has put a term for this problem before: it is an "embarassment of 
riches".
There is so much latitude of choice here that it's hard to know what the 

[Haskell-cafe] Reminder Munich Haskell Meeting

2012-01-29 Thread Heinrich Hördegen



Dear all,

just to remind you: Tomorrow, Monday 30. Jan 2012,  Haskellers meet in 
Munich. Check out the details and click the button, if you plan to join:


http://www.haskell-munich.de/dates

See you,
Heinrich

--
--

hoerde...@funktional.info
www.funktional.info

--


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


Re: [Haskell-cafe] ANN: bytestring-lexing 0.3.0

2012-01-29 Thread Erik de Castro Lopo
Wren,

I notice that readDecimal has a typesig:


readDecimal :: Integral a => ByteString -> Maybe (a, ByteString)

which I would then use in Warp as:

readInt64BSL :: ByteString -> Int64
readInt64BSL bs = fst $ fromMaybe (0, "") $ BSL.readDecimal bs

However, this version with the fromMaybe and fst is a little slower
than if these two extra bits weren't necessary.

Would you consider a function with the following signature in
bytestring-lexing?

readDecimalX :: Integral a => ByteString -> a

The idea is that it gives something faster for applications like Warp
where reading an valid decimal should be as fast as possible, but if
the string isn't valid it doesn't really matter what the result is.

Cheers,
Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/

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