[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-12 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote:
 Heinrich Apfelmus writes:
 I'm not sure what the right solution is, but I think it definitely
 involves catering for different node types. For instance, the library
 could operate on a type

 newtype Graph node a b = Graph (Gr a b, Data.Map.Map Int node)

 or it could offer a more useful  NodeMap  type and make the  Node  type
 abstract. Some systematic and simple abstractions to manage nodes is
 needed anyway.
 
 As I said, we're considering using an Associated Type to let users
 choose what type they want to use (probably with a default Map instance
 for this).  However, we'd recommend/push the Int-based one.

For my  make  example, I prefer a plain parameter because it would be
too verbose to define a new class that has  FilePaths  as node types.
I'd use the  Int  instead, but this defeats the point: why offer
flexible node types when it's too much of a burden to use them?

 An explicit type parameter for the vertex type is not appropriate for
 this reason: you don't want to change it.

It's true that I don't want to change the node type, but I want to curry
it. If I don't feel like writing out the node type every time, I can use
a type synonym:

   type MyGraph a b = Graph FilePath a b


Graphs with different node types don't behave differently; graphs are
parametric with respect to the node type, just like lists don't behave
differently on different element types.


 Also, hard-coding  Node = Int  feels like the wrong kind of flexibility:
 the user is able to do anything with it, just in case the library forgot
 some important functionality. Which is exactly what happened in my case
 when I used  Map.findIndex . I prefer the library to get it right.
 
 What do you mean by the library forgot some important functionality?

Ah, I'm comparing  Node = Int  to a  Node  type that is entirely
abstract. After all, conceptually,  Node  is not an integer, it's a
unique identifier.

If  Node  is abstract, then you will probably miss things like the [1..]
 that you mentioned.

Nonetheless, I would like to see  Node  to become abstract. This means
that the graph library should include a library that deals with unique
identifiers  Node . The [1..] pattern would correspond to a function

freshNodes :: () - [Node]

 PS: While we're at it, I think  newNodes  should return an infinite list
 of  Node  instead of requiring a fixed number to be specified in
 advance?
 
 Well, if we let the vertex type be _anything_ (that is an instance of
 Ord; we'll probably require that much at least, though maybe just Eq
 would make sense for list-based graphs), then how do we generate
 newNodes?  Require Enum?  Bounded?

Ah, that suggestion was for  Node = Int  or  Node = abstract . If the
library user uses his own node type, it's him who is responsible for
allocating new  Nodes .

 Really, performance aside, this is my biggest possible problem with
 generic label types is that it may make it harder to define various
 algorithms on graphs because you can no longer guarantee what you can do
 with the vertex types; as such people may resort to requring the vertex
 type to be Int or something to use a specific algorithm.

Ah, you mean algorithms that create new nodes on the fly? I don't think
that  Node = Int  works for them either, because the user might have his
own ideas about which  Ints  can appear as graph vertexes. For instance,
he might only use even numbers to denote vertexes and will be surprised
by a library algorithm that suddenly creates odd vertexes. In short,
Node  needs to be abstract for that.

Other than that, I don't see much of a difference between custom vertex
types and  Int  . Internally, you can always use  Int  to reference
nodes and keep the association between the custom vertex type and  Int
in a separate map, like this

   data Graph node a b =
   Graph { internal :: Gr a b , nodes :: Map node a }


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-12 Thread Heinrich Apfelmus
Henning Thielemann wrote:
 
 Ivan Miljenovic wrote:
 
 You're splitting apart related data into _three_ different data
 structures (the graph, vertex labels and edge labels)?  _That_ doesn't
 make sense.
 
 There are no edge labels, only vertex labels. And yes, I find separation
 of data structures for separation of concerns a good strategy.

It appears to me that the concerns of labels and vertexes are not
separate enough. After all, the point is that they have to be kept in
sync. Keeping them in sync should be the business of the graph library,
not of the user. It doesn't have to be baked into the graph type,
though,  an abstract  Node  type might work as well.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-12 Thread Ivan Lazar Miljenovic
Heinrich Apfelmus apfel...@quantentunnel.de writes:

 Ivan Lazar Miljenovic wrote:
 As I said, we're considering using an Associated Type to let users
 choose what type they want to use (probably with a default Map instance
 for this).  However, we'd recommend/push the Int-based one.

 For my  make  example, I prefer a plain parameter because it would be
 too verbose to define a new class that has  FilePaths  as node types.
 I'd use the  Int  instead, but this defeats the point: why offer
 flexible node types when it's too much of a burden to use them?

The point is so that you can define new graph types with that node type.

 An explicit type parameter for the vertex type is not appropriate for
 this reason: you don't want to change it.

 It's true that I don't want to change the node type, but I want to curry
 it. If I don't feel like writing out the node type every time, I can use
 a type synonym:

type MyGraph a b = Graph FilePath a b


 Graphs with different node types don't behave differently; graphs are
 parametric with respect to the node type, just like lists don't behave
 differently on different element types.

There will be a Map-based graph available that will have the node type
parameter, but the variant that's currently called PatriciaTree will
most likely be the preferred default one (as it will have better
performance due to its use of IntMap).

We can't require the class to have the vertex type as a type parameter
for when we want a graph (such as PatriciaTree) _with_ a fixed vertex
type.

 Also, hard-coding  Node = Int  feels like the wrong kind of flexibility:
 the user is able to do anything with it, just in case the library forgot
 some important functionality. Which is exactly what happened in my case
 when I used  Map.findIndex . I prefer the library to get it right.
 
 What do you mean by the library forgot some important functionality?

 Ah, I'm comparing  Node = Int  to a  Node  type that is entirely
 abstract. After all, conceptually,  Node  is not an integer, it's a
 unique identifier.

 If  Node  is abstract, then you will probably miss things like the [1..]
  that you mentioned.

 Nonetheless, I would like to see  Node  to become abstract. This means
 that the graph library should include a library that deals with unique
 identifiers  Node . The [1..] pattern would correspond to a function

 freshNodes :: () - [Node]

Well, I don't use [1..] to get new nodes, I use them to map over nodes
(depending on how I construct the graph) or to create a new graph
completely from scratch.

Also, that type signature doesn't make sense; something like freshNodes
:: (Graph g) = g - [Vertex g] might, but the problem with a generic
node type is that its not really possible to do such a thing in general;
AFAICT the full type signature will need to be:

freshNodes :: ( Graph g, Enum (Vertex g), Bounded (Vertext g)
  , Ord (Vertex g)) = g - [Vertex g]

where the Bounded is needed for empty graphs (i.e. use minBound); if the
graph isn't empty, then take the maximum (hence Ord).  This of course
will be tricky to implement for the general case (if we have vertices
[1,2,4], should it return 3?  What happens about overflows?).

If we define such a function, it will most likely not be part of the
class definition since we wouldn't want to put these restrictions on the
vertex type (since I might want Integer as my vertex type, which isn't
an instance of Bounded; maybe having an unsafe variant of this that
assumes the graph is non-empty makes sense).

 Really, performance aside, this is my biggest possible problem with
 generic label types is that it may make it harder to define various
 algorithms on graphs because you can no longer guarantee what you can do
 with the vertex types; as such people may resort to requring the vertex
 type to be Int or something to use a specific algorithm.

 Ah, you mean algorithms that create new nodes on the fly? I don't think
 that  Node = Int  works for them either, because the user might have his
 own ideas about which  Ints  can appear as graph vertexes. For instance,
 he might only use even numbers to denote vertexes and will be surprised
 by a library algorithm that suddenly creates odd vertexes. In short,
 Node  needs to be abstract for that.

Actually, I've looked through my code and it appears that (apart from
verboseness), there won't be too much of a problem with removing the
assumption of vertex type == Int.

However, I can't see any reason why someone would only want to use even
Int values.  As I think I've said before (I've been making these
arguments in various threads and discussions, so I'm not sure if I've
said it here): the vertex type is just an _index_ to ensure consistency,
etc; it is _not_ IMHO meant to represent the actual data: that's what
the labels are for.

 Other than that, I don't see much of a difference between custom vertex
 types and  Int  . Internally, you can always use  Int  to reference
 nodes and keep 

Re: [Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-12 Thread Ivan Lazar Miljenovic
Heinrich Apfelmus apfel...@quantentunnel.de writes:
 It appears to me that the concerns of labels and vertexes are not
 separate enough. After all, the point is that they have to be kept in
 sync. Keeping them in sync should be the business of the graph library,
 not of the user. It doesn't have to be baked into the graph type,
 though,  an abstract  Node  type might work as well.

An abstract vertex type is orthoganal to the label type (though it took
me a while to convince Thomas of that; he wanted to somehow embed the
vertex type inside the label :s).

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


[Haskell-cafe] Re: tweak vacuum-* output

2010-05-12 Thread Gleb Alexeyev

Ozgur Akgun wrote:

Hi all,

I am using vacuum-opengl and vacuum-ubigraph to visualise and analyse some
of my data structures. They are quite helpful most of the time, however
sometimes I feel the need to tweak the generated output -- such as removing
the auto-generted identifiers from constrcutor names, pack some things
together, or similar.

Is there a way to configure their output?

And for the vacuum-ubigraph option, I like it's output generally, however
while creating the expression tree, is doesn't respect my structures. If
there is a flag or so to fix this issue, I'd appreciate it. The Problem is
like the following:

data Expr = Sum Expr Expr | Mult Expr Expr | Single Int
e = Sum (Single 2) (Mult (Single 3) (Single 4))

And it orients the tree in such a way that Mult looks like the root node,
instead of Sum, as I would expect.



Hi,
I can answer only about vacuum-ubigraph.
Regarding expression tree: the problem is Ubigraph doesn't know anything 
about the tree. It uses physical simulation to determine the optimum 
graph layout, the Mult node has the most links attached to it, that's 
why it's located at the center of the graph. As far as I can tell from 
Ubigraph docs, this cannot be tweaked. Theoretically one can change the 
shape of the graph visualization by introducing invisible links and/or 
nodes.


And no, there's no way to tweak the vacuum-ubigraph output without 
modifying its code.

Thanks,
Ozgur Akgun





___
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] Speed of Error handling with Continuations vs. Eithers

2010-05-12 Thread Andrea Vezzosi
On Wed, May 12, 2010 at 7:50 AM, wren ng thornton w...@freegeek.org wrote:
 wren ng thornton wrote:

 Here's one big difference:

 newtype ErrCPS e m a = ErrCPS { runErrCPS ::
    forall r . (e - m r) --  error handler
    - (a - m r) --  success handler
    - m r }

 The analogous version I use is:

    newtype MaybeCPS a = MaybeCPS
        (forall r. (a - Maybe r) - Maybe r)

 While I also offer a transformer version of MaybeCPS, the transformer
 *does* suffer from significant slowdown. Also, for MaybeCPS it's better to
 leave the handlers inline in client code rather than to abstract them out;
 that helps to keep things concrete. So perhaps you should first try a direct
 CPS translation:

    newtype ErrCPS e a = ErrCPS
        (forall r. (a - Either e r) - Either e r)

    runErrCPS :: ErrCPS e a - Either e a
    runErrCPS (ErrCPS f) = f return

 I'd be curious if this version suffers the same slowdown.


 With this change [1] I can't notice any difference for your benchmark[2].
 Then again, all the runTest calls take 0 msec and I've had no luck making
 the computation take much time; perhaps your computer can detect a
 difference.

On my machine, with ghc-6.12.1, yours and the original ErrCPS give
quite similar results, both ~2x slower than Either.
However it's important to note that these results are highly dependent
on the monadic expressions being evaluated, with a different benchmark
you can get an huge speedup with the CPS versions.

mkEMA is in fact quite peculiar, since there's no catchError and the
throwError call is rarely (or never?) made, and thanks to foldM you
get that (=) is only used in a right associated way, which is the
ideal situation for Either.

In a larger program one might mix the two to get the best of both
worlds i guess, and maybe we can make a library where each combinator
from Control.Monad is reimplemented with the most fitting alternative
behind the scenes.

the nice part is that you can get the CPS version in a generic way
using Codensity:
http://hackage.haskell.org/packages/archive/mmtl/0.1/doc/html/Control-Monad-Codensity.html


 You may want to see what standard benchmarking tools like Microbench[3] or
 the magnificent Criterion[4] have to say. I'd do it myself, but I haven't
 had a chance to reinstall everything since getting my new computer (due to
 the installation issues on newer versions of OSX).


 [1]
 http://community.haskell.org/~wren/wren-extras/src/Control/Monad/ErrCPS.hs

 [2]
 http://community.haskell.org/~wren/wren-extras/test/Control/Monad/ErrCPS/MaxCantorBenchmark.hs

 [3] http://hackage.haskell.org/package/microbench

 [4] http://hackage.haskell.org/package/criterion

 --
 Live well,
 ~wren
 ___
 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] Re: hSetEncoding on socket handles

2010-05-12 Thread Simon Marlow

On 12/05/2010 01:56, David Powell wrote:

Greetings,

I am having trouble sending unicode characters as utf8 over a socket handle.
Despite setting the encoding on the socket handle to utf8, it still seems to
use some other encoding when writing to the socket.  It works correctly when
writing to stdout, but not to a socket handle.  I am using ghc 6.12.1 and
network-2.2.1.7.  I can get it to work using System.IO.UTF8, but I was under
the impression this was no longer necessary?

I also don't seem to understand the interaction between hSetEncoding and
hSetBinaryMode because if I set the binary mode to 'False' and the
encoding to
utf8 on the socket, then when writing to the socket the string seems to be
truncated at the first non-ascii codepoint.

Here is a test snippet, which can be used with netcat as a listening server
(ie. nc -l 1234).

  import System.IO
  import Network
  main = do
   let a=λ
   s - connectTo 127.0.0.1 (PortNumber 1234)
   hSetEncoding s utf8
   hSetEncoding stdout utf8
   hPutStrLn s a
   putStrLn a
   hClose s


You've found a bug, thanks.  The bug is that a socket is bidirectional 
and we're only setting the encoding for one side (the read side) but we 
should be setting it for both sides.


I just created a ticket:

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

Expect a fix in GHC 6.12.3.  In the meantime you can work around it, 
e.g. this worked for me to create a write-only socket that hSetEncoding 
works with:


connectTo hostname (PortNumber port) = do
proto - getProtocolNumber tcp
bracketOnError
(socket AF_INET Stream proto)
(sClose)  -- only done if there's an error
(\sock - do
  he - getHostByName hostname
  connect sock (SockAddrInet port (hostAddress he))
  socketToHandle sock WriteMode
)

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


[Haskell-cafe] ghc api renamed source

2010-05-12 Thread Phyx
Hi all,

 

I was wondering if it's possible to get to the renamed source before
actually typechecking,

 

I currently have

 

parsed  - parse modName

checked - typecheckModule parsed

let renamed = tm_renamed_source checked

value   = tm_typechecked_source checked

 

but if typechecking failes, I get no information at all (an error), while I
should be able to still get the renamed source.

Any suggestions?

 

Cheers,

Phyx

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


Re: [Haskell-cafe] Speed of Error handling with Continuations vs. Eithers

2010-05-12 Thread Antoine Latter
On Tue, May 11, 2010 at 8:28 PM, wren ng thornton w...@freegeek.org wrote:
 Max Cantor wrote:

 Based on some discussions in #haskell, it seemed to be a consensus
 that using a modified continuation monad for Error handling instead
 of Eithers would be a significant optimization since it would
 eliminate a lot of conditional branching (everytime = is called
 in the Either monad, there is a conditional.
 I implemented a ErrCPS monad which does exactly that, but the speed
 has been disappointing.  It runs almost exactly 3x slower than a
 drop in replacement using the MonadError instance of Either from mtl.


 I have noticed speedup in my CPS version of Maybe[1] (kidnapped from the
 Wiki) so the difference is curious. Jan-Willem's comments about closures are
 significant when doing CPS work, but I'd expect Maybe and Either to perform
 similarly, whatever their performance is. It's been a while since I've
 benchmarked MaybeCPS, so perhaps I now have the slowdown too. Let's look at
 the code and see if we can find other differences...

 [1]
 http://community.haskell.org/~wren/wren-extras/src/Control/Monad/MaybeCPS.hs


 Here's one big difference:

 newtype ErrCPS e m a = ErrCPS { runErrCPS ::
    forall r . (e - m r) --  error handler
    - (a - m r) --  success handler
    - m r }

 The analogous version I use is:

    newtype MaybeCPS a = MaybeCPS
        (forall r. (a - Maybe r) - Maybe r)

 While I also offer a transformer version of MaybeCPS, the transformer *does*
 suffer from significant slowdown. Also, for MaybeCPS it's better to leave
 the handlers inline in client code rather than to abstract them out; that
 helps to keep things concrete. So perhaps you should first try a direct CPS
 translation:


Is the CPS transformed MaybeT slower because it's done in 2-CPS,
rather than in 1-CPS like the MaybeCPS? I only did MaybeT in 2-CPS
because it was the easiest, not because I thought it would be easiest.

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


Re: [Haskell-cafe] ghc api renamed source

2010-05-12 Thread Thomas Schilling
The difficulty is that renamer and type-checker are mutually recursive
because of Template Haskell.  I've been looking into this a while ago
and I have a basic idea how a better API could look like, but I
haven't sorted out the details.

One very hacky workaround -- and I'm not sure whether it can actually
work -- is to copy the file TcRnDriver from the GHC sources and modify
it to do what you need.  It wouldn't be an easy task, though.

On 12 May 2010 14:35, Phyx loneti...@gmail.com wrote:
 Hi all,



 I was wondering if it’s possible to get to the renamed source before
 actually typechecking,



 I currently have



     parsed  - parse modName

     checked - typecheckModule parsed

     let renamed = tm_renamed_source checked

     value   = tm_typechecked_source checked



 but if typechecking failes, I get no information at all (an error), while I
 should be able to still get the renamed source.

 Any suggestions?



 Cheers,

 Phyx

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





-- 
Push the envelope.  Watch it bend.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: Monad.Reader Issue 16

2010-05-12 Thread Brent Yorgey
I am very pleased to announce that Issue 16 of The Monad.Reader is now
available [1].

Issue 16 consists of the following three articles:

* Demand More of Your Automata by Aran Donohue
* Iteratee: Teaching an Old Fold New Tricks by John W. Lato
* Playing with Priority Queues by Louis Wasserman

Feel free to browse the source files [2]. You can check out the entire
repository using darcs:

darcs get http://code.haskell.org/~byorgey/TMR/Issue16

If you'd like to write something for Issue 17, please get in
touch. The deadline will likely be sometime in September; more details
will be forthcoming.

-Brent

[1] http://themonadreader.files.wordpress.com/2010/05/issue16.pdf
[2] http://code.haskell.org/~byorgey/TMR/Issue16
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Why is TChan GHC specific?

2010-05-12 Thread Edward Amsden
I'm currently just getting into playing around with concurrency in
haskell, primarily because I find STM intriguing. In looking through
the docs I noticed that the transactional channels are GHC specific.
http://hackage.haskell.org/packages/archive/stm/2.1.1.2/doc/html/Control-Concurrent-STM-TChan.html

I dug around the wiki and Google but I couldn't find the reason for this.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is TChan GHC specific?

2010-05-12 Thread Peter Robinson
As far as I know, TChan needs the 'retry' combinator which requires GHC's RTS.
Same is true for TMVar, I think.

  Peter

On 12 May 2010 21:15, Edward Amsden eca7...@cs.rit.edu wrote:
 I'm currently just getting into playing around with concurrency in
 haskell, primarily because I find STM intriguing. In looking through
 the docs I noticed that the transactional channels are GHC specific.
 http://hackage.haskell.org/packages/archive/stm/2.1.1.2/doc/html/Control-Concurrent-STM-TChan.html

 I dug around the wiki and Google but I couldn't find the reason for this.
 ___
 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] corner case in Text.JSON 0.4.3

2010-05-12 Thread Martin Hilbig

hi,

since i got no answer from the maintainer, maybe someone else can take 
care of it, or at least point out, what i did wrong.


so, i recently stumbled upon some error while using Text.JSON 0.4.3 [1]:

  Text/JSON/String.hs:(127,4)-(137,49): Non-exhaustive patterns in case

indeed ghc warned:

  [5 of 7] Compiling Text.JSON.String ( Text/JSON/String.hs, 
dist/build/Text/JSON/String.o )


  Text/JSON/String.hs:127:4:
  Warning: Pattern match(es) are non-exhaustive
   In a case alternative: Patterns not matched: []

from looking at the code i couldn't see how this would ever happen, but 
you can reproduce it be running the files from [2]:


  $ ./test  problem
  Ok (JSArray [JSString (JSONString {fromJSString = this}),JSString 
(JSONString {fromJSString = is}),JSString (JSONString {fromJSString = 
some}),JSString (JSONString {fromJSString = json}),JSObject 
(JSONObject {fromJSObject = [(that,JSString (JSONString {fromJSString 
= works}))]})])

test: Text/JSON/String.hs:(127,4)-(137,49): Non-exhaustive patterns in case

the patch i put there fixes it (at least for me) to return an Error 
instead of dying:


  $ ./test  problem
  Ok (JSArray [JSString (JSONString {fromJSString = this}),JSString 
(JSONString {fromJSString = is}),JSString (JSONString {fromJSString = 
some}),JSString (JSONString {fromJSString = json}),JSObject 
(JSONObject {fromJSObject = [(that,JSString (JSONString {fromJSString 
= works}))]})])

  Error Unexpected end of String: does
  Error Malformed JSON: invalid token in this context not\]
  test: stdin: hGetLine: end of file

have fun
martin hilbig

[1]: http://hackage.haskell.org/package/json
[2]: http://friendpaste.com/3IvnChRMoczf0mIKpOtrYE
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] corner case in Text.JSON 0.4.3

2010-05-12 Thread Iavor Diatchki
Hi,
I think it was probably I who wrote this, so I'll take the blame :-)
It seems like a genuine bug, where we are not checking for strings
that are not terminated.  Thanks for spotting it, and also for the
patch!  I'll try to update the package soon.
-Iavor

On Wed, May 12, 2010 at 12:53 PM, Martin Hilbig mar...@mhilbig.de wrote:
 hi,

 since i got no answer from the maintainer, maybe someone else can take care
 of it, or at least point out, what i did wrong.

 so, i recently stumbled upon some error while using Text.JSON 0.4.3 [1]:

  Text/JSON/String.hs:(127,4)-(137,49): Non-exhaustive patterns in case

 indeed ghc warned:

  [5 of 7] Compiling Text.JSON.String ( Text/JSON/String.hs,
 dist/build/Text/JSON/String.o )

  Text/JSON/String.hs:127:4:
      Warning: Pattern match(es) are non-exhaustive
               In a case alternative: Patterns not matched: []

 from looking at the code i couldn't see how this would ever happen, but you
 can reproduce it be running the files from [2]:

  $ ./test  problem
  Ok (JSArray [JSString (JSONString {fromJSString = this}),JSString
 (JSONString {fromJSString = is}),JSString (JSONString {fromJSString =
 some}),JSString (JSONString {fromJSString = json}),JSObject (JSONObject
 {fromJSObject = [(that,JSString (JSONString {fromJSString =
 works}))]})])
 test: Text/JSON/String.hs:(127,4)-(137,49): Non-exhaustive patterns in case

 the patch i put there fixes it (at least for me) to return an Error instead
 of dying:

  $ ./test  problem
  Ok (JSArray [JSString (JSONString {fromJSString = this}),JSString
 (JSONString {fromJSString = is}),JSString (JSONString {fromJSString =
 some}),JSString (JSONString {fromJSString = json}),JSObject (JSONObject
 {fromJSObject = [(that,JSString (JSONString {fromJSString =
 works}))]})])
  Error Unexpected end of String: does
  Error Malformed JSON: invalid token in this context not\]
  test: stdin: hGetLine: end of file

 have fun
 martin hilbig

 [1]: http://hackage.haskell.org/package/json
 [2]: http://friendpaste.com/3IvnChRMoczf0mIKpOtrYE
 ___
 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] Re: [Haskell] ANN: Monad.Reader Issue 16

2010-05-12 Thread Edward Kmett
On Wed, May 12, 2010 at 2:12 PM, Brent Yorgey byor...@seas.upenn.eduwrote:

 I am very pleased to announce that Issue 16 of The Monad.Reader is now
 available [1].

 Issue 16 consists of the following three articles:

* Demand More of Your Automata by Aran Donohue
* Iteratee: Teaching an Old Fold New Tricks by John W. Lato
* Playing with Priority Queues by Louis Wasserman


Great stuff.

As an aside, in Playing with Priority Queues, Louis provides a number of
heaps but stops short of one with O(1) worst-case persistent insert.I have
an implementation of Brodal/Okasaki heaps that achieves those bounds that is
available on hackage.

http://hackage.haskell.org/package/heaps

As he notes, it does make the implementation harder to follow, but it may be
of interest for the reader who wants to dig into this space further. =)

If I have enough downtime, I'm hoping to add a functional version of
Chazelle-style soft heaps to the library as well, which gives
O(log(1/epsilon)) delete at the expense of corrupting (increasing) an
epsilon worth of the keys in your heap, which is actually quite useful for a
number of deterministic algorithms, like an O(n) median finding algorithm,
and the fast construction of minimum spanning trees.

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


Re: [Haskell-cafe] corner case in Text.JSON 0.4.3

2010-05-12 Thread Daniel Fischer
On Wednesday 12 May 2010 21:53:41, Martin Hilbig wrote:
 hi,

 since i got no answer from the maintainer, maybe someone else can take
 care of it, or at least point out, what i did wrong.

 so, i recently stumbled upon some error while using Text.JSON 0.4.3 [1]:

Text/JSON/String.hs:(127,4)-(137,49): Non-exhaustive patterns in case

 indeed ghc warned:

[5 of 7] Compiling Text.JSON.String ( Text/JSON/String.hs,
 dist/build/Text/JSON/String.o )

Text/JSON/String.hs:127:4:
Warning: Pattern match(es) are non-exhaustive
 In a case alternative: Patterns not matched: []

 from looking at the code i couldn't see how this would ever happen, but

readJSString will die a horrible death if the closing quote is missing. 
Your input misses the closing quote, so...

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


Re: [Haskell-cafe] corner case in Text.JSON 0.4.3

2010-05-12 Thread Iavor Diatchki
Hi,
it seems that this was already fixed in the repo, I've put a new
version (0.4.4) on hackage.  Thanks, again, for spotting this!
-Iavor

On Wed, May 12, 2010 at 1:24 PM, Daniel Fischer
daniel.is.fisc...@web.de wrote:
 On Wednesday 12 May 2010 21:53:41, Martin Hilbig wrote:
 hi,

 since i got no answer from the maintainer, maybe someone else can take
 care of it, or at least point out, what i did wrong.

 so, i recently stumbled upon some error while using Text.JSON 0.4.3 [1]:

    Text/JSON/String.hs:(127,4)-(137,49): Non-exhaustive patterns in case

 indeed ghc warned:

    [5 of 7] Compiling Text.JSON.String ( Text/JSON/String.hs,
 dist/build/Text/JSON/String.o )

    Text/JSON/String.hs:127:4:
        Warning: Pattern match(es) are non-exhaustive
                 In a case alternative: Patterns not matched: []

 from looking at the code i couldn't see how this would ever happen, but

 readJSString will die a horrible death if the closing quote is missing.
 Your input misses the closing quote, so...

 ___
 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] Re: tweak vacuum-* output

2010-05-12 Thread Ozgur Akgun
Thanks for the answer.

I see your point, that Ubigraph does some magic* to place vertices and
edges.
This makes me wonder, how they generate the binary tree demo:
http://ubietylab.net/ubigraph/content/Demos/random_binary_tree.html
Is there a way to disable this optimal graph layout determination process?

Best,
Ozgur

* Nothing is magic.


On 12 May 2010 12:11, Gleb Alexeyev gleb.alex...@gmail.com wrote:

 Ozgur Akgun wrote:

 Hi all,

 I am using vacuum-opengl and vacuum-ubigraph to visualise and analyse some
 of my data structures. They are quite helpful most of the time, however
 sometimes I feel the need to tweak the generated output -- such as
 removing
 the auto-generted identifiers from constrcutor names, pack some things
 together, or similar.

 Is there a way to configure their output?

 And for the vacuum-ubigraph option, I like it's output generally, however
 while creating the expression tree, is doesn't respect my structures. If
 there is a flag or so to fix this issue, I'd appreciate it. The Problem is
 like the following:

 data Expr = Sum Expr Expr | Mult Expr Expr | Single Int
 e = Sum (Single 2) (Mult (Single 3) (Single 4))

 And it orients the tree in such a way that Mult looks like the root node,
 instead of Sum, as I would expect.


 Hi,
 I can answer only about vacuum-ubigraph.
 Regarding expression tree: the problem is Ubigraph doesn't know anything
 about the tree. It uses physical simulation to determine the optimum graph
 layout, the Mult node has the most links attached to it, that's why it's
 located at the center of the graph. As far as I can tell from Ubigraph docs,
 this cannot be tweaked. Theoretically one can change the shape of the graph
 visualization by introducing invisible links and/or nodes.

 And no, there's no way to tweak the vacuum-ubigraph output without
 modifying its code.

 Thanks,
 Ozgur Akgun




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


Re: [Haskell-cafe] ANN: Monad.Reader Issue 16

2010-05-12 Thread Richard O'Keefe


On May 13, 2010, at 6:12 AM, Brent Yorgey wrote:


I am very pleased to announce that Issue 16 of The Monad.Reader is now
available [1].


I am very pleased to receive it, and deeply grateful to
John Lato for his Iteratee article.  Many thanks!





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


Re: [Haskell-cafe] ANN: Monad.Reader Issue 16

2010-05-12 Thread Edward Z. Yang
Excerpts from Brent Yorgey's message of Wed May 12 14:12:53 -0400 2010:
 I am very pleased to announce that Issue 16 of The Monad.Reader is now
 available [1].

Excellent news!  Looking forward to reading.

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


[Haskell-cafe] debugging a hanging program: where to start?

2010-05-12 Thread Aran Donohue
Hi Cafe,

I have a program that I can reliably cause to hang. It's concurrent using
STM, so I think it could be a deadlock or related issue. I also do some IO,
so I think it could be blocking in a system call. It only hangs when
compiled with -threaded. I tried building with -prof, and running with -hc
-xt to get a clue where in which function it is stopping, but the resulting
profile didn't help much.

I've started sprinkling print statements, but I thought I'd trawl for better
tips and techniques. Any suggestions on approaches?

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


Re: [Haskell-cafe] debugging a hanging program: where to start?

2010-05-12 Thread Jason Dagit
On Wed, May 12, 2010 at 8:15 PM, Aran Donohue aran.dono...@gmail.comwrote:

 Hi Cafe,

 I have a program that I can reliably cause to hang. It's concurrent using
 STM, so I think it could be a deadlock or related issue. I also do some IO,
 so I think it could be blocking in a system call. It only hangs when
 compiled with -threaded. I tried building with -prof, and running with -hc
 -xt to get a clue where in which function it is stopping, but the resulting
 profile didn't help much.


Usually it's the other way around (hangs without threaded).  So, I would
guess that you're experiencing some sort of deadlock issue.


 I've started sprinkling print statements, but I thought I'd trawl for
 better tips and techniques. Any suggestions on approaches?


Try threadscope:
http://research.microsoft.com/en-us/projects/threadscope/

I haven't used it myself but I've heard it's *the* tool for investigating
parallel program behavior for haskell programs.

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


Re: [Haskell-cafe] ANN: Monad.Reader Issue 16

2010-05-12 Thread David Leimbach
On Wed, May 12, 2010 at 7:24 PM, Edward Z. Yang ezy...@mit.edu wrote:

 Excerpts from Brent Yorgey's message of Wed May 12 14:12:53 -0400 2010:
  I am very pleased to announce that Issue 16 of The Monad.Reader is now
  available [1].

 Excellent news!  Looking forward to reading.


I'm trying the Iteratee examples, and everything is fine in this issue up to
the point where it gets to IO and the lifting.  I'm afraid my brain must be
too small for figuring out the right syntax to make the 'throbber' do
anything.

Dave



 Cheers,
 Edward
 ___
 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] corner case in Text.JSON 0.4.3

2010-05-12 Thread Don Stewart
martin:
 hi,

 since i got no answer from the maintainer, maybe someone else can take  
 care of it, or at least point out, what i did wrong.

 so, i recently stumbled upon some error while using Text.JSON 0.4.3 [1]:

   Text/JSON/String.hs:(127,4)-(137,49): Non-exhaustive patterns in case

 indeed ghc warned:

   [5 of 7] Compiling Text.JSON.String ( Text/JSON/String.hs,  
 dist/build/Text/JSON/String.o )

   Text/JSON/String.hs:127:4:
   Warning: Pattern match(es) are non-exhaustive
In a case alternative: Patterns not matched: []

 from looking at the code i couldn't see how this would ever happen, but  
 you can reproduce it be running the files from [2]:

   $ ./test  problem
   Ok (JSArray [JSString (JSONString {fromJSString = this}),JSString  
 (JSONString {fromJSString = is}),JSString (JSONString {fromJSString =  
 some}),JSString (JSONString {fromJSString = json}),JSObject  
 (JSONObject {fromJSObject = [(that,JSString (JSONString {fromJSString  
 = works}))]})])
 test: Text/JSON/String.hs:(127,4)-(137,49): Non-exhaustive patterns in case

 the patch i put there fixes it (at least for me) to return an Error  
 instead of dying:

   $ ./test  problem
   Ok (JSArray [JSString (JSONString {fromJSString = this}),JSString  
 (JSONString {fromJSString = is}),JSString (JSONString {fromJSString =  
 some}),JSString (JSONString {fromJSString = json}),JSObject  
 (JSONObject {fromJSObject = [(that,JSString (JSONString {fromJSString  
 = works}))]})])
   Error Unexpected end of String: does
   Error Malformed JSON: invalid token in this context not\]
   test: stdin: hGetLine: end of file

 have fun
 martin hilbig

 [1]: http://hackage.haskell.org/package/json
 [2]: http://friendpaste.com/3IvnChRMoczf0mIKpOtrYE

Send me the patch :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe