[Haskell-cafe] Capturing the parent element as I parse XML using parsec

2012-07-29 Thread C K Kashyap
Hi,

With the help of the cafe I've been able to write up the xml parser using
parsec -
https://github.com/ckkashyap/really-simple-xml-parser/blob/master/RSXP.hs

I am struggling with an idea though - How can I capture the parent element
of each element as I parse? Is it possible or would I have to do a second
pass to do the fixup?

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


[Haskell-cafe] Current state of garbage collection in Haskell

2012-07-29 Thread C K Kashyap
Hi,
I was looking at a video that talks about GC pauses. That got me curious
about the current state of GC in Haskell - say ghc 7.4.1.
Would it suffer from lengthy pauses when we talk about memory in the range
of 500M +?
What would be a good way to keep abreast with the progress on haskell GC?
Regards,
Kashyap
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Explaining instance declarations

2012-07-29 Thread Patrick Browne
{- I am trying to understand and provide a *simplified* explanation of instance contexts and their relationship with class hierarchies. I use the example from [1]. Are the following two sentences and annotated code a reasonable explanation?  When instantiating an instance I of C, its context must be at the same level or lower than the context of any instance of any super-class of C.  The purpose of this rule is to guarantee that the required super-class methods exist. [1] 4.3.2  Instance Declarations http://www.haskell.org/onlinereport/haskell2010/haskellch4.htmlClass hierarchy 
Eq1   Show1       Foo   
     \ /                |
     \   /                  |
    Num1               Bar
       |
       |
    Num2-}class Foo a whereclass Show1 a whereclass Foo a = Bar a whereclass Eq1 a where-- Eq1 and Show1 are super-classes of Num1 and Num2.class (Eq1 a, Show1 a) = Num1 aclass Num1 a = Num2 a -- We must make an instance of Foo [a], before we can have instance Bar [a]instance (Num1 a) = Foo [a] where -- But that instance of Foo [a] depends on a being a member of Num1-- Hence Bar[a] can only be defined if their exists Num1 a-- But Eq1  Show1 are super classes of Num1-- The following context causes an *error*, because the context is weaker than required-- instance (Eq1 a, Show1 a) = Bar [a] where-- But this is OKinstance (Num1 a) = Bar [a] where-- Also, this would be OK-- instance (Num2 a) = Bar [a] where
 Tá an teachtaireacht seo scanta ó thaobh ábhar agus víreas ag Seirbhís Scanta Ríomhphost de chuid Seirbhísí Faisnéise, ITBÁC agus meastar í a bheith slán.  http://www.dit.ie
This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean.  http://www.dit.ie



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


[Haskell-cafe] Munich Haskell Meeting

2012-07-29 Thread Heinrich Hördegen

Dear all,

next Tuesday, 31st of July, at 19h30, Munich's functional programming 
enthusiasts will meet at Max-Emanuell-Brauerei. If the weather is fine, 
we will sit outside. If you plan to join, please go to:


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

and click the button.

Heinrich

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


Re: [Haskell-cafe] How to define a Monad instance

2012-07-29 Thread Johan Holmquist
As for understanding monads, you can try to define the State monad
[1]. Not sure if it's the best example but it's intuitive in that it
let's you thread a state behind the scenes.

***

Not related to your question -- in your example if you want to
translate characters but do not plan to change the length of the
input, you don't need Maybe. Your 'table' can then be defined as:

table :: Char - Char
table 'a' = 'b'
table 'A' = 'B'
table x  = x

Then your 'replaceAll' is simply 'map':

replaceAll = map

/Johan

[1] 
http://hackage.haskell.org/packages/archive/mtl/2.1.2/doc/html/Control-Monad-State-Lazy.html

2012/7/28 Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de:
 On 07/28/2012 03:35 PM, Thiago Negri wrote:
 [...]

 As Monads are used for sequencing, first thing I did was to define the
 following data type:

 data TableDefinition a = Match a a (TableDefinition a) | Restart


 So TableDefinition a is like [(a, a)].

 [...]



 So, to create a replacement table:

 table' :: TableDefinition Char
 table' =
  Match 'a' 'b'
  (Match 'A' 'B'
   Restart)

 It look like a Monad (for me), as I can sequence any number of
 replacement values:

 table'' :: TableDefinition Char
 table'' = Match 'a' 'c'
   (Match 'c' 'a'
   (Match 'b' 'e'
   (Match 'e' 'b'
Restart)))


 Yes, but monads aren't just about sequencing. I like to see a monad as a
 generalized computation (e.g. nondeterministic, involving IO, involving
 state etc). Therefore, you should ask yourself if TableDefinition can be
 seen as some kind of abstract computation. In particular, can you
 execute a computation and extract its result? as in

   do
 r - Match 'a' 'c' Restart
 if r == 'y' then Restart else Match 2 3 (Match 3 4 Restart)

 Doesn't immediately make sense to me. In particular think about the
 different possible result types of a TableDefinition computation.

 If all you want is sequencing, you might be looking for a Monoid instance
 instead, corresponding to the Monoid instance of [b], where b=(a,a) here.

  [...]



 I'd like to define the same data structure as:

 newTable :: TableDefinition Char
 newTable = do
  'a' :  'b'
  'A' :  'B'

 But I can't figure a way to define a Monad instance for that. :(


 The desugaring of the example looks like this:

   ('a' : 'b')  ('A' : 'B')

 Only () is used, but not (=) (i.e. results are always discarded). If
 this is the only case that makes sense, you're probably looking for a Monoid
 instead (see above)

 -- Steffen


 ___
 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] Current state of garbage collection in Haskell

2012-07-29 Thread Alexander Solla
On Sun, Jul 29, 2012 at 12:52 AM, C K Kashyap ckkash...@gmail.com wrote:

 Hi,
 I was looking at a video that talks about GC pauses. That got me curious
 about the current state of GC in Haskell - say ghc 7.4.1.
 Would it suffer from lengthy pauses when we talk about memory in the range
 of 500M +?
 What would be a good way to keep abreast with the progress on haskell GC?
 Regards,
 Kashyap


Have you read the latest GHC manual pages?[1]  It has a list of options,
suggestions, gotchas, etc.  I haven't read the GHC specific mailing lists,
but cvs-ghc sounds like where you might get real-time updates.

[1](
http://www.haskell.org/ghc/docs/latest/html/users_guide/runtime-control.html#rts-options-gc
)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Capturing the parent element as I parse XML using parsec

2012-07-29 Thread Antoine Latter
On Sun, Jul 29, 2012 at 1:21 AM, C K Kashyap ckkash...@gmail.com wrote:
 Hi,

 With the help of the cafe I've been able to write up the xml parser using
 parsec -
 https://github.com/ckkashyap/really-simple-xml-parser/blob/master/RSXP.hs

 I am struggling with an idea though - How can I capture the parent element
 of each element as I parse? Is it possible or would I have to do a second
 pass to do the fixup?


What are you trying to do? Maybe you could give an example of what
you'd like to produce?

Generally speaking, having tree elements in a Haskell datatype point
to their parent and their children is asking for trouble - it means
you can't change any part of the tree without re-building the entire
tree (otherwise your parent pointers point to the parent in the old
version of the tree).

If you're interested in complex traversals and transformation of XML
trees, I like the cursor API here:
http://hackage.haskell.org/packages/archive/xml/1.3.12/doc/html/Text-XML-Light-Cursor.html

HaXML is also popular for whole-tree queries and transformations.

Antoine

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


[Haskell-cafe] GHC rendering of non-ASCII characters configurable?

2012-07-29 Thread Richard Cobbe
I'm working on an application that involves processing a lot of Unicode
data, and I'm finding the built-in Show implementation for Char to be
really inconvenient.  Specifically, it renders all characters at U+0080 and
above with decimal escapes:

Prelude '\x80'
'\128'

This is annoying because all of the Unicode charts give the code points in
hex, and indeed the charts are split into different PDFs at numbers that
are nice and round in hex but not in decimal.  So in order to figure out
which character I'm looking at, I have to convert back to hex and then look
it up in the charts.

Is there any way to ask GHC to render super-ASCII characters with their
hexadecimal escapes, instead?  I'm perfectly happy to write my own custom
Show instance, but I don't know how to hook that into ghci's REPL (or, for
that matter, the routines that HUnit uses to generate the messages on
failed tests, etc.).

I'm using GHC 7.4.1 on MacOS 10.7.4.

Thanks,

Richard

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


Re: [Haskell-cafe] Logging pure code

2012-07-29 Thread Joey Adams
On Fri, Jul 27, 2012 at 9:52 AM, Marco Túlio Gontijo e Silva
marcotmar...@gmail.com wrote:
 I thought that the only thing I needed to take care while using
 unsafePerformIO was knowing that the time of execution is undetermined
 and that it could even run more than once.  This is not a problem for
 my logging.  Is there something else I should be aware while using
 unsafePerformIO?

Another thing to be aware of is that unsafePerformIO and STM don't
interact well.  In particular, STM will abort doomed transactions.  If
the transaction is IO that has exception handlers set up, those
handlers won't be run.  This is the case for unsafeIOToSTM, but I'm
not sure if it's the case for unsafePerformIO as well.

Are you using STM in your program?  Also, what version of GHC are you using?

-Joey

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


Re: [Haskell-cafe] Current state of garbage collection in Haskell

2012-07-29 Thread Thomas Schilling
GHC does not provide any form of real-time guarantees (and support for
them is not planned).

That said, it's not as bad as it sounds:

 - Collecting the first (young) generation is fast and you can control
the size of that first generation via runtime system (RTS) options.

 - The older generation is collected rarely and can be collected in parallel.

 - You can explicitly invoke the GC via System.Mem.performGC

In a multi-threaded / multi-core program collecting the first
generation still requires stopping all application threads even though
only one thread (CPU) will perform GC (and having other threads help
out usually doesn't work out due to locality issues). This can be
particularly expensive if the OS decides to deschedule an OS thread,
as then the GHC RTS has to wait for the OS. You can avoid that
particular problem by properly configuring the OS via (linux boot
isolcpus=... and taskset(8)). The GHC team has been working on a
independent *local* GC, but it's unlikely to make it into the main
branch at this time. It turned out to be very difficult to implement,
with not large enough gains. Building a fully-concurrent GC is
(AFAICT) even harder.

I don't know how long the pause times for your 500MB live heap would
be. Generally, you want your heap to be about twice the size of your
live data. Other than that it depends heavily on the characteristics
of you heap objects. E.g., if it's mostly arrays of unboxed
non-pointer data, then it'll be very quick to collect (since the GC
doesn't have to do anything with the contents of these arrays). If
it's mostly many small objects with pointers to other objects, GC will
be very expensive and bound by the latency of your RAM. So, I suggest
you run some tests with realistic heaps.

Regarding keeping up, Simon Marlow is the main person working on GHC's
GC (often collaborating with others) and he keeps a list of papers on
his homepage: http://research.microsoft.com/en-us/people/simonmar/

If you have further questions about GHC's GC, you can ask them on the
glasgow-haskell-us...@haskell.org mailing list (but please consult the
GHC user's guide section on RTS options first).

HTH

On 29 July 2012 08:52, C K Kashyap ckkash...@gmail.com wrote:
 Hi,
 I was looking at a video that talks about GC pauses. That got me curious
 about the current state of GC in Haskell - say ghc 7.4.1.
 Would it suffer from lengthy pauses when we talk about memory in the range
 of 500M +?
 What would be a good way to keep abreast with the progress on haskell GC?
 Regards,
 Kashyap

 ___
 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


Re: [Haskell-cafe] Logging pure code

2012-07-29 Thread Marco Túlio Gontijo e Silva
Hi Joey.

Thanks for your answer.

On Sun, Jul 29, 2012 at 3:16 PM, Joey Adams joeyadams3.14...@gmail.com wrote:
 On Fri, Jul 27, 2012 at 9:52 AM, Marco Túlio Gontijo e Silva
 marcotmar...@gmail.com wrote:
 I thought that the only thing I needed to take care while using
 unsafePerformIO was knowing that the time of execution is undetermined
 and that it could even run more than once.  This is not a problem for
 my logging.  Is there something else I should be aware while using
 unsafePerformIO?

 Another thing to be aware of is that unsafePerformIO and STM don't
 interact well.  In particular, STM will abort doomed transactions.  If
 the transaction is IO that has exception handlers set up, those
 handlers won't be run.  This is the case for unsafeIOToSTM, but I'm
 not sure if it's the case for unsafePerformIO as well.

 Are you using STM in your program?  Also, what version of GHC are you using?

No, not in my program.  Maybe a library that I use uses it, but not
that I'm aware of.  I'm using GHC version 7.4.1, I'll try it with
7.4.2 later.

Greetings!
(...)
-- 
marcot
http://marcot.eti.br/

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


Re: [Haskell-cafe] Capturing the parent element as I parse XML using parsec

2012-07-29 Thread Richard O'Keefe

On 29/07/2012, at 6:21 PM, C K Kashyap wrote:
 I am struggling with an idea though - How can I capture the parent element of 
 each element as I parse? Is it possible or would I have to do a second pass 
 to do the fixup?

Why do you *want* the parent element of each element?
One of the insanely horrible aspects of the Document Object Model is that every
element is nailed in place by pointers everywhere, with the result that you
cannot share elements, and even moving an element was painful.
I still do a fair bit of SGML/XML process in C using a Document Value Model
library that uses hash consing, and it's so much easier it isn't funny.

While you are traversing a document tree it is useful to keep track of the
path from the root.  Given

data XML
   = Element String [(String,String)] [XML]
   | Text String

you do something like

traverse :: ([XML] - [a] - a) - ([XML] - String - a) - XML - a
traverse f g xml = loop [] xml
  where loop ancs (Text s)   = g ancs  s
loop ancs e@(Element _ _ ks) = f ancs' (map (loop ancs') ks)
   where ancs' = e:ancs

(This is yet another area where Haskell's non-strictness pays off.)
If you do that, then you have the parent information available without
it being stored in the tree.





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


Re: [Haskell-cafe] Logging pure code

2012-07-29 Thread Thomas Schilling
On 27 July 2012 14:52, Marco Túlio Gontijo e Silva
marcotmar...@gmail.com wrote:
 thread blocked indefinitely in an MVar operation

IIRC, that means that a thread is blocked on an MVar and the MVar is
only reachable by that thread.  You said you tried adding NOINLINE,
which is usually required for unsafePerformIO. Did you make sure to
recompile everything from scratch after doing so? Other than that, you
may ask on the glasgow-haskell-users mailing list as this is read more
frequently by the GHC team.

/ Thomas
-- 
Push the envelope. Watch it bend.

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


Re: [Haskell-cafe] Is (==) commutative?

2012-07-29 Thread wren ng thornton

On 7/24/12 9:19 PM, Christian Sternagel wrote:

Dear all,

Thanks for your replies. Just to clarify: I am fully aware that inside
Haskell there is no guarantee that certain (intended) requirements on
type class instances are satisfied. I was asking whether the intention
for Eq is that (==) is commutative, because if it was, I would require
that as an axiom for the equivalent of Eq in our formal setting (I'm
using the proof assistant Isabelle/HOLCF [1]). Afterwards only types for
which one could prove commutativity could be instances of Eq. But if
there where already standard instances which violated this
requirement, adding it in the formal setting would prevent it from being
applicable to standard Haskell programs.


Indeed, the standard wisdom is that Eq ought to denote an equivalence 
relation.


However, the instance for Double and Float is not an equivalence 
relation. This is necessary due to Double/Float vaguely matching the 
IEEE-754 spec which requires that NaN /= NaN. If NaN is removed, I think 
Double/Float ought to behave as desired--- though there was a recent 
kerfluffle about the fact that the CPU-internal representation of 
Double/Float has more bits of precision than the in-memory 
representation, so vagaries about when values leave registers to be 
stored in memory will affect whether two values come out to be equal or 
not. Not to mention that Float/Double violate numerous laws of other 
classes; e.g., Ord is not a total ordering because of NaN; Num is not a 
ring because addition and multiplication are not associative (they are 
commutative though);...


Depending on what your goals are, it may be best to avoid the entire 
cesspool of floating point numbers. It would limit the applicability of 
your work, though if analysis of number crunching isn't your goal then 
it's a legitimately pragmatic option.



Another point to bear in mind is that even though Eq is widely 
recognized as denoting an equivalence relation, people sometimes 
willfully subvert this intention. I'm thinking in particular of the fact 
that the Num class has, until recently, required an Eq instance--- which 
in turn precludes some useful/cute Num instances like lifting Num 
operations over (Num b = a - b), or implementing powerseries as 
infinite lists, etc.


--
Live well,
~wren

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


Re: [Haskell-cafe] Is (==) commutative?

2012-07-29 Thread wren ng thornton

On 7/24/12 9:19 PM, Christian Sternagel wrote:

(x == y) = True == x = y
(x == y) = False == not (x = y)
(x == _|_) = _|_
(_|_ == y) = _|_

Those axioms state that (==) is sound w.r.t. to meta-equality and strict
in both it's arguments.


An immediate problem that arises here is: what exactly does 
meta-equality denote in Isabelle/HOLCF? If it is meant to denote 
syntactic identity or Leibniz equality a la Coq, then the first axiom is 
certainly too strong for any interesting data types (e.g., Rational, 
Data.Set, Data.Map, Data.IntSet,...)


While Eq is intended to denote an equivalence relation, it is just that; 
it is not an equality relation. This means you should be treating Eq as 
defining a setoid (or partial setoid, for instances like Double/Float). 
That is, you must distinguish between the raw type and the type 
quotiented by its (==). The containers libraries have taken pains to try 
and ensure that the difference cannot be observed within Haskell, but 
not all instances are so doctrinaire.


--
Live well,
~wren

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


Re: [Haskell-cafe] Reddy on Referential Transparency

2012-07-29 Thread wren ng thornton

On 7/27/12 1:49 PM, Ross Paterson wrote:

So a language is referentially transparent if replacing a sub-term with
another with the same denotation doesn't change the overall meaning?
But then isn't any language RT with a sufficiently cunning denotational
semantics?  Or even a dumb one that gives each term a distinct denotation.


Yes, but such denotations aren't useful for very much. The whole point 
of denotational semantics is to assert that some (primitive) expressions 
denote the same thing, and then to derive that other expressions (e.g., 
whole programs) denote the same thing. If we say that every expression 
is different from every other expression, then ---for example--- the 
only semantics-preserving transformation is the identity transformation. 
Our semantics is, thus, worthless for vetting whether a compiler's 
transformation is okay or not. In fact, this model explains exactly 
nothing about the *meaning* of those expressions.


--
Live well,
~wren

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