Re: [Haskell-cafe] Re: programmatic DB interface?

2010-02-05 Thread Magnus Therning
On Fri, Feb 5, 2010 at 10:38, Johannes Waldmann
 wrote:
>
>> As I posted earlier, using 'T' to separate date and time is correct
>> ISO8601 according to wikipedia[1].
>
> So you're saying  "2009-12-20 16:55:57.297"
> (returned by the psql server) is wrong,
> and it should instead send "2009-12-20T16:55:57.297Z" ?

Well, it isn't necessarily *wrong* ;-)

"2009-12-20 16:55:57.297" is made up of two pieces, one for date and one
for time.

"2009-12-20T16:55:57.297Z" is made up of one piece, which specifies both
date and time.

This is why I believe that the function ISO8601DateFormat is correct when
it provides a format for a combined date and time.

> What would be the query to obtain this format?
>
> I don't see this mentioned anyplace on
> http://www.postgresql.org/docs/8.3/interactive/functions-datetime.html

Neither do I, I don't find anything relating to ISO8601 dates (they seem
more concerned with ISO DOW and year).

> Perhaps we take this back to haskell-cafe (or libraries?) as it might be
> of general interest.

Sure, why not.  It was most likely a mistake on my side to drop
haskell-cafe in the first place.

/M

-- 
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] safe lazy IO or Iteratee?

2010-02-05 Thread John Millikin
Benchmark attached. It just enumerates a list until EOF is reached.

An interesting thing I've noticed is that IterateeMCPS performs better
with no optimization, but -O2 gives IterateeM the advantage. Their
relative performance depends heavily on the chunk size -- for example,
CPS is much faster at chunk size 1, but slower with 100-element
chunks.

On Fri, Feb 5, 2010 at 08:56, John Lato  wrote:
> On Fri, Feb 5, 2010 at 4:31 PM, Valery V. Vorotyntsev
>  wrote:
>>> John Lato  wrote:
>>>
 Both designs appear to offer similar performance in aggregate,
 although there are differences for particular functions.  I haven't
 yet had a chance to test the performance of the CPS variant, although
 Oleg has indicated he expects it will be higher.
>>
>> @jwlato:
>> Do you mind creating `IterateeCPS' tree in
>> , so we can
>> start writing CPS performance testing code?
>
> I'm working on the CPS version and will make it public when it's done.
>  It may take a week or so; this term started at 90 and has picked up.
> I have several benchmark sources that aren't public yet, but I can put
> them online for your perusal.
>
>>
>> AFAICS, you have benchmarks for IterateeM-driven code already:
>> http://inmachina.net/~jwlato/haskell/iteratee/tests/benchmarks.hs
>
> Those will make more sense when I've added the context of the
> codebases in use.  There are several more sets of output that I simply
> haven't published yet, including bytestring-based variants.
>
>>
>> John Millikin  wrote:
>>
>>> I wrote some criterion benchmarks for IterateeM vs IterateeCPS, and
>>> the CPS version was notably slower. I don't understand enough about
>>> CPS to diagnose why, but the additional runtime was present in even
>>> simple cases (reading from a file, writing back out).
>
> That's very interesting.  I wonder if I'll see the same, and if I'd be
> able to figure it out myself...
>
> Did you benchmark any cases without doing IO?  Sometimes the cost of
> the IO can overwhelm any other measurable differences, and also disk
> caching can affect results.  Criterion should highlight any major
> outliers, but I still like to avoid IO when benchmarking unless
> strictly necessary.
>
>>
>> @jmillikin:
>> Could you please publish those benchmarks?
>
> +1
>
> John
>
-- Benchmark for Oleg Kiselyov's iteratees. You will need:
-- 
-- http://okmij.org/ftp/Haskell/Iteratee/LowLevelIO.hs
-- http://okmij.org/ftp/Haskell/Iteratee/IterateeM.hs
-- http://okmij.org/ftp/Haskell/Iteratee/IterateeMCPS.hs
-- 
-- 
-- ghc --make -O2 benchmark.hs

import Criterion.Main
import Criterion.Config
import qualified IterateeM as M
import qualified IterateeMCPS as CPS
import qualified Control.Monad.Identity as I

config = defaultConfig { cfgPerformGC = ljust True }

enumM :: Monad m => Int -> Int -> M.IterV Int m a -> M.Iteratee Int m a
enumM n = M.enum_pure_nchunk [0..n]

enumCPS :: Monad m => Int -> Int -> CPS.Iteratee Int m a -> m (CPS.Iteratee Int m a)
enumCPS n = CPS.enum_pure_nchunk [0..n]

runM :: (M.IterV el I.Identity () -> M.Iteratee el' I.Identity a) -> a
runM enum = I.runIdentity . M.run $ M.skip_till_eof M.>>== enum

runCPS :: Monad m => (CPS.Iteratee el m () -> CPS.Iteratee el' I.Identity a) -> a
runCPS enum = I.runIdentity . CPS.run $ enum CPS.skip_till_eof

main :: IO ()
main = defaultMainWith config (return ())
	[ bgroup "IterateeM"
		[ bench "100/10" $ whnf runM $ enumM 100 10
		, bench "200/10" $ whnf runM $ enumM 200 10
		, bench "300/10" $ whnf runM $ enumM 300 10
		]
	, bgroup "IterateeCPS"
		[ bench "100/10" $ whnf runCPS $ enumCPS 100 10
		, bench "200/10" $ whnf runCPS $ enumCPS 200 10
		, bench "300/10" $ whnf runCPS $ enumCPS 300 10
		]
	]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] cabal fun (not)

2010-02-05 Thread Ivan Miljenovic
On 6 February 2010 01:05, Johannes Waldmann
 wrote:
> so please please please have "cabal install" fail with some error
> message if (that is, before) the install would break anything. - J.

If you upgrade a library, it will break all other libraries that
depend upon it.  "ghc-pkg list" will tell you which libraries are
broken and need to be rebuilt.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
Joan Crawford  - "I, Joan Crawford, I believe in the dollar.
Everything I earn, I spend." -
http://www.brainyquote.com/quotes/authors/j/joan_crawford.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] a beginner question: decorate-op-undecorate

2010-02-05 Thread Aran Donohue
Thanks for the helpful thoughts.

I guess I was just reaching for a Haskell version of a programming pattern
from other languages---dealing with baggage if you will.

Thanks,
Aran

On Fri, Feb 5, 2010 at 7:24 PM, Luke Palmer  wrote:

> On Fri, Feb 5, 2010 at 10:34 AM, Aran Donohue 
> wrote:
> > What would be an idiomatic Haskell way to accomplish this? Currently I've
> > got "liftedPartitionEithers :: [a] -> (a -> Either b c) -> ([a],
> [a])" which
> > is my own version of partitionEithers that calls a selector first.
>
> Since you are not using b or c anywhere else, the only thing you care
> about in that Either is whether it is Left or Right.  Which makes it
> seem much more like a Bool.  After this conversion, I can hoogle for
> your signature.
>
>
> http://haskell.org/hoogle/?hoogle=[a]+-%3E+%28a+-%3E+Bool%29+-%3E+%28[a]%2C[a]%29
>
> Which gives, among other things, Data.List.partition :: (a -> Bool) ->
> [a] -> ([a],[a]).
>
> Without more details about the precise thing you want to accomplish, I
> don't know what else to say.  Many idioms are about the details of the
> problem, even down to argument order.
>
> Luke
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] a beginner question: decorate-op-undecorate

2010-02-05 Thread Brandon S. Allbery KF8NH

On Feb 5, 2010, at 19:13 , Brandon S. Allbery KF8NH wrote:

Hm.  Does it make sense to make this a Functor?

> instance Functor Binding where
>   fmap f (Binding v e) = Binding v (f e)



Inaccurate/incomplete as written, since Functor expects kind (*) and  
Binding is (* -> *).  You'd have to fix v to declare instances.


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




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


Re: [Haskell-cafe] a beginner question: decorate-op-undecorate

2010-02-05 Thread Luke Palmer
On Fri, Feb 5, 2010 at 10:34 AM, Aran Donohue  wrote:
> What would be an idiomatic Haskell way to accomplish this? Currently I've
> got "liftedPartitionEithers :: [a] -> (a -> Either b c) -> ([a], [a])" which
> is my own version of partitionEithers that calls a selector first.

Since you are not using b or c anywhere else, the only thing you care
about in that Either is whether it is Left or Right.  Which makes it
seem much more like a Bool.  After this conversion, I can hoogle for
your signature.

http://haskell.org/hoogle/?hoogle=[a]+-%3E+%28a+-%3E+Bool%29+-%3E+%28[a]%2C[a]%29

Which gives, among other things, Data.List.partition :: (a -> Bool) ->
[a] -> ([a],[a]).

Without more details about the precise thing you want to accomplish, I
don't know what else to say.  Many idioms are about the details of the
problem, even down to argument order.

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


Re: [Haskell-cafe] Re: sendfile leaking descriptors on Linux?

2010-02-05 Thread Brandon S. Allbery KF8NH

On Feb 5, 2010, at 02:56 , Bardur Arantsson wrote:
I should have posted this earlier, but the exact message I'm seeing  
in the case where the Bad Client disconnects is this:


  hums: Network.Socket.SendFile.Linux: resource vanished (Broken pipe)

Oddly, I haven't been able to reproduce this using a wget client  
with a ^C during transfer. When I "disconnect" wget with ^C or  
"pkill wget" or even "pkill -9 wget", I get this message:


 hums: Network.Socket.SendFile.Linux: resource vanished (Connection  
reset by peer)


(and no leak, as observed by "lsof | grep hums").



"Broken pipe" is normally handled as a signal, and is only mapped to  
an error if SIGPIPE is set to SIG_IGN.  I can well imagine that the  
SIGPIPE signal handler isn't closing resources properly; a workaround  
would be to use the System.Posix.Signals API to ignore SIGPIPE, but I  
don't know if that would work as a general solution (it would depend  
on what other uses of pipes/sockets exist).


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




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


Re: [Haskell-cafe] a beginner question: decorate-op-undecorate

2010-02-05 Thread Brandon S. Allbery KF8NH

On Feb 5, 2010, at 12:34 , Aran Donohue wrote:

data Binding = Binding Var (Either Value [Value])

representing a variable bound either to a fixed value or that has a  
list of possible values.


I'd like to perform an operation on say, the fixed-value members of  
a list of bindings. Data.Either has "partitionEithers"---I'd  
essentially like to use partitionEithers, but in a way that it  
"peeks" into the value field of the binding. For the sake of  
argument, let's say I can't or can't modify Binding to move the  
Either to the outside.


What would be an idiomatic Haskell way to accomplish this? Currently  
I've got "liftedPartitionEithers :: [a] -> (a -> Either b c) ->  
([a], [a])" which is my own version of partitionEithers that calls a  
selector first. Another option would be to map each Binding to a new  
datatype that has the Either on the outside, use partitionEithers,  
and map back.



Hm.  Does it make sense to make this a Functor?

> instance Functor Binding where
>   fmap f (Binding v e) = Binding v (f e)

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




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


Re: [Haskell-cafe] Re: Trapping getChar before echo

2010-02-05 Thread Judah Jacobson
On Fri, Feb 5, 2010 at 10:41 AM, Andrew Coppin
 wrote:
> Tim Attwood wrote:
>>>
>>> Last time I tried something like this [on Windows], it didn't seem to
>>> work. I wanted to trap arrow keys and so forth, but they seem to be being
>>> used for input history. (I.e., pressing the up-arrow produces
>>> previously-entered lines of text, and none of this appears to be reaching
>>> the Haskell program itself.) Has this changed since I tried it last year?
>>
>> Doesn't work in windows, at least up till 6.10.1. There's a work-around
>> though.
>>
>> {-# LANGUAGE ForeignFunctionInterface #-}
>>
>> import Data.Char
>> import Control.Monad (liftM, forever)
>> import Foreign.C.Types
>>
>> getHiddenChar = liftM (chr.fromEnum) c_getch
>> foreign import ccall unsafe "conio.h getch"
>>  c_getch :: IO CInt
>>
>> main = do
>>  forever $ do
>>     c <- getHiddenChar
>>     putStrLn $ show (fromEnum c)
>
> Thanks for the info.
>
> Does anyone know how this is related to the "haskeline" package on Hackage?

The haskeline package provides a readline-like library for reading in
a line of input with arrow keys, tab completion, etc.  It works on
both Windows and unix platforms.  Documentation and a full list of
features can be found at http://trac.haskell.org/haskeline/ .

On Windows, haskeline gets all user input by calling Win32 API
functions such as ReadConsoleInputW:

http://msdn.microsoft.com/en-us/library/ms684961%28VS.85%29.aspx

That function returns an INPUT_RECORD struct with information about
key press events (among others); those includes simple characters,
arrow keys, page up/down, etc.  AFAIK that's the only way to get at
such events in the Windows console; there's no effective analogue to
the unix setting, where e.g. pressing the up key causes stdin to
receive the ANSI key sequence "\ESC[A".

The source code of haskeline has examples of how to import and use
those API functions:
http://code.haskell.org/haskeline/System/Console/Haskeline/Backend/Win32.hsc

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


Re: [Haskell-cafe] Re: Generating repeatable arbitrary values with QuickCheck 2

2010-02-05 Thread David Menendez
On Fri, Feb 5, 2010 at 3:39 PM, Ryan Ingram  wrote:
> On Fri, Feb 5, 2010 at 5:19 AM, Martijn van Steenbergen
>  wrote:
>> Ryan Ingram wrote:
>>>
>>> Unfortunately, this makes things like

  infinite_xs <- sequence (repeat arbitrary)
>>>
>>> no longer work, since the state never comes out the other side.
>>
>> You're asking to execute an infinite number of monadic actions. How can this
>> ever terminate at all?
>
> Stefan already gave an example, but to explain slightly further --
>
> There's nothing "magical" about monadic actions.  It's just another
> function call.
>
> In the case of QuickCheck, Gen is a reader monad with a "broken" >>=
> that changes the state of the generator passed to each side:

Incidentally, the alternative Gen I suggested also works for infinite
lists. (It's equivalent to StateT StdGen (Reader Int), using the
StateT from Control.Monad.State.Lazy.)

The problem, as Ryan pointed out, is that you can't access the state
after the infinite computation, so you can't create two infinite
streams or an infinite tree, which the current definition of Gen
allows.

More concretely, this works fine:

stream = do
x <- arbitrary
xs <- stream
return (x:xs)

but you can't call arbitrary after you call stream

broken = do
xs <- stream
y <- arbitrary  -- can't evaluate until stream is fully evaluated
(i.e., never)

The present definition of Gen avoids this by splitting the StdGen at
every >>=, but that creates the situation where two expressions which
should be equivalent produce different results in some contexts.

It isn't clear to me which implementation is best. I lean towards the
StateT-like implementation, on the theory that it's limitations are
easier to explain, but I guess it comes down to whether we want to
make life easier for (a) people creating infinite structures or (b)
people who need reproducible results.

-- 
Dave Menendez 

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


Re: [Haskell-cafe] Anyone up for Google SoC 2010?

2010-02-05 Thread Malcolm Wallace

If the goal is to have "more source code [..] created
and released for the use and benefit of all", how does my project fail
to achieve this?


Also, it is worth pointing out that from Google's point of view, they  
are most interested in whether the programme yields students who stick  
around and continue to contribute to open source projects.


I think Niklas and his HSE library very visibly pass on both criteria  
- quality code that is actively used, and a continuing contribution.


Regards,
Malcolm

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


Re: [Haskell-cafe] Anyone up for Google SoC 2010?

2010-02-05 Thread Niklas Broberg
> There may be an eternal discussion on it, but it seems pretty clear to
> me which side SoC comes down on: http://code.google.com/soc/

I'm really not sure what you're getting at. How do the points you list
not relate to my project? And how does my analogy contradict any of
those points? If the goal is to have "more source code [..] created
and released for the use and benefit of all", how does my project fail
to achieve this?

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


Re: [Haskell-cafe] Anyone up for Google SoC 2010?

2010-02-05 Thread Gwern Branwen
On Fri, Feb 5, 2010 at 3:38 PM, Niklas Broberg  wrote:
> I'm at a loss as to what criteria is actually used to judge success
> here. It seems to me a bit like the eternal discussion between "basic
> research" and "applied research". Just because something
> (research/library/project) doesn't have an immediate, palpable impact
> and/or delivers a visible tool, that certainly doesn't imply that it
> doesn't have merit or won't have as profound an impact on the domain,
> if more diffuse than a tool (or other palpable deliverable) would.
>
> /Niklas

There may be an eternal discussion on it, but it seems pretty clear to
me which side SoC comes down on: http://code.google.com/soc/

"Through Google Summer of Code, accepted student applicants are paired
with a mentor or mentors from the participating projects, thus gaining
exposure to real-world software development scenarios and the
opportunity for employment in areas related to their academic
pursuits. In turn, the participating projects are able to more easily
identify and bring in new developers. Best of all, more source code is
created and released for the use and benefit of all."

or http://socghop.appspot.com/document/show/program/google/gsoc2009/faqs#goals

# Google Summer of Code has several goals:

* Get more open source code created and released for the benefit of all
* Inspire young developers to begin participating in open source development
* Help open source projects identify and bring in new developers
and committers
* Provide students the opportunity to do work related to their
academic pursuits during the summer (think "flip bits, not burgers")
* Give students more exposure to real-world software development
scenarios (e.g., distributed development, software licensing
questions, mailing-list etiquette)

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


Re: [Haskell-cafe] Re: Generating repeatable arbitrary values with QuickCheck 2

2010-02-05 Thread Ryan Ingram
On Fri, Feb 5, 2010 at 5:19 AM, Martijn van Steenbergen
 wrote:
> Ryan Ingram wrote:
>>
>> Unfortunately, this makes things like
>>>
>>>  infinite_xs <- sequence (repeat arbitrary)
>>
>> no longer work, since the state never comes out the other side.
>
> You're asking to execute an infinite number of monadic actions. How can this
> ever terminate at all?

Stefan already gave an example, but to explain slightly further --

There's nothing "magical" about monadic actions.  It's just another
function call.

In the case of QuickCheck, Gen is a reader monad with a "broken" >>=
that changes the state of the generator passed to each side:

> newtype Gen a = Gen (Int -> StdGen -> a)
> generate n g (Gen f) = f n g
>
> return x = Gen (\_ _ -> x)
> m >>= f = Gen mbindf where
>mbindf n g = b where
>(g1,g2) = split g
>a = generate n g1 m
>b = generate n g2 (f a)

Now, to see how this generates data for an infinite list, just consider
>  sequence [arbitrary, ...
which we can represent as
>  sequence (arbitrary:undefined)

Recall the definition of sequence:

> sequence [] = return []
> sequence (a:as) = do
>x <- a
>xs <- sequence as
>return (x:xs)

If we are ever required to evaluate the rest of the list, we'll get
undefined and computation will fail.  The goal is to get something out
of the computation without needing to do so; if that works, then it
will work for (arbitrary:arbitrary:undefined) and so on up to an
infinite list of actions.  Let's try it!

generate 42 g $ sequence (aribtrary : undefined)

= generate 42 sg $ do
x <- arbitrary
xs <- sequence undefined
return (x:xs)

= generate 42 sg (
 arbitrary >>= \x -> sequence undefined >>= \xs -> return (x:xs)
   )

= let
m = arbitrary
f = \x -> sequence undefined >>= \xs -> return (x:xs)
mbindf n g = b where
(g1,g2) = split g
a = generate n g m
b = generate n g (f a)
  in
 generate 42 sg (Gen mbindf)

= let ... in mbindf 42 sg

= let
m = arbitrary
f = \x -> sequence undefined >>= \xs -> return (x:xs)
n = 42
g = sg
(g1,g2) = split g
a = generate n g1 m
b = generate n g2 (f a)
  in b

= let ... in generate n g2 (f a)
= let ... in generate n g2 (sequence undefined >>= \xs -> return (a:xs)

= let
m = arbitrary
n = 42
g = sg
(g1,g2) = split g
a = generate n g1 m

m1 = sequence undefined
f = \xs -> return (a:xs)
mbindf n1 g3 = b where
(g4,g5) = split g3
a1 = generate n1 g4 m1
b = generate n1 g5 (f a1)
  in generate n g2 (Gen mbindf)
= let ... in mbindf n g2

= let
m = arbitrary
n = 42
g = sg
(g1,g2) = split g
a = generate n g1 m

m1 = sequence undefined
f = \xs -> return (a:xs)
(g4,g5) = split g2
a1 = generate n g4 m1
b = generate n g5 (f a1)
  in generate n g5 (f a1)

= let ... in generate n g5 (return (a:a1))
= let ... in generate n g5 (Gen (\_ _ -> (a:a1)))
= let ... in (\_ _ -> (a:a1)) n g5
= let ... in (a:a1)
= let ... in (generate n g1 m : a1)
= let ... in (generate n g1 arbitrary : a1)
= let ... in ( : a1)

We have now output a cons cell with an arbitrary value without even
evaluating the rest of the input to sequence (which is undefined;
could have been 'repeat aribtrary' or anything else)

Lazy evaluation is pretty neat :)

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


Re: [Haskell-cafe] Anyone up for Google SoC 2010?

2010-02-05 Thread Niklas Broberg
On Fri, Feb 5, 2010 at 8:55 PM, Edward Kmett  wrote:
> You can add me to the list of voices that were unwilling to use it before
> the summer-of-code project due to the random incompatibilities caused by the
> huge supply of extensions it supported out of the box, but who were happy to
> switch to it after the changes were made to make them configurable.

This was indeed the main priority of the project, and the reason why
even I would not have recommended anyone to use haskell-src-exts in
production before the project.

> The rest is just gravy that happens to permit a number of applications such
> as refactoring browsers that were impossible with the previous
> implementation. And, as I recall, the fairly radical exploratory "pretty
> print . parse = id" goal was explicitly listed merely as a secondary goal on
> the original application.

Indeed it was, and I am not aware of any major applications that
actually use the exact-print functionality yet (please, tell me if you
have one!). I do know of several that make very good use of the new
Annotated syntax tree, though, which was introduced as a step towards
exact-printing. The benefits of that, together with the configurable
extensions, is more than enough to now make me happily recommend
haskell-src-exts to anyone working with Haskell source code in any
application. The rest is, as you accurately put it, just gravy.

I must admit I'm a bit sad to have the value of my project questioned
in this way, a project that I myself was more than pleased with, both
with the actual work achieved and the significant positive feedback I
have received after its conclusion. If haskell-src-exts was indeed
popular even before the project, that's all well and good to me. But
it doesn't mean that the library offered to the users then was
satisfactory, nor does it mean that the project failed to deliver
something that those same users needed and/or could make good use of.
Even if the number of direct users did not rise dramatically as a
consequence of the project, why would it not be valid use of a project
slot to greatly improve a library that was already popular? Browsing
the numbers [1] posted by Don Stewart in September last year (the
Haskell Symposium figures, which is the latest I could find) suggests
a substantial increase of downloads of the package both before, during
and after the project, but I can only speculate why. And since the
project concluded late August, figures for September and onwards would
have been more telling.

I'm at a loss as to what criteria is actually used to judge success
here. It seems to me a bit like the eternal discussion between "basic
research" and "applied research". Just because something
(research/library/project) doesn't have an immediate, palpable impact
and/or delivers a visible tool, that certainly doesn't imply that it
doesn't have merit or won't have as profound an impact on the domain,
if more diffuse than a tool (or other palpable deliverable) would.

/Niklas

[1] http://www.galois.com/~dons/hackage/september-2009/total-downloads.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] online Real World Haskell - tool used?

2010-02-05 Thread Bryan O'Sullivan
On Thu, Feb 4, 2010 at 7:51 PM, Sophie  wrote:

>
> I believe the online Real World Haskell book with commenting system was
> generated with an open-source tool (written by one of the authors?). Any
> idea where I might find this?


See http://bitbucket.org/bos/hgbook for the code.


> I am also curious what authoring tools were used to write the book.


DocBook, emacs, and vi.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: could we get a Data instance for Data.Text.Text?

2010-02-05 Thread Bryan O'Sullivan
On Fri, Feb 5, 2010 at 9:33 AM, Jeremy Shaw  wrote:

> I have attached a new version that should work with GHC 6.10, though I have
> not tested it.
>

Thanks. I fixed the compilation warning, added a Data instance for lazy
Text, and released 0.7.1.0.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Anyone up for Google SoC 2010?

2010-02-05 Thread Edward Kmett
You can add me to the list of voices that were unwilling to use it before
the summer-of-code project due to the random incompatibilities caused by the
huge supply of extensions it supported out of the box, but who were happy to
switch to it after the changes were made to make them configurable.

That said, I don't support a major public application.

But keep in mind haskell-src-exts is used by almost every quasiquoter that
wants antiquotation, so the improvements in mere compatibility with Haskell
98 as a baseline have had fairly wide-reaching impact, affecting almost
every one of those 23 (or 57 depending how you count) dependencies on the
haskell-src-exts library. One might argue that that well exceeds your 3 or 4
feature user guideline. =)

The rest is just gravy that happens to permit a number of applications such
as refactoring browsers that were impossible with the previous
implementation. And, as I recall, the fairly radical exploratory "pretty
print . parse = id" goal was explicitly listed merely as a secondary goal on
the original application.

It seems hardly appropriate to judge the impact of the entire SoC effort on
the impact of that secondary exploratory component.

-Edward Kmett

On Fri, Feb 5, 2010 at 12:48 PM, Gwern Branwen  wrote:

> On Fri, Feb 5, 2010 at 6:20 AM, Sittampalam, Ganesh
>  wrote:
> > Gwern Branwen wrote:
> >> On Wed, Feb 3, 2010 at 8:14 PM, Henk-Jan van Tuyl 
> >> wrote:
> >>> On Wed, 03 Feb 2010 23:34:34 +0100, Neil Mitchell
> >>> 
> >>> wrote:
> >>>
>  Hi Gwern,
> 
>  Please update: "haskell-src-exts -> haskell-src" **Unknown**
> 
>  This project was an unqualified success.  haskell-src-exts is now
>  one
>  of the most commonly used Haskell libraries, achieved the goals in
>  the project proposal, and is an essential piece of Haskell
>  infrastructure.
> >>>
> >>> You can see this using Roel van Dijk's reversed dependencies
> >>> overview [1]: 23 direct and 57 indirect dependencies on
> >>> haskell-src-exts-1.8.0
> >>>
> >>> Regards,
> >>> Henk-Jan van Tuyl
> >>
> >> And how many of those used haskell-src-exts *before* the SoC project?
> >> And would have used it regardless? You can't point to a popular
> >> project which got a SoC student, and say look at how popular it is -
> >> obviously the SoC student was hugely successful.
> >
> > Regardless of that, is there any reason to disregard Neil's summary and
> not update your page?
> >
> > Ganesh
>
> I prefer to wait. haskell-src-exts was popular before, it was popular
> after. The question is not whether the patches were applied, or
> whether the mentor told Google it was successful, but whether it was
> the best possible use of the SoC slot. If features do not get used,
> then it wasn't a good SoC. If you know 3 or 4 uses of the new
> haskell-src-exts features in (relatively) major applications like
> hlint, then I'll concede the point and mark it a success.
>
> --
> gwern
> ___
> 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] Simulation of interconnect network

2010-02-05 Thread Roger King
I am building a simulator for an interconnect network for a multiprocessor 
computer.  I would like to develop it in Haskell as an opportunity to learn 
Haskell.

The network will have a number of routers with input ports and output ports and 
crossbars between them.  I would like to simulate the protocol.  This would be 
an event driven simulator.  It would be at a high level, leaving out many 
details.  I would like it to be fast and be able to run it on several 
processors.

I would like to know if you have any advice.  Has anyone done this before?  Are 
there any discrete event simulators written in Haskell?
R



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


[Haskell-cafe] Re: sendfile leaking descriptors on Linux?

2010-02-05 Thread Bardur Arantsson
I desperation, I've tried to instrument a couple of the functions in 
SendFile:


> sendFile'' :: Socket -> Handle -> Integer -> Integer -> IO ()
> sendFile'' outs inp off count =
> do let out_fd = Fd (fdSocket outs)
>in_fd <- handleToFd inp
>putStrLn ("in_fd=" ++ show in_fd)
>finally (wrapSendFile' _sendFile out_fd in_fd off count)
>(do
>  putStrLn ("SENDFILE DONE " ++ show in_fd)
>)
>
> sendFile' :: Socket -> FilePath -> Integer -> Integer -> IO ()
> sendFile' outs infp offset count =
> bracket
>(openBinaryFile infp ReadMode)
>(\h -> do
>  putStrLn "CLOSING FILE!"
>  hClose h
>  putStrLn "FILE CLOSED!")
>(\inp -> sendFile'' outs inp offset count)

(Yes, this made me feel dirty.)

Here's the resulting output from around when the file descriptor gets lost:

---
Serving file 'X'...
Sending 674465792 bytes... 

in_fd=7 

SENDFILE DONE 7 

CLOSING FILE! 

FILE CLOSED! 

hums: Network.Socket.SendFile.Linux: resource vanished (Broken pipe) 

Got request for CONTENT for objectId=1700,f2150400 


Serving file 'X'...
Sending 672892928 bytes... 

in_fd=7 

SENDFILE DONE 7 

CLOSING FILE! 

FILE CLOSED! 

hums: Network.Socket.SendFile.Linux: resource vanished (Broken pipe) 

Got request for CONTENT for objectId=1700,f2150400 


Serving file 'X'...
Sending 670140416 bytes... 

in_fd=7 



<*- What happened here?

Got request for CONTENT for objectId=1700,f2150400 


Serving file 'X'...
Sending 667256832 bytes... 

in_fd=9 

SENDFILE DONE 9 

CLOSING FILE! 

FILE CLOSED! 

hums: Network.Socket.SendFile.Linux: resource vanished (Broken pipe) 

Got request for CONTENT for objectId=1700,f2150400 


Serving file 'X'...
Sending 665028608 bytes... 

in_fd=9 

SENDFILE DONE 9 

CLOSING FILE! 

FILE CLOSED! 

hums: Network.Socket.SendFile.Linux: resource vanished (Broken pipe) 

Got request for CONTENT for objectId=1700,f2150400 


Serving file 'X'...
---


Anyone got any clues as to what might cause the behavior show at the mark?

The only idea I have is that *something* in the SendFile library kills 
the thread completely (or somehow evades "finally"), but I have no idea 
what it might be.


Cheers,

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


Re: [Haskell-cafe] GUI programming

2010-02-05 Thread Mario Blažević

Victor Nazarov wrote:

Hello,

I've been writing some GUI application with Gtk2hs. It's an
interpreter for lambda-calculus and combinatory logic, it's GPL and if
you interested I can share it with cafe.

The problem is that the GUI code has become very ugly and I'm tempted
to rewrite it totally. I've been looking forward to the FRP stuff, but
I've never seen a single definition of the term. Conal Eliot's
"denotational programming" is too general to be definition. I want to
try Grapefruit, but I got totally lost when I see arrow notation.

I consider more lightweight and more imperative approach, something
closer to CSP (Communicating Secuential Processes) then FRP. I've just
crafted some sample program to illustrate my idea.

The behaviour is a monad and it's IO monad so you can do any IO
(Gtk2hs) programming you wish. The differences is that you don't
attach static event handlers and tries to determine what to do
dependent on application state. You attach and detach handlers as much
as possible. Behaviour looks like a process that can stop execution
and wait for some GUI event. When event arrived it continues
execution.


	To summarize, the behaviour is a suspendable IO computation. It looks 
very much like a coroutine, in fact. I'm planning to extract the 
Control.Concurrent.Coroutine module [1] into a separate package soon. It 
implements a similar concept but generalized to transform any monad and 
any functorial suspension.


[1] 
http://hackage.haskell.org/packages/archive/scc/0.4/doc/html/Control-Concurrent-Coroutine.html




Do you see this approach viable. There are steel some details to emerge:
* How to wait for several events
* How to handle IO exceptions


	I don't really know how applicable the idea is to GUI programming. 
That's not my area of expertise. I am surprised, though, that neither 
your code not your comments seem to address the issue of concurrency, as 
I expect that would be crucial in a GUI setting. Wouldn't you need 
different behaviours to run in different threads?




Here is the code:
{-# LANGUAGE ExistentialQuantification #-}
...



	I don't see the purpose of your BBind constructor. It seems to me that 
you could simply move the first three cases of runBehaviour 
implementation into your >>= and get rid of the constructor. Do you 
need that much laziness?




import Data.IORef
import System.Glib
import Graphics.UI.Gtk
import Control.Monad.Trans

type Event obj = IO () -> IO (ConnectId obj)

data Behaviour a =
  forall b. BBind (Behaviour b) (b -> Behaviour a)
  | BIO (IO a)
  | forall obj. GObjectClass obj => BWaitEvent (Event obj) (Behaviour a)

instance Monad Behaviour
 where action >>= generator = BBind action generator
   return a = BIO (return a)

instance MonadIO Behaviour
 where liftIO action = BIO action

runBehaviour :: Behaviour a -> IO a
runBehaviour (BBind (BWaitEvent event after) f) = runBehaviour
(BWaitEvent event (after >>= f))
runBehaviour (BBind (BIO a) f) = a >>= \x -> runBehaviour (f x)
runBehaviour (BBind (BBind a f) g) = runBehaviour (a >>= (\x -> f x >>= g))
runBehaviour (BIO a) = a
runBehaviour (BWaitEvent event after) =
 do sigIdRef <- newIORef (error "You can't access sigIdRef before
signal is connected")
sigId <- event $
  do sigId <- readIORef sigIdRef
 signalDisconnect sigId
 runBehaviour after
 return ()
writeIORef sigIdRef sigId
return (error "You can't expect result from behaviour")

waitEvent :: GObjectClass obj => Event obj -> Behaviour ()
waitEvent event = BWaitEvent event (return ())

main :: IO ()
main =
  do initGUI
 window <- windowNew
 onDestroy window mainQuit
 set window [windowTitle := "Hello World"]
 button <- buttonNew
 let buttonB label =
   do liftIO $ set button [buttonLabel := label]
  waitEvent (onClicked button)
  buttonB (label ++ "*")
 runBehaviour (buttonB "*")
 set window [containerChild := button]
 widgetShowAll window
 mainGUI






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



--
Mario Blazevic
mblaze...@stilo.com
Stilo International

This message, including any attachments, is for the sole use of the
intended recipient(s) and may contain confidential and privileged
information. Any unauthorized review, use, disclosure, copying, or
distribution is strictly prohibited. If you are not the intended
recipient(s) please contact the sender by reply email and destroy
all copies of the original message and any attachments.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Trapping getChar before echo

2010-02-05 Thread Andrew Coppin

Tim Attwood wrote:
Last time I tried something like this [on Windows], it didn't seem to 
work. I wanted to trap arrow keys and so forth, but they seem to be 
being used for input history. (I.e., pressing the up-arrow produces 
previously-entered lines of text, and none of this appears to be 
reaching the Haskell program itself.) Has this changed since I tried 
it last year?


Doesn't work in windows, at least up till 6.10.1. There's a 
work-around though.


{-# LANGUAGE ForeignFunctionInterface #-}

import Data.Char
import Control.Monad (liftM, forever)
import Foreign.C.Types

getHiddenChar = liftM (chr.fromEnum) c_getch
foreign import ccall unsafe "conio.h getch"
 c_getch :: IO CInt

main = do
  forever $ do
 c <- getHiddenChar
 putStrLn $ show (fromEnum c)


Thanks for the info.

Does anyone know how this is related to the "haskeline" package on Hackage?

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


[Haskell-cafe] Two GET HTTP requests

2010-02-05 Thread Chris Eidhof
Hi everyone,

I'm trying to do a number of successive HTTP requests in one program. Here's 
what I tried:

Approach 1: I used the 'download' package, which failed to install on OS X. It 
fails with "error: libio.h: No such file or directory".

Approach 2: I installed the 'download-curl' package, and tried again. This 
seems to fail on the following example:

> import Network.Curl.Download
> 
> main = do x <- openURI "http://haskell.org";
>   y <- openURI "http://haskell.org/hoogle";
>   return ()

If I put a print statement around the second line of the do-statement it looks 
like openURI never returns.

Approach 3: I used the simpleHTTP function from the HTTP package. This crashed, 
after I dug a little deeper into the code, it threw an error on calling the 
parseURI function (openFile: no such file exists). I installed the latest 
network package and upgraded my HTTP package, and the parseURI error went away. 
I felt like I was almost there, and tried the following:

> simpleHTTP (getRequest "http://haskell.org";)

This failed with just the text "Bus error". I searched the HTTPBis git 
repository, but couldn't find the text "Bus error". I don't have a clue of how 
to fix this.

I'm a bit stuck here, I would love to help fix the errors, but don't know what 
would be the best place to begin. If anyone can point me in the right 
direction, I will try to patch at least one of these packages.

Thanks,

-chris

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


Re: [Haskell-cafe] a beginner question: decorate-op-undecorate

2010-02-05 Thread Felipe Lessa
On Fri, Feb 05, 2010 at 12:34:01PM -0500, Aran Donohue wrote:
> Hi Haskell-Cafe,
>
> Consider a data type such as
>
> data Binding = Binding Var (Either Value [Value])
>
> representing a variable bound either to a fixed value or that has a list of
> possible values.
>
> I'd like to perform an operation on say, the fixed-value members of a list
> of bindings. Data.Either has "partitionEithers"---I'd essentially like to
> use partitionEithers, but in a way that it "peeks" into the value field of
> the binding. For the sake of argument, let's say I can't or can't modify
> Binding to move the Either to the outside.
>
> What would be an idiomatic Haskell way to accomplish this? Currently I've
> got "liftedPartitionEithers :: [a] -> (a -> Either b c) -> ([a], [a])" which
> is my own version of partitionEithers that calls a selector first. Another
> option would be to map each Binding to a new datatype that has the Either on
> the outside, use partitionEithers, and map back.
>
> Thanks,
> Aran

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

You could try using uniplate[1], something like

transformBi (either doWhatYouLike id)

I guess :).

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

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


Re: [Haskell-cafe] Anyone up for Google SoC 2010?

2010-02-05 Thread Gwern Branwen
On Fri, Feb 5, 2010 at 6:20 AM, Sittampalam, Ganesh
 wrote:
> Gwern Branwen wrote:
>> On Wed, Feb 3, 2010 at 8:14 PM, Henk-Jan van Tuyl 
>> wrote:
>>> On Wed, 03 Feb 2010 23:34:34 +0100, Neil Mitchell
>>> 
>>> wrote:
>>>
 Hi Gwern,

 Please update: "haskell-src-exts -> haskell-src" **Unknown**

 This project was an unqualified success.  haskell-src-exts is now
 one
 of the most commonly used Haskell libraries, achieved the goals in
 the project proposal, and is an essential piece of Haskell
 infrastructure.
>>>
>>> You can see this using Roel van Dijk's reversed dependencies
>>> overview [1]: 23 direct and 57 indirect dependencies on
>>> haskell-src-exts-1.8.0
>>>
>>> Regards,
>>> Henk-Jan van Tuyl
>>
>> And how many of those used haskell-src-exts *before* the SoC project?
>> And would have used it regardless? You can't point to a popular
>> project which got a SoC student, and say look at how popular it is -
>> obviously the SoC student was hugely successful.
>
> Regardless of that, is there any reason to disregard Neil's summary and not 
> update your page?
>
> Ganesh

I prefer to wait. haskell-src-exts was popular before, it was popular
after. The question is not whether the patches were applied, or
whether the mentor told Google it was successful, but whether it was
the best possible use of the SoC slot. If features do not get used,
then it wasn't a good SoC. If you know 3 or 4 uses of the new
haskell-src-exts features in (relatively) major applications like
hlint, then I'll concede the point and mark it a success.

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


[Haskell-cafe] a beginner question: decorate-op-undecorate

2010-02-05 Thread Aran Donohue
Hi Haskell-Cafe,

Consider a data type such as

data Binding = Binding Var (Either Value [Value])

representing a variable bound either to a fixed value or that has a list of
possible values.

I'd like to perform an operation on say, the fixed-value members of a list
of bindings. Data.Either has "partitionEithers"---I'd essentially like to
use partitionEithers, but in a way that it "peeks" into the value field of
the binding. For the sake of argument, let's say I can't or can't modify
Binding to move the Either to the outside.

What would be an idiomatic Haskell way to accomplish this? Currently I've
got "liftedPartitionEithers :: [a] -> (a -> Either b c) -> ([a], [a])" which
is my own version of partitionEithers that calls a selector first. Another
option would be to map each Binding to a new datatype that has the Either on
the outside, use partitionEithers, and map back.

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


Re: [Haskell-cafe] Re: could we get a Data instance for Data.Text.Text?

2010-02-05 Thread Jeremy Shaw
Hello,

I have attached a new version that should work with GHC 6.10, though I have
not tested it.

The older Data.Data uses mkNorepType instead of mkNoRepType. I just changed
the patch to use the older spelling. In GHC >= 6.12 this will issue a
warning that the old spelling has been deprecated. This seems like a
reasonable fix as long as text drops support for GHC 6.10 before mkNorepType
is completely removed from Data.Data (which may never happen?):

Here is the bug:

http://hackage.haskell.org/trac/ghc/ticket/2760

Also, this patch still won't work with GHC < 6.10, is that ok?

I also noticed in the containers package, there are #ifdefs around the Data
instances:

#if __GLASGOW_HASKELL__
...
#endif

Should I add that as well? Or is text only supported under GHC anyway?

- jeremy

On Tue, Feb 2, 2010 at 12:03 AM, Bryan O'Sullivan wrote:

> On Mon, Feb 1, 2010 at 12:08 PM, Jeremy Shaw  wrote:
>
>> Attached.
>>
>
> Data/Text.hs:175:63:
> Module `Data.Data' does not export `mkNoRepType'
>
> Can you send a followup patch that works against GHC 6.10.4, please?
>


data-instance-for-text-2.dpatch
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: sendfile leaking descriptors on Linux?

2010-02-05 Thread Bardur Arantsson

Thomas Hartman wrote:

Do you have a test script to reproduce the behavior?



Unfortunately not, but the behavior *is* 100% reproducible with
my PS3 client. The production of a leaked FD appears to require a
particularly abrupt disconnect (see my other reply in this thread), so
you're probably safe in most cases.

Cheers,


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


Re: [Haskell-cafe] safe lazy IO or Iteratee?

2010-02-05 Thread John Lato
On Fri, Feb 5, 2010 at 4:31 PM, Valery V. Vorotyntsev
 wrote:
>> John Lato  wrote:
>>
>>> Both designs appear to offer similar performance in aggregate,
>>> although there are differences for particular functions.  I haven't
>>> yet had a chance to test the performance of the CPS variant, although
>>> Oleg has indicated he expects it will be higher.
>
> @jwlato:
> Do you mind creating `IterateeCPS' tree in
> , so we can
> start writing CPS performance testing code?

I'm working on the CPS version and will make it public when it's done.
 It may take a week or so; this term started at 90 and has picked up.
I have several benchmark sources that aren't public yet, but I can put
them online for your perusal.

>
> AFAICS, you have benchmarks for IterateeM-driven code already:
> http://inmachina.net/~jwlato/haskell/iteratee/tests/benchmarks.hs

Those will make more sense when I've added the context of the
codebases in use.  There are several more sets of output that I simply
haven't published yet, including bytestring-based variants.

>
> John Millikin  wrote:
>
>> I wrote some criterion benchmarks for IterateeM vs IterateeCPS, and
>> the CPS version was notably slower. I don't understand enough about
>> CPS to diagnose why, but the additional runtime was present in even
>> simple cases (reading from a file, writing back out).

That's very interesting.  I wonder if I'll see the same, and if I'd be
able to figure it out myself...

Did you benchmark any cases without doing IO?  Sometimes the cost of
the IO can overwhelm any other measurable differences, and also disk
caching can affect results.  Criterion should highlight any major
outliers, but I still like to avoid IO when benchmarking unless
strictly necessary.

>
> @jmillikin:
> Could you please publish those benchmarks?

+1

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


Re: [Haskell-cafe] Stack ADT?

2010-02-05 Thread michael rice
I see now that what I thought was happening wasn't happening at all.

> top (push 1 s1)  gives me the top of the new Stack returned by PUSH. s1 
> remains unchanged.

Thanks,

Michael


--- On Fri, 2/5/10, minh thu  wrote:

From: minh thu 
Subject: Re: [Haskell-cafe] Stack ADT?
To: "michael rice" 
Cc: haskell-cafe@haskell.org, "Casey Hawthorne" 
Date: Friday, February 5, 2010, 11:04 AM

2010/2/5 michael rice 
>
> Not using Stack for anything, just trying to understand how things can be 
> done in Haskell.
>
> To that end...
>
> What's going on here? I'm not even calling function POP.
>
> Michael
>
> ==
>
> module Data.Stack (Stack, emptyStack, isEmptyStack, push, pop, top) where
>
> newtype Stack a = Stack [a]
>
> emptyStack = Stack []
> isEmptyStack (Stack xs) = null xs
> push x (Stack xs) = Stack (x:xs)
> pop (Stack (_:xs)) = Stack xs
> top (Stack (x:_)) = x
>
> ==
>
> [mich...@localhost ~]$ ghci Stack.hs
> GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
> Loading package ghc-prim ... linking ... done.
> Loading package integer ... linking ... done.
> Loading package base ... linking ... done.
> [1 of 1] Compiling Data.Stack       ( Stack.hs, interpreted )
> Ok, modules loaded: Data.Stack.
> *Data.Stack> let s1 = emptyStack
> *Data.Stack> top (push 1 s1)
> 1
> *Data.Stack> top (push 2 s1)
> 2
> *Data.Stack> top (push 3 s1)
> 3
> *Data.Stack> let s2 = pop s1
> *Data.Stack> top s2
> *** Exception: Stack.hs:8:0-28: Non-exhaustive patterns in function pop

When you write
  push 1 s1
you get a new stack value. you can view it by typing 'it' in ghci
(provided you have an instance of Show for it).

s1 is still s1, the empty stack.

When you write
  let s2 = pop s1
Nothing happens yet, but if you want to evaluate s2, e.g. by typing it
in ghci, pop will be applied to the empty stack, which is not taken
care of in its definition.
And you do want evaluate s2 when you eventually write
  top s2.

HTH,
Thu



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


Re: [Haskell-cafe] safe lazy IO or Iteratee?

2010-02-05 Thread Valery V. Vorotyntsev
> John Lato  wrote:
>
>> Both designs appear to offer similar performance in aggregate,
>> although there are differences for particular functions.  I haven't
>> yet had a chance to test the performance of the CPS variant, although
>> Oleg has indicated he expects it will be higher.

@jwlato:
Do you mind creating `IterateeCPS' tree in
, so we can
start writing CPS performance testing code?

AFAICS, you have benchmarks for IterateeM-driven code already:
http://inmachina.net/~jwlato/haskell/iteratee/tests/benchmarks.hs


John Millikin  wrote:

> I wrote some criterion benchmarks for IterateeM vs IterateeCPS, and
> the CPS version was notably slower. I don't understand enough about
> CPS to diagnose why, but the additional runtime was present in even
> simple cases (reading from a file, writing back out).

@jmillikin:
Could you please publish those benchmarks?

Thanks.

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


Re: [Haskell-cafe] Stack ADT?

2010-02-05 Thread minh thu
2010/2/5 michael rice 
>
> Not using Stack for anything, just trying to understand how things can be 
> done in Haskell.
>
> To that end...
>
> What's going on here? I'm not even calling function POP.
>
> Michael
>
> ==
>
> module Data.Stack (Stack, emptyStack, isEmptyStack, push, pop, top) where
>
> newtype Stack a = Stack [a]
>
> emptyStack = Stack []
> isEmptyStack (Stack xs) = null xs
> push x (Stack xs) = Stack (x:xs)
> pop (Stack (_:xs)) = Stack xs
> top (Stack (x:_)) = x
>
> ==
>
> [mich...@localhost ~]$ ghci Stack.hs
> GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
> Loading package ghc-prim ... linking ... done.
> Loading package integer ... linking ... done.
> Loading package base ... linking ... done.
> [1 of 1] Compiling Data.Stack   ( Stack.hs, interpreted )
> Ok, modules loaded: Data.Stack.
> *Data.Stack> let s1 = emptyStack
> *Data.Stack> top (push 1 s1)
> 1
> *Data.Stack> top (push 2 s1)
> 2
> *Data.Stack> top (push 3 s1)
> 3
> *Data.Stack> let s2 = pop s1
> *Data.Stack> top s2
> *** Exception: Stack.hs:8:0-28: Non-exhaustive patterns in function pop

When you write
  push 1 s1
you get a new stack value. you can view it by typing 'it' in ghci
(provided you have an instance of Show for it).

s1 is still s1, the empty stack.

When you write
  let s2 = pop s1
Nothing happens yet, but if you want to evaluate s2, e.g. by typing it
in ghci, pop will be applied to the empty stack, which is not taken
care of in its definition.
And you do want evaluate s2 when you eventually write
  top s2.

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


Re: [Haskell-cafe] Stack ADT?

2010-02-05 Thread Rahul Kapoor
> What's going on here? I'm not even calling function POP.
> *Data.Stack> let s2 = pop s1
> *Data.Stack> top s2
> *** Exception: Stack.hs:8:0-28: Non-exhaustive patterns in function pop

Haskell being a non strict language, does not evaluate pop s1 when you define
let s2 = pop s1.
but when you try to use s2 by evaluating "top s2" "pop s1" needs to be evaluated
leading to the error in "pop", since the definition of pop, does not
deal with the case when
the Stack is empty (Stack []).

> pop (Stack (_:xs)) = Stack xs
> top (Stack (x:_)) = x
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Stack ADT?

2010-02-05 Thread Andrew Wagner
What's "going on" is that data structures in Haskell are immutable. Thus,
when you call "push" on a stack, you get a new stack with the new element
pushed onto it, and the original stack is left un-touched.

On Fri, Feb 5, 2010 at 10:56 AM, michael rice  wrote:

> Not using Stack for anything, just trying to understand how things can be
> done in Haskell.
>
> To that end...
>
> What's going on here? I'm not even calling function POP.
>
> Michael
>
> ==
>
> module Data.Stack (Stack, emptyStack, isEmptyStack, push, pop, top) where
>
> newtype Stack a = Stack [a]
>
> emptyStack = Stack []
> isEmptyStack (Stack xs) = null xs
> push x (Stack xs) = Stack (x:xs)
> pop (Stack (_:xs)) = Stack xs
> top (Stack (x:_)) = x
>
> ==
>
> [mich...@localhost ~]$ ghci Stack.hs
> GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
> Loading package ghc-prim ... linking ... done.
> Loading package integer ... linking ... done.
> Loading package base ... linking ... done.
> [1 of 1] Compiling Data.Stack   ( Stack.hs, interpreted )
> Ok, modules loaded: Data.Stack.
> *Data.Stack> let s1 = emptyStack
> *Data.Stack> top (push 1 s1)
> 1
> *Data.Stack> top (push 2 s1)
> 2
> *Data.Stack> top (push 3 s1)
> 3
> *Data.Stack> let s2 = pop s1
> *Data.Stack> top s2
> *** Exception: Stack.hs:8:0-28: Non-exhaustive patterns in function pop
>
> *Data.Stack>
>
>
>
>
> --- On *Fri, 2/5/10, Casey Hawthorne * wrote:
>
>
> From: Casey Hawthorne 
> Subject: Re: [Haskell-cafe] Stack ADT?
> To: haskell-cafe@haskell.org
> Date: Friday, February 5, 2010, 10:36 AM
>
> You could also implement stacks with mutable data structures, e.g.
> STArray, etc.
>
> What do you want to use a stack ADT for?
>
> Usually stacks are discussed for pedagogical purposes but usually
> recursion is used if you need a stack like operation.
> --
> Regards,
> Casey
> ___
> 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Stack ADT?

2010-02-05 Thread michael rice
Not using Stack for anything, just trying to understand how things can be done 
in Haskell.

To that end...

What's going on here? I'm not even calling function POP.

Michael

==

module Data.Stack (Stack, emptyStack, isEmptyStack, push, pop, top) where

newtype Stack a = Stack [a]

emptyStack = Stack []
isEmptyStack (Stack xs) = null xs
push x (Stack xs) = Stack (x:xs)
pop (Stack (_:xs)) = Stack xs
top (Stack (x:_)) = x

==

[mich...@localhost ~]$ ghci Stack.hs
GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Data.Stack   ( Stack.hs, interpreted )
Ok, modules loaded: Data.Stack.
*Data.Stack> let s1 = emptyStack
*Data.Stack> top (push 1 s1)
1
*Data.Stack> top (push 2 s1)
2
*Data.Stack> top (push 3 s1)
3
*Data.Stack> let s2 = pop s1 
*Data.Stack> top s2
*** Exception: Stack.hs:8:0-28: Non-exhaustive patterns in function pop

*Data.Stack> 




--- On Fri, 2/5/10, Casey Hawthorne  wrote:

From: Casey Hawthorne 
Subject: Re: [Haskell-cafe] Stack ADT?
To: haskell-cafe@haskell.org
Date: Friday, February 5, 2010, 10:36 AM

You could also implement stacks with mutable data structures, e.g.
STArray, etc.

What do you want to use a stack ADT for?

Usually stacks are discussed for pedagogical purposes but usually
recursion is used if you need a stack like operation.
--
Regards,
Casey
___
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] Stack ADT?

2010-02-05 Thread Colin Paul Adams
> "Casey" == Casey Hawthorne  writes:

Casey> You could also implement stacks with mutable data structures,
Casey> e.g.  STArray, etc.

Casey> What do you want to use a stack ADT for?

BTW, There is a Myers stack in Edison.
Disclaimer - I don't know what a Myers stack is.
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Stack ADT?

2010-02-05 Thread Casey Hawthorne
You could also implement stacks with mutable data structures, e.g.
STArray, etc.

What do you want to use a stack ADT for?

Usually stacks are discussed for pedagogical purposes but usually
recursion is used if you need a stack like operation.
--
Regards,
Casey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] safe lazy IO or Iteratee?

2010-02-05 Thread John Millikin
I didn't count the commented-out designs in Oleg's code, only those
which are "live".

> Both designs appear to offer similar performance in aggregate,
> although there are differences for particular functions.  I haven't
> yet had a chance to test the performance of the CPS variant, although
> Oleg has indicated he expects it will be higher.

I wrote some criterion benchmarks for IterateeM vs IterateeCPS, and
the CPS version was notably slower. I don't understand enough about
CPS to diagnose why, but the additional runtime was present in even
simple cases (reading from a file, writing back out).

On Fri, Feb 5, 2010 at 06:04, John Lato  wrote:
>> Subject: Re: [Haskell-cafe] safe lazy IO or Iteratee?
>>
>> Downside: iteratees are very hard to understand. I wrote a
>> decently-sized article about them trying to figure out how to make
>> them useful, and some comments in one of Oleg's implementations
>> suggest that the "iteratee" package is subtly wrong. Oleg has written
>> at least three versions (non-monadic, monadic, monadic CPS) and I've
>> no idea why or whether their differences are important. Even dons says
>> he didn't understand them until after writing his own iteratee-based
>> IO layer.
>
> More significant than, and orthogonal to, the differences between
> non-monadic and monadic are the two primary implementations Oleg has
> written.  They are[1]:
>
> Design 1:
> newtype Iteratee el m a = Iteratee{runIter:: Stream el -> m (IterV el m a)}
> data IterV el m a = IE_done a (Stream el)
>                  | IE_cont (Iteratee el m a) (Maybe ErrMsg)
>
> Design 2:
> newtype Iteratee el m a = Iteratee{runIter:: m (IterV el m a)}
> data IterV el m a = IE_done a (Stream el)
>                  | IE_cont (Stream el -> Iteratee el m a) (Maybe ErrMsg
>
> With the first design, it's impossible to get the state of an iteratee
> without feeding it a chunk.  There are other consequences too.  The
> second design seems to require some specialized combinators, that is
> (>>==) and ($$), which are not required for the first version.
> Neither situation is ideal.  The CPS version appears to remedy both
> flaws, but at the expense of introducing CPS at a low level (this can
> be hidden from the end user in many cases).  I already think of
> iteratees as holding continuations, so to me the so-called "CPS
> version" is to me a double CPS.
>
> Both designs appear to offer similar performance in aggregate,
> although there are differences for particular functions.  I haven't
> yet had a chance to test the performance of the CPS variant, although
> Oleg has indicated he expects it will be higher.
>
> The monadic/non-monadic issue is related.  Non-monadic iteratees are
> iteratees that can't perform monadic effects when they're running
> (although they can still be fed from a monadic enumerator).
> Essentially it's the difference between "fold" and "foldM".  They are
> simpler and more efficient because of this, but also much less
> powerful.  Any iteratee design can support both non-monadic and
> monadic, but *I* don't want to support both.  At least, I don't want
> to have double modules for everything for nearly identical functions,
> and polymorphic code that can handle non-monadic and monadic iteratees
> is non-trivial[2].
>
> Much of my recent work has been in the consequences of these various
> design considerations for the next version of the iteratee library.
> Currently undecided, although I'm leaning towards CPS.  It seems to
> solve a lot of problems, and the implementation details are generally
> cleaner too.
>
> Cheers,
> John
>
> [1] Both taken from
> http://okmij.org/ftp/Haskell/Iteratee/IterateeM.hs.  Design 1 is
> commented out on that page.
>
> [2] At least for me.  Maybe others can provide a better solution.
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: programmatic DB interface?

2010-02-05 Thread Johannes Waldmann
Colin Paul Adams wrote:

> Colin> It is just the code to generate the SQL for CREATE TABLE is
> Colin> presumably faulty. 

well this wouldn't help in my case since I did not CREATE TABLE
from haskelldb. In my application, the DB is given externally,
and I used Database.HaskellDB.DBDirect to create the  Haskell interface.

J.



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


Re: [Haskell-cafe] Re: programmatic DB interface?

2010-02-05 Thread Colin Paul Adams
> "Johannes" == Johannes Waldmann  writes:

>> That is exactly the problem - it is wrong for CalendarT.

Johannes> what do you mean by "it" ... what package should be fixed
Johannes> (old-locale, haskelldb-hdbc-postgreqsl, ...)?  Because
Johannes> obviously something seems broken here.

"It" is the use of unzoned times. I sent the following patch to the
haskelldb list several months ago. But there has not been a new release
since then.

Colin> It is just the code to generate the SQL for CREATE TABLE is
Colin> presumably faulty. For CalendarTimeT columns it should
Colin> generate a time of

Colin> timestamp with time zone

Colin> as CalendarTime is a zoned timestamp.

here's my patch:

--- Default.hs~ 2009-02-13 23:06:25.0 +
+++ Default.hs  2009-10-01 16:43:34.0 +0100
@@ -92,7 +92,7 @@
   IntegerT  -> SqlType "bigint"
   DoubleT   -> SqlType "double precision"
   BoolT -> SqlType "bit"
-  CalendarTimeT -> SqlType "timestamp"
+  CalendarTimeT -> SqlType "timestamp with time zone"
   BStrT a   -> SqlType1 "varchar" a
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] cabal fun (not)

2010-02-05 Thread Johannes Waldmann
while trying to live with different versions of packages,
I found cabal-install's behaviour strange because:

you can "cabal install" a package without any complaint
but the next "ghc-pkg list" is all red because of conflicts.
and it's too late then - there's no way to get back.
even if you re-install some package, it seems it is getting
a different hashcode, so it's not recognized. if you were doing
"cabal install --global" for some ghc package (e.g. old-locale),
then ghc seems completely hosed and you've got to re-install
the compiler. well that's not a big deal by itself
but afterwards you have to re-install all packages ...

so please please please have "cabal install" fail with some error
message if (that is, before) the install would break anything. - J.

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.12.1

$ cabal --version
cabal-install version 0.8.0
using version 1.8.0.2 of the Cabal library



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


Re: [Haskell-cafe] Re: programmatic DB interface?

2010-02-05 Thread Johannes Waldmann

> That is exactly the problem - it is wrong for CalendarT.

what do you mean by "it" ... what package should be fixed
(old-locale, haskelldb-hdbc-postgreqsl, ...)?
Because obviously something seems broken here.

J.




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


Re: [Haskell-cafe] Re: programmatic DB interface?

2010-02-05 Thread Colin Paul Adams
> "Johannes" == Johannes Waldmann  writes:

Johannes> Michael Snoyman  snoyman.com> writes:
>> Did you append an empty string in the SELECT statement?

Johannes> Magnus says 1. is wrong, but I don't see how the DB server
Johannes> could be convinced to send the ...T...Z format.  In my
Johannes> application, the table definition contains 'timestamp
Johannes> without time zone' and I cannot change that.

That is exactly the problem - it is wrong for CalendarT.
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: programmatic DB interface?

2010-02-05 Thread Johannes Waldmann
Michael Snoyman  snoyman.com> writes:

> Did you append an empty string in the SELECT statement? 

I did not write a SELECT statement (see first post of this thread) ...
SELECTs are generated by haskelldb(-hdbc-postgresql)

I have a working version now, but only by
1. changing the format string computation to
  "%Y-%m-%d" ++ ' ' : fmt
2. adding a line in instance Convertible SqlValue ZonedTime
   for safeConvert y@(SqlLocalTime x)

Magnus says 1. is wrong, but I don't see how the DB server 
could be convinced to send the ...T...Z format.
In my application, the table definition contains 'timestamp without time zone'
and I cannot change that.

J.


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


Re: [Haskell-cafe] safe lazy IO or Iteratee?

2010-02-05 Thread John Lato
> Subject: Re: [Haskell-cafe] safe lazy IO or Iteratee?
>
> Downside: iteratees are very hard to understand. I wrote a
> decently-sized article about them trying to figure out how to make
> them useful, and some comments in one of Oleg's implementations
> suggest that the "iteratee" package is subtly wrong. Oleg has written
> at least three versions (non-monadic, monadic, monadic CPS) and I've
> no idea why or whether their differences are important. Even dons says
> he didn't understand them until after writing his own iteratee-based
> IO layer.

More significant than, and orthogonal to, the differences between
non-monadic and monadic are the two primary implementations Oleg has
written.  They are[1]:

Design 1:
newtype Iteratee el m a = Iteratee{runIter:: Stream el -> m (IterV el m a)}
data IterV el m a = IE_done a (Stream el)
  | IE_cont (Iteratee el m a) (Maybe ErrMsg)

Design 2:
newtype Iteratee el m a = Iteratee{runIter:: m (IterV el m a)}
data IterV el m a = IE_done a (Stream el)
  | IE_cont (Stream el -> Iteratee el m a) (Maybe ErrMsg

With the first design, it's impossible to get the state of an iteratee
without feeding it a chunk.  There are other consequences too.  The
second design seems to require some specialized combinators, that is
(>>==) and ($$), which are not required for the first version.
Neither situation is ideal.  The CPS version appears to remedy both
flaws, but at the expense of introducing CPS at a low level (this can
be hidden from the end user in many cases).  I already think of
iteratees as holding continuations, so to me the so-called "CPS
version" is to me a double CPS.

Both designs appear to offer similar performance in aggregate,
although there are differences for particular functions.  I haven't
yet had a chance to test the performance of the CPS variant, although
Oleg has indicated he expects it will be higher.

The monadic/non-monadic issue is related.  Non-monadic iteratees are
iteratees that can't perform monadic effects when they're running
(although they can still be fed from a monadic enumerator).
Essentially it's the difference between "fold" and "foldM".  They are
simpler and more efficient because of this, but also much less
powerful.  Any iteratee design can support both non-monadic and
monadic, but *I* don't want to support both.  At least, I don't want
to have double modules for everything for nearly identical functions,
and polymorphic code that can handle non-monadic and monadic iteratees
is non-trivial[2].

Much of my recent work has been in the consequences of these various
design considerations for the next version of the iteratee library.
Currently undecided, although I'm leaning towards CPS.  It seems to
solve a lot of problems, and the implementation details are generally
cleaner too.

Cheers,
John

[1] Both taken from
http://okmij.org/ftp/Haskell/Iteratee/IterateeM.hs.  Design 1 is
commented out on that page.

[2] At least for me.  Maybe others can provide a better solution.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] multMM :: Matrix -> Matrix -> Matrix --multiplies two matrices question (Homework)

2010-02-05 Thread Keith Sheppard
I did a blog post on basic matrix ops which may be useful to you

http://blog.keithsheppard.name/2009/06/bird-tracks-through-math-land-basic.html

It uses a 2D list representation for matrices which you would not do
for any performance critical work.

best
keith

On Wed, Feb 3, 2010 at 1:38 AM, 조광래  wrote:
> hi i was trying to solve it but
>
> All i got is
> type Matrix=[[Double]]
>
> multMM :: Matrix -> Matrix -> Matrix --multiplies two matrices
> multMM m t =    [[sum (zipWith (*) (head m)(a)) ] ]where  a = [head a | a<-
> t]
>
>
> Main> multMM [[2,1,-6],[1,-3,2]] [[1,0,-3],[0,4,20],[-2,1,1]]
> [[14.0]]
>
> from this i could get only the first multiplication 14    that is by  2*1 +
> 1*0 + -6*-2 = 14
>
> how can i make this go throw all rows and colums to get multiple of matrixs?
>
> Thank you~
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



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


Re: [Haskell-cafe] Re: Generating repeatable arbitrary values with QuickCheck 2

2010-02-05 Thread Stefan Holdermans

Martijn,

Ryan wrote:


Unfortunately, this makes things like

infinite_xs <- sequence (repeat arbitrary)

no longer work, since the state never comes out the other side.


You replied:

You're asking to execute an infinite number of monadic actions. How  
can this ever terminate at all?


There is this thing called lazy evaluation, you know. ;-)

Try for yourself:

  import System.Random
  import Test.QuickCheck

  foo :: Gen [Int]
  foo = do
ns <- sequence (repeat arbitrary)
return (take 5 ns)

  main ::   IO ()
  main = do
stdGen <- newStdGen
print (generate 42 stdGen foo)

Cheers,

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


[Haskell-cafe] online Real World Haskell - tool used?

2010-02-05 Thread Sophie

Not a Haskell question, pardon me.

I believe the online Real World Haskell book with commenting system was 
generated with an open-source tool (written by one of the authors?). 
Any idea where I might find this?


[I think I had gotten the link long ago, lost it].

I am also curious what authoring tools were used to write the book.

Thanks!

Sophie


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


Re: [Haskell-cafe] Re: Generating repeatable arbitrary values with QuickCheck 2

2010-02-05 Thread Martijn van Steenbergen

Ryan Ingram wrote:

Unfortunately, this makes things like

 infinite_xs <- sequence (repeat arbitrary)

no longer work, since the state never comes out the other side.


You're asking to execute an infinite number of monadic actions. How can 
this ever terminate at all?


Martijn.

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


Re: [Haskell-cafe] Re: programmatic DB interface?

2010-02-05 Thread Michael Snoyman
On Fri, Feb 5, 2010 at 10:55 AM, Johannes Waldmann <
waldm...@imn.htwk-leipzig.de> wrote:

> > and then read with my own parse string:"%Y-%m-%d %T%Q"
> > This seems to work just fine.
>
> Thanks. - When I'm using that format string, I get:
>
> Convertible: error converting source data SqlLocalTime 2008-10-29 00:00:00
> of type SqlValue to type Data.Time.LocalTime.LocalTime.ZonedTime:
> incompatible types
>
> I guess I need to find out who wants ZonedTime.
>
> In my DB description (generated by dbdirect),
> the only time-related type is CalendarTime.
>
> J.
>
>
> Did you append an empty string in the SELECT statement? If you append the
empty string (||''), HDBC treats the field as text and so returns a
SqlByteString. However, if you do not append the empty string, it treats the
field as a timestamp and tries to convert it before it even reaches your
code.

All of this is just speculation, of course, since I haven't actually looked
at the code. But my "extensive" (ie, 5 minute) testing implies it to be
true.

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


Re: [Haskell-cafe] Re: sendfile leaking descriptors on Linux?

2010-02-05 Thread MightyByte
I've been seeing a steady stream of similar resource vanished messages
for as long as I've been running my happstack app.  This message I get
is this:

: hClose: resource vanished (Broken pipe)

I run my app from a shell script inside a "while true" loop, so it
automatically gets restarted if it crashes.  This incurs no more than
a few seconds of down time.  Since that is acceptable for my
application, I've never put much effort into investigating the issue.
But I don't think the resource vanished error results in program
termination.  When I have looked into it, I've had similar trouble
reproducing it.  Clients such as wget and firefox don't seem to cause
the problem.  If I remember correctly it only happens with IE.

On Fri, Feb 5, 2010 at 2:56 AM, Bardur Arantsson  wrote:
> Jeremy Shaw wrote:
>>
>> Actually,
>>
>> We should start by testing if native sendfile leaks file descriptors even
>> when the whole file is sent. We have a test suite, but I am not sure if it
>> tests for file handle leaking...
>>
>
> I should have posted this earlier, but the exact message I'm seeing in the
> case where the Bad Client disconnects is this:
>
>   hums: Network.Socket.SendFile.Linux: resource vanished (Broken pipe)
>
> Oddly, I haven't been able to reproduce this using a wget client with a ^C
> during transfer. When I "disconnect" wget with ^C or "pkill wget" or even
> "pkill -9 wget", I get this message:
>
>  hums: Network.Socket.SendFile.Linux: resource vanished (Connection reset by
> peer)
>
> (and no leak, as observed by "lsof | grep hums").
>
> So there appears to be some vital difference between the handling of the two
> cases.
>
> Another observation which may be useful:
>
> Before the sendfile' API change (Handle -> FilePath) in sendfile-0.6.x, my
> code used "withFile" to open the file and to ensure that it was closed. So
> it seems that withBinaryFile *should* also be fine. Unless the "Broken pipe"
> error somehow escapes the scope without causing a "close".
>
> I don't have time to dig more right now, but I'll try to see if I can find
> out more later.
>
> Cheers,
>
> ___
> 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] Anyone up for Google SoC 2010?

2010-02-05 Thread Sittampalam, Ganesh
Gwern Branwen wrote:
> On Wed, Feb 3, 2010 at 8:14 PM, Henk-Jan van Tuyl 
> wrote: 
>> On Wed, 03 Feb 2010 23:34:34 +0100, Neil Mitchell
>> 
>> wrote:
>> 
>>> Hi Gwern,
>>> 
>>> Please update: "haskell-src-exts -> haskell-src" **Unknown**
>>> 
>>> This project was an unqualified success.  haskell-src-exts is now
>>> one 
>>> of the most commonly used Haskell libraries, achieved the goals in
>>> the project proposal, and is an essential piece of Haskell
>>> infrastructure. 
>> 
>> You can see this using Roel van Dijk's reversed dependencies
>> overview [1]: 23 direct and 57 indirect dependencies on
>> haskell-src-exts-1.8.0 
>> 
>> Regards,
>> Henk-Jan van Tuyl
> 
> And how many of those used haskell-src-exts *before* the SoC project?
> And would have used it regardless? You can't point to a popular
> project which got a SoC student, and say look at how popular it is -
> obviously the SoC student was hugely successful.  

Regardless of that, is there any reason to disregard Neil's summary and not 
update your page?

Ganesh


=== 
 Please access the attached hyperlink for an important electronic 
communications disclaimer: 
 http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html 
 
=== 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: programmatic DB interface?

2010-02-05 Thread Johannes Waldmann
> and then read with my own parse string:"%Y-%m-%d %T%Q"
> This seems to work just fine. 

Thanks. - When I'm using that format string, I get:

Convertible: error converting source data SqlLocalTime 2008-10-29 00:00:00 
of type SqlValue to type Data.Time.LocalTime.LocalTime.ZonedTime: 
incompatible types

I guess I need to find out who wants ZonedTime.

In my DB description (generated by dbdirect),
the only time-related type is CalendarTime.

J.


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


[Haskell-cafe] Re: sendfile leaking descriptors on Linux?

2010-02-05 Thread Bardur Arantsson

Jeremy Shaw wrote:

Actually,

We should start by testing if native sendfile leaks file descriptors even
when the whole file is sent. We have a test suite, but I am not sure if it
tests for file handle leaking...



I should have posted this earlier, but the exact message I'm seeing in 
the case where the Bad Client disconnects is this:


   hums: Network.Socket.SendFile.Linux: resource vanished (Broken pipe)

Oddly, I haven't been able to reproduce this using a wget client with a 
^C during transfer. When I "disconnect" wget with ^C or "pkill wget" or 
even "pkill -9 wget", I get this message:


  hums: Network.Socket.SendFile.Linux: resource vanished (Connection 
reset by peer)


(and no leak, as observed by "lsof | grep hums").

So there appears to be some vital difference between the handling of the 
two cases.


Another observation which may be useful:

Before the sendfile' API change (Handle -> FilePath) in sendfile-0.6.x, 
my code used "withFile" to open the file and to ensure that it was 
closed. So it seems that withBinaryFile *should* also be fine. Unless 
the "Broken pipe" error somehow escapes the scope without causing a "close".


I don't have time to dig more right now, but I'll try to see if I can 
find out more later.


Cheers,

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


[Haskell-cafe] Dutch HUG: meeting Monday 8th in Utrecht

2010-02-05 Thread Tom Lokhorst
I'd like to invite functional programmers in The Netherlands to the
Dutch Haskell User Group [1, 2] meeting next Monday at 19:00.

Two talks are scheduled:

 - Sebastiaan Visser and Tom Lokhorst will give a talk entitled
"AwesomePrelude, Liberating Haskell from data types!"
 - Martijn van Steenbergen will talk about serializing monadic
computations. In particular, he will describe a monadic EDSL to
describe compass-and-straightedge constructions and how to serialize
and deserialize such values.

The meeting will be in the Booth Hall [3] of the Utrecht University
Library. There's free car parking [4] at the library, and it's easily
accessible by bike and bus [5].

After the talks we will move to The Basket [6] for drinks.

See you next Monday!


- Tom Lokhorst

[1]: http://www.haskell.org/haskellwiki/Dutch_HUG
[2]: http://groups.google.com/group/dutch-hug
[3]: 
http://www.uu.nl/EN/library/contact/university_library/zaalverhuur/Pages/default.aspx#booth
[4]: 
http://www.uu.nl/EN/library/contact/university_library/Parkeren/Pages/default.aspx
[5]: 
http://www.uu.nl/EN/library/contact/university_library/plattegrondenrou/Pages/default.aspx
[6]: http://utrecht.thebasket.nl/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] safe lazy IO or Iteratee?

2010-02-05 Thread Nicolas Pouillard
On Thu, 4 Feb 2010 12:51:59 -0800, John Millikin  wrote:
> Both have advantages and disadvantages. The primary advantage of lazy
> IO over iteratees is that it's much, *much* easier to understand --
> existing experience with monads can be used immediately. The downsides
> of lazy IO, of course, are well documented[1][2][3].
> 
> Some are fixed by the safe/strict IO packages. However, safe lazy IO
> is still "unpredictable" in that it's difficult to know how many
> resources will be used, the order of some operations (eg, releasing
> handles), or whether some particular expression will throw an
> exception.

I don't know if you include safe-lazy-io [1] here but its purpose is to cure
these downsides. In particular file handles are properly released on time
even when asking for a stream of a list of files. Moreover exceptions are
not hidden and can be caught properly in the wrapping IO layer.

Some restrictions are there though. For instance one cannot arbitrarily
interleave different streams, one have to use one of the predefined
interleaving scheme. Another limitation is that the client cannot react
to errors without getting back to the non-lazy IO world, however this
is a big selling point as well of lazy-IO: "reuse pure code".

I don't want to claim that (safe-)lazy-IO should be used in all situations,
this would be terribly wrong. However I recommend it for situations were
the interleaving of input is standard and errors have not to be caught
in the processing code.

Best regards,

[1]: http://www.haskell.org/pipermail/haskell/2009-March/021133.html

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


Re: [Haskell-cafe] Sparks created, but not used (par/pseq, ST monad)

2010-02-05 Thread Michael Lesniak
Hello Daniel,

>> and running with
>>
>>     ./st +RTS -N -s
> You'd need to give a number of capacities, I think (-N2 e.g.).
The runtime option -N chooses the maximum number of cores,  according
to GHC's documentation.


> I think with the strict ST monad, when you have
>    a <- f n1
>    b <- f n2
> they are already evaluated, so there's no point in sparking evaluation in
> parallel.
Very good point and probably the reason for my problems, thanks!


Cheers,
  Michael


-- 
Dipl.-Inf. Michael C. Lesniak
University of Kassel
Programming Languages / Methodologies Research Group
Department of Computer Science and Electrical Engineering

Wilhelmshöher Allee 73
34121 Kassel

Phone: +49-(0)561-804-6269
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe