Re: [Haskell-cafe] efficient chop

2011-09-13 Thread Daniel Gorín
On Sep 14, 2011, at 5:29 AM, Kazu Yamamoto (山本和彦) wrote:

> Hello,
> 
> Of course, I use ByteString or Text for real programming. But I would
> like to know whether or not there are any efficient methods to remove
> a tail part of a list.
> 
> --Kazu

In that case, I would prefer this version, since it is lazier:

lazyChop :: String -> String
lazyChop s = pref ++ if null s' then [] else (mid_sp ++ lazyChop s')
  where
(pref,sp_suf) = break isSpace s
(mid_sp,s')   = span isSpace sp_suf

By "lazier" I mean:

*Main> chopReverse $ "hello world " ++ undefined
"*** Exception: Prelude.undefined
*Main> chopFoldr $ "hello world " ++ undefined
"*** Exception: Prelude.undefined
*Main> lazyChop $ "hello world " ++ undefined
"hello world*** Exception: Prelude.undefined

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


Re: [Haskell-cafe] regex-applicative library needs your help! (algorithmic challenge)

2011-09-13 Thread Roman Cheplyaka
* Eugene Kirpichov  [2011-09-14 08:38:10+0400]
> Hi,
> I don't see how fallback to NFA simulation is really a failure wrt DoS
> attacks. It's not exponential in time or memory, just linear memory
> (in size of regex) instead of constant, and slower than DFA.

Hi Eugene, thanks for pointing that out.

Indeed, I now see that he uses breadth-first rather than depth-first
search. Then he has the same problem as I do. I shall study his code
more closely.

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

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


Re: [Haskell-cafe] [Haskell] [ANNOUNCE] Haskdogs-0.1

2011-09-13 Thread Ivan Lazar Miljenovic
Re-cc'ing -cafe:

On 14 September 2011 14:29, yi huang  wrote:
> On Wed, Sep 14, 2011 at 11:32 AM, Ivan Lazar Miljenovic
>  wrote:
>>
>> On 14 September 2011 13:27, yi huang  wrote:
>> > On Wed, Sep 14, 2011 at 10:18 AM, Ivan Lazar Miljenovic
>> >  wrote:
>> >>
>> >> On 14 September 2011 11:24, yi huang  wrote:
>> >> > Cabal compains about "Unknown build tool hasktags".
>> >> > It seems not necessary to set "Build-tools: hasktags" in cabal file?
>> >>
>> >> cabal-install isn't capable of automatically building and installing
>> >> build-tools for you.  So to install haskdogs, you need to do "cabal
>> >> install hasktags && cabal install haskdogs".
>> >
>> > I have installed hasktags, and .cabal/bin is in my PATH, i can run
>> > hasktags
>> > directly from shell.
>> > What else did i miss?
>>
>> How did you specify your PATH?  You can't use ~/.cabal/bin, you need
>> either $HOME/.cabal/bin or the fully expanded path.
>
> It is $HOME/.cabal/bin , and `which hasktags' can find it without problem.
> Cabal 1.10.2, ghc 7.0.4, i'm trying to look into cabal source to find the
> problem.

Actually... looks like you're right.  I can't build it either, he
appears to have hard-coded some paths in and it appears that you need
some kind of magic to register a program as a build tool (that's what
the error is from: hasktags isn't a registered build-tool).

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] regex-applicative library needs your help! (algorithmic challenge)

2011-09-13 Thread Eugene Kirpichov
Hi,
I don't see how fallback to NFA simulation is really a failure wrt DoS
attacks. It's not exponential in time or memory, just linear memory
(in size of regex) instead of constant, and slower than DFA.

On Wed, Sep 14, 2011 at 1:29 AM, Roman Cheplyaka  wrote:
> * Chris Kuklewicz  [2011-09-13 08:21:55+0100]
>> I wrote regex-tdfa, the efficient (though not yet lightning fast) Posix-like 
>> engine.
>>
>> You are not the first to want an efficient Perl-like engine.  The answer you
>> seek flows from Russ Cox (though in C++):
>>
>> > http://google-opensource.blogspot.com/2010/03/re2-principled-approach-to-regular.html
>>
>> > http://code.google.com/p/re2/
>>
>> Quoting relevant bit:
>>
>> > It also finds the leftmost-first match, the same match that Perl would, and
>> > can return submatch information. The one significant exception is that RE2
>> > drops support for backreferences¹ and generalized zero-width assertions,
>> > because they cannot be implemented efficiently.
>
> Hi Chris, thanks for the response.
>
> There's one thing about Cox's work that I don't understand. On the
> page [1] he mentions that the algorithm falls back to direct NFA
> simulation (search for "If all else fails" on that page).
> This defeats his goal of defending against DoS attacks (the second
> paragraph of that page).
>
> And I wouldn't be comfortable with an algorithm that is worst-case
> exponential either.
>
> Then there's another issue: I specifically want a combinator library,
> and not every automaton-based algorithm can serve this purpose in a
> statically typed language (unless there's some clever trick I don't
> know).
>
> [1]: http://swtch.com/~rsc/regexp/regexp3.html
>
> --
> Roman I. Cheplyaka :: http://ro-che.info/
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Eugene Kirpichov
Principal Engineer, Mirantis Inc. http://www.mirantis.com/
Editor, http://fprog.ru/

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


Re: [Haskell-cafe] efficient chop

2011-09-13 Thread Ivan Lazar Miljenovic
On 14 September 2011 13:29, Kazu Yamamoto  wrote:
> Hello,
>
> Of course, I use ByteString or Text for real programming. But I would
> like to know whether or not there are any efficient methods to remove
> a tail part of a list.

I doubt it; lists aren't that great a data type if you want to keep
manipulating the end all the time.  You'd have more luck with a
Sequence or some other data type.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] efficient chop

2011-09-13 Thread 山本和彦
Hello,

Of course, I use ByteString or Text for real programming. But I would
like to know whether or not there are any efficient methods to remove
a tail part of a list.

--Kazu

From: Thomas DuBuisson 
Subject: Re: [Haskell-cafe] efficient chop

> This was a recent question on StackOverflow:
> 
> http://stackoverflow.com/questions/6270324/in-haskell-how-do-you-trim-whitespace-from-the-beginning-and-end-of-a-string/6270382#6270382
> 
> Where I started:
> 
> If you have serious text processing needs then use the text package
> from hackage.
> 
> And concluded:
> 
> A quick Criterion benchmark tells me that (for a particularly long
> string of words with spaces and ~200 pre and post spaces) my trim
> takes 1.6 ms, the trim using reverse takes 3.5ms, and Data.Text.strip
> takes 0.0016 ms.
> 
> Cheers,
> Thomas
> 
> On Tue, Sep 13, 2011 at 8:03 PM, Kazu Yamamoto  wrote:
>> Hello Cafe,
>>
>> I would like to have an efficient implementation of the chop function.
>> As you guess, the chop function drops spaces in the tail of a list.
>>
>>   chop " foo  bar baz   "
>>   ->   " foo  bar baz"
>>
>> A naive implementation is as follows:
>>
>>    chopReverse :: String -> String
>>    chopReverse = reverse . dropWhile isSpace . reverse
>>
>> But this is not elegant. foldr version is as follows:
>>
>>    chopFoldr :: String -> String
>>    chopFoldr = foldr f []
>>      where
>>        f c []
>>          | isSpace c = []
>>          | otherwise = c:[]
>>        f c cs = c:cs
>>
>> But this code is slower than chopReverse in some cases.
>>
>> Are there any more efficient implementations of chop? Any suggestions?
>>
>> --Kazu
>>
>> ___
>> 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] efficient chop

2011-09-13 Thread Thomas DuBuisson
This was a recent question on StackOverflow:

http://stackoverflow.com/questions/6270324/in-haskell-how-do-you-trim-whitespace-from-the-beginning-and-end-of-a-string/6270382#6270382

Where I started:

If you have serious text processing needs then use the text package
from hackage.

And concluded:

A quick Criterion benchmark tells me that (for a particularly long
string of words with spaces and ~200 pre and post spaces) my trim
takes 1.6 ms, the trim using reverse takes 3.5ms, and Data.Text.strip
takes 0.0016 ms.

Cheers,
Thomas

On Tue, Sep 13, 2011 at 8:03 PM, Kazu Yamamoto  wrote:
> Hello Cafe,
>
> I would like to have an efficient implementation of the chop function.
> As you guess, the chop function drops spaces in the tail of a list.
>
>   chop " foo  bar baz   "
>   ->   " foo  bar baz"
>
> A naive implementation is as follows:
>
>    chopReverse :: String -> String
>    chopReverse = reverse . dropWhile isSpace . reverse
>
> But this is not elegant. foldr version is as follows:
>
>    chopFoldr :: String -> String
>    chopFoldr = foldr f []
>      where
>        f c []
>          | isSpace c = []
>          | otherwise = c:[]
>        f c cs = c:cs
>
> But this code is slower than chopReverse in some cases.
>
> Are there any more efficient implementations of chop? Any suggestions?
>
> --Kazu
>
> ___
> 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] efficient chop

2011-09-13 Thread 山本和彦
Hello Cafe,

I would like to have an efficient implementation of the chop function.
As you guess, the chop function drops spaces in the tail of a list.

   chop " foo  bar baz   "
   ->   " foo  bar baz"

A naive implementation is as follows:

chopReverse :: String -> String
chopReverse = reverse . dropWhile isSpace . reverse

But this is not elegant. foldr version is as follows:

chopFoldr :: String -> String
chopFoldr = foldr f []
  where
f c []
  | isSpace c = []
  | otherwise = c:[]
f c cs = c:cs

But this code is slower than chopReverse in some cases.

Are there any more efficient implementations of chop? Any suggestions?

--Kazu

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


Re: [Haskell-cafe] Tupling functions

2011-09-13 Thread Casey McCann
On Tue, Sep 13, 2011 at 10:03 PM, Chris Smith  wrote:
> Ah, okay... then sure, you can do this:
>
> class Tuple a b c | a b -> c where
>    tuple :: a -> b -> c
>
> instance Tuple (a -> b, a -> c) a (b,c) where
>    tuple (f,g) x = (f x, g x)

This wouldn't actually work well in practice. There's no dependency
between the various occurrences of "a" in the types, so unless they're
already known to be the same, GHC will complain about an ambiguous
instance (please excuse the silly GHCi prompt):

Ok, modules loaded: Tupling.
∀x. x ⊢ tuple ((+3), show) 4

:0:1:
No instance for (Tuple (a0 -> a0, a1 -> String) b0 c0)
  arising from a use of `tuple'

Given that the class is only intended to be used where those types are
equal, you really want it to unify them based on use of the tuple
function.

> and so on...  You'll need fundeps (or type families if you prefer to
> write it that way), and probably at least flexible and/or overlapping
> instances, too, but of course GHC will tell you about those.

I rather prefer type families in this case, both because the problem
is easily expressed in "type function" style, and because it gives you
an easy type equality constraint to use, rather than using arcane
trickery with overlaps to force post-hoc unification. We'd probably
want to do something like this:

class Tuple t where
type Arg t :: *
type Result t :: *
tuple :: t -> Arg t -> Result t

instance (x1 ~ x2) => Tuple (x1 -> a, x2 -> b) where
type Arg (x1 -> a, x2 -> b) = x1
type Result (x1 -> a, x2 -> b) = (a, b)
tuple (f, g) x = (f x, g x)

instance (x1 ~ x2, x2 ~ x3) => Tuple (x1 -> a, x2 -> b, x3 -> c) where
type Arg (x1 -> a, x2 -> b, x3 -> c) = x1
type Result (x1 -> a, x2 -> b, x3 -> c) = (a, b, c)
tuple (f, g, h) x = (f x, g x, h x)

Used like so:

Ok, modules loaded: Tupling.
∀x. x ⊢ tuple ((+2), show, (< 2)) 3
(5,"3",False)

Note that not only does this avoid ambiguity, it even unifies
ambiguous types that are then defaulted by the usual means.

That said, I question the utility of a class like this. The
boilerplate instances are tedious to write and it's not flexible in
any way; tuples not being defined inductively makes them a real pain
to work with unless there's a particularly good reason to do so.
Something equivalent to right-nested (,) with () as a terminator is
much more pleasant, and since we're deep in the pits of
non-portability anyway, might as well pull out bang patterns and
UNPACK pragmas if avoiding extra bottoms was the reason for using
plain tuples.

- C.

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


Re: [Haskell-cafe] [Haskell] [ANNOUNCE] Haskdogs-0.1

2011-09-13 Thread Ivan Lazar Miljenovic
On 14 September 2011 11:24, yi huang  wrote:
> Cabal compains about "Unknown build tool hasktags".
> It seems not necessary to set "Build-tools: hasktags" in cabal file?

cabal-install isn't capable of automatically building and installing
build-tools for you.  So to install haskdogs, you need to do "cabal
install hasktags && cabal install haskdogs".

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] Tupling functions

2011-09-13 Thread Chris Smith
On Wed, 2011-09-14 at 13:56 +1200, Richard O'Keefe wrote:
> I don't *expect* to implement anything just once.  I am perfectly
> happy writing as many instance declarations as I have tuple sizes
> that I care about.

Ah, okay... then sure, you can do this:

class Tuple a b c | a b -> c where
tuple :: a -> b -> c

instance Tuple (a -> b, a -> c) a (b,c) where
tuple (f,g) x = (f x, g x)

and so on...  You'll need fundeps (or type families if you prefer to
write it that way), and probably at least flexible and/or overlapping
instances, too, but of course GHC will tell you about those.

-- 
Chris Smith


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


Re: [Haskell-cafe] Tupling functions

2011-09-13 Thread Richard O'Keefe

On 14/09/2011, at 1:44 PM, Chris Smith wrote:

> On Wed, 2011-09-14 at 13:35 +1200, Richard O'Keefe wrote:
>> I would like to have
>> 
>>  tuple (f1,f2)   x = (f1 x, f2 x)
>>  tuple (f1,f2,f3)x = (f1 x, f2 x, f3 x)

> There is no polymorphism across tuple structures,

I know that.  I know how tuples get to be instances of Ix,
one instance declaration for each of (,) (,,) (,,,) 

> so if you absolutely
> *must* have n-tuples instead of nested 2-tuples, then you just need to
> implement the new functions as needed.  You can't implement that only
> once.

I don't *expect* to implement anything just once.  I am perfectly
happy writing as many instance declarations as I have tuple sizes
that I care about.  It's just that I can't see how to get the types
right, because in

class Thingy t ... where
tuple :: t -> a -> b

b depends on t and possibly a, so

instance Thingy (,,) where
tuple (f,g,h) x = (f x, g x, h x)

it's not an arbitrary b.  Can this be done with functional dependencies?





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


Re: [Haskell-cafe] Tupling functions

2011-09-13 Thread Chris Smith
On Wed, 2011-09-14 at 13:35 +1200, Richard O'Keefe wrote:
> I would like to have
> 
>   tuple (f1,f2)   x = (f1 x, f2 x)
>   tuple (f1,f2,f3)x = (f1 x, f2 x, f3 x)
>   tuple (f1,f2,f3,f4) x = (f1 x, f2 x, f3 x, f4 x)
>   ...
> 
> I'm aware of Control.Arrow and the &&& combinator, and I can use that
> instead, but f1 &&& f2 &&& f3 doesn't have _exactly_ the type I want.
> 
> What should I do?

There is no polymorphism across tuple structures, so if you absolutely
*must* have n-tuples instead of nested 2-tuples, then you just need to
implement the new functions as needed.  You can't implement that only
once.  Plenty of places in base do this, especially for instances.

-- 
Chris Smith



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


[Haskell-cafe] Tupling functions

2011-09-13 Thread Richard O'Keefe
I would like to have

tuple (f1,f2)   x = (f1 x, f2 x)
tuple (f1,f2,f3)x = (f1 x, f2 x, f3 x)
tuple (f1,f2,f3,f4) x = (f1 x, f2 x, f3 x, f4 x)
...

I'm aware of Control.Arrow and the &&& combinator, and I can use that
instead, but f1 &&& f2 &&& f3 doesn't have _exactly_ the type I want.

What should I do?


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


Re: [Haskell-cafe] [Haskell] [ANNOUNCE] Haskdogs-0.1

2011-09-13 Thread yi huang
Cabal compains about "Unknown build tool hasktags".
It seems not necessary to set "Build-tools: hasktags" in cabal file?

On Wed, Sep 14, 2011 at 4:39 AM, Sergey Mironov  wrote:

> Hi! I am pleased to announce haskdogs - project-level ctag file generator.
>
> haskdogs is a small shellscript-like tool which creates tag file for
> entire haskell project directory. It takes into account first-level
> dependencies by recursively scanning imports and adding matching
> packages to the final tag list. As a result, programmer can use
> his/her text editor supporting tags (vim, for example) to jump
> directly to definition of any standard or foreign function he/she
> uses. Note, that haskdogs calls some Unix shell commands like test or
> mkdir so this tool will likely fail to work on pure Windows platforms.
>
> To use it, do
>
> 0) cabal install hasktags haskdogs && mkdir -p ~/.cabal/var/haskdogs
> 1) cabal unpack TrickyProject-4.2 && cd TrickyProject-4.2
> 2) haskdogs
> 3) enjoy the tagfile with references to every function
>
> http://hackage.haskell.org/package/haskdogs-0.1
>
> Sergey
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



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


Re: [Haskell-cafe] Categorized Weaknesses from the State of Haskell 2011 Survey

2011-09-13 Thread Evan Laforge
I would appreciate is a few paragraphs in the toplevel haddock page or
module that describe the general architecture and layout of the
modules, as well as the typical entry points.  Since the module system
doesn't have a notion of private modules and it's common to re-export
symbols, it can be unclear where to start, which modules to look at,
and why it is the author chose that particular decomposition for the
functions.  Overall design and architecture is hard to get out of the
code.

I think the same goes for each module.  It's frustrating when I want
to figure out how something works, and each module just has a giant
chunk of license copy-paste at the top.

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


Re: [Haskell-cafe] Haskell 101 on classes .... duh ..... :^)

2011-09-13 Thread Vasili I. Galchin
Hi Brandon,

 Here is Ivan's web site. http://ivanmiljenovic.wordpress.com/  .. I
have written in Haskell before ... a POSIX Realtime hackage package. It is
true I am little rusty now  because industry is too stubborn except in
places like Silicon Valley, Wall Street, Virginia (defence industry) to use
FPLs ... have to pay the bills sadly...

Vasili


On Tue, Sep 13, 2011 at 9:57 AM, Brandon Allbery wrote:

> On Tue, Sep 13, 2011 at 00:08, Vasili I. Galchin wrote:
>
>>   I am trying to model multigraphs but getting errors with ghci
>> and can't figure out why I have a serious blind spot 
>>
>
> Why do you need to use classes for this?  (Note:  forget everything you
> know about classes from OOP.  Haskell typeclasses have approximately nothing
> to do with OOP.)
>
> junk1.hs:19:12:
>> Constructor `Arrow' should have 1 argument, but has been given 0
>> In the pattern: Arrow
>> In the definition of `source': source Arrow = fst Arrow
>> In the instance declaration for `Graph Arrow Int'
>>
>
> It's asking "Arrow *what*?"  You specified Arrow as taking a tuple
> argument; if you want to use it here, you need to provide that argument (or
> a placeholder, but in this case you clearly want the tuple).
>
> >   source (Arrow p) = fst p
> >   target (Arrow p) = snd p
>
> Or you can use pattern matching to deconstruct the tuple as well:
>
> >   source (Arrow (f,_)) = f
> >   target (Arrow (_,t)) = t
>
> --
> brandon s allbery  allber...@gmail.com
> wandering unix systems administrator (available) (412) 475-9364 vm/sms
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Categorized Weaknesses from the State of Haskell 2011 Survey

2011-09-13 Thread A.M.

On Sep 13, 2011, at 7:38 PM, Michael Orlitzky wrote:
> 
>> One thing I am puzzled about, is just how extremely difficult it must
>> be, to click on "Detailed documentation of the HaXml APIs" from the
>> HaXml homepage, look for a moment until you see
>> "Text.XML.HaXml.Parse" in the list of modules, click on it, and find,
>> right at the top of the page, a function that parses a String into an
>> XML document tree.
> 
> As someone who just wants to parse an XML file, here's what happens.
> First, I click on the API docs. I'm presented with a list:
> 
>* Text
>  o XML
>+ Text.XML.HaXml
>  # Text.XML.HaXml.ByteStringPP
>  # Text.XML.HaXml.Combinators
>  # DtdToHaskell
>* Text.XML.HaXml.DtdToHaskell.Convert
> 



I think you make an important point here. As a beginner myself, I am often 
surprised by the sparse first impression of modules that hackage offers. To a 
beginner, the one sentence introduction often using domain-specific language is 
thwarting. Compare hackage to CPAN or Sphinx documentation which present pages 
of examples covering all programmer-visible interfaces and the difference is 
clear: hackage is a module repository first and a documentation browser last.

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


Re: [Haskell-cafe] Categorized Weaknesses from the State of Haskell 2011 Survey

2011-09-13 Thread Michael Orlitzky
On 09/13/2011 05:15 PM, Malcolm Wallace wrote:
> 
> I am the first to admit that HaXml's documentation is not as good as
> it could be, and I am sorry that you have had a bad experience.

Sorry for the tirade =) That was a while ago, but I definitely felt some
sympathy for the guy in the quote.


> One thing I am puzzled about, is just how extremely difficult it must
> be, to click on "Detailed documentation of the HaXml APIs" from the
> HaXml homepage, look for a moment until you see
> "Text.XML.HaXml.Parse" in the list of modules, click on it, and find,
> right at the top of the page, a function that parses a String into an
> XML document tree.

As someone who just wants to parse an XML file, here's what happens.
First, I click on the API docs. I'm presented with a list:

* Text
  o XML
+ Text.XML.HaXml
  # Text.XML.HaXml.ByteStringPP
  # Text.XML.HaXml.Combinators
  # DtdToHaskell
* Text.XML.HaXml.DtdToHaskell.Convert
* Text.XML.HaXml.DtdToHaskell.Instance
* Text.XML.HaXml.DtdToHaskell.TypeDef
  # Text.XML.HaXml.Escape
  # Html
* Text.XML.HaXml.Html.Generate
* Text.XML.HaXml.Html.Parse
* Text.XML.HaXml.Html.ParseLazy
* Text.XML.HaXml.Html.Pretty
  # Text.XML.HaXml.Lex
  # Text.XML.HaXml.Namespaces
  # Text.XML.HaXml.OneOfN
  # Text.XML.HaXml.Parse
  # Text.XML.HaXml.ParseLazy
  # Text.XML.HaXml.Posn
  # Text.XML.HaXml.Pretty
  # Text.XML.HaXml.SAX
  # Schema
* Text.XML.HaXml.Schema.Environment
* Text.XML.HaXml.Schema.HaskellTypeModel
* Text.XML.HaXml.Schema.NameConversion
* Text.XML.HaXml.Schema.Parse
* Text.XML.HaXml.Schema.PrettyHaskell
* Text.XML.HaXml.Schema.PrimitiveTypes
* Text.XML.HaXml.Schema.Schema
* Text.XML.HaXml.Schema.TypeConversion
* Text.XML.HaXml.Schema.XSDTypeModel
  # Text.XML.HaXml.ShowXmlLazy
  # Text.XML.HaXml.TypeMapping
  # Text.XML.HaXml.Types
  # Text.XML.HaXml.Util
  # Text.XML.HaXml.Validate
  # Text.XML.HaXml.Verbatim
  # Text.XML.HaXml.Wrappers
  # Text.XML.HaXml.XmlContent
* Text.XML.HaXml.XmlContent.Haskell
* Text.XML.HaXml.XmlContent.Parser
  # Xtract
* Text.XML.HaXml.Xtract.Combinators
* Text.XML.HaXml.Xtract.Lex
* Text.XML.HaXml.Xtract.Parse


Jesus! /You/ know that I want to look in Text.XML.HaXml.Parse, but /I/
don't. Let's say I choose the first link: Text.XML.HaXml. It's a list of
modules, along with their documentation. All blank! Hitting the back button.

The first thing I notice is that there seems to be specialized parser
modules for different content types, e.g. Text.XML.HaXml.Html.Parse.
Maybe I want Text.XML.HaXml.Schema.Parse? I mean, I want to parse
something with a schema, right? Nope, it's for parsing XSDs.

How about Text.XML.HaXml.Util? This looks right...

  Only a small module containing some helper functions to extract xml
  content - I would have added this to Types but I've put it into an
  additional module - to avoid circular references (Verbatim - Types)

and it's got a function called docContent which is supposed to "Get the
main element of the document..." Great. Its type is,

  docContent :: i -> Document i -> Content i

so now, to have any hope of using this function (or figure out that I'm
in the wrong place entirely), I have to go figure out what those types
are. Document has one constructor,

  Document Prolog (SymTab EntityDef) (Element i) [Misc]

which leads me to,

  Prolog (Maybe XMLDecl) [Misc] (Maybe DocTypeDecl) [Misc]
XMLDecl VersionInfo (Maybe EncodingDecl) (Maybe SDDecl)
  type VersionInfo = String
  newtype EncodingDecl = EncodingDecl String
  type SDDecl = Bool
data Misc = Comment Comment | PI ProcessingInstruction
  type Comment = String
  type ProcessingInstruction = (PITarget, String)
type PITarget = String
data DocTypeDecl = DTD QName (Maybe ExternalID) [MarkupDecl]
  data QName = N Name | QN Namespace Name
type Name = String
data Namespace = Namespace {nsPrefix :: String, nsURI :: String}
  data External

Re: [Haskell-cafe] Categorized Weaknesses from the State of Haskell 2011 Survey

2011-09-13 Thread Eric Rasmussen
+1 for Heinrich Apfelmus's suggestion of cookbook recipes.

In other language communities I see a lot of "quickstart" guides designed to
help someone get up and running without a full understanding of what they're
doing, presumably with the hope that once they get started it will provide
the motivation to keep learning. But admittedly, and for good reason,
learning the how without the why seems to run counter to the general
mentality of the Haskell community.

For widely used libraries it'd be nice to a see a supporting wiki page
broken into sections like conceptual overview, how to navigate the API if
it's extensive, tutorials, and cookbook recipes. Motivating the community to
contribute supporting documentation could alleviate some of the burden for
library writers. Frequently updated and extensive community docs can also
help newcomers decide which library to start with for a given task, rather
than relying purely on Hackage descriptions. I'm slowly assembling
supporting docs of this kind for the libraries I use the most, and if anyone
is working on something similar I'm happy to help by trying out the
tutorials and giving feedback.

Thanks!
Eric



On Tue, Sep 13, 2011 at 2:15 PM, Malcolm Wallace wrote:

>
> On 13 Sep 2011, at 18:59, Michael Orlitzky wrote:
>
> >> Malcolm Wallace and Colin Runciman's ICFP99 paper functioned well as a
> >> tutorial for HaXml when I used it - maybe it is a bit out of date now?
> >> HaXml is hardly a dire case.
> >
> > The paper is out-of-date, so it's worse than useless: you'll waste your
> > time figuring out that it's wrong, and you still won't know how to do
> > anything.
> >
> > There's not one single example anywhere that just shows you how to read
> > or write a damned XML file.
> > If there were anything approaching a physical manifestation of HaXml, I
> > would've strangled it.
>
> I am the first to admit that HaXml's documentation is not as good as it
> could be, and I am sorry that you have had a bad experience.
>
> One thing I am puzzled about, is just how extremely difficult it must be,
> to click on "Detailed documentation of the HaXml APIs" from the HaXml
> homepage, look for a moment until you see "Text.XML.HaXml.Parse" in the list
> of modules, click on it, and find, right at the top of the page, a function
> that parses a String into an XML document tree.
>
> It is absolutely true that finding the reverse conversion (XML tree to
> String) is more obscure, being either the two-stage process of first using
> "Text.XML.HaXml.Pretty" to convert to a Doc, then
> "Text.PrettyPrint.HughesPJ" to render to a String; or alternatively the
> one-shot conversion in "Text.XML.HaXml.Verbatim".  Neither module name is as
> clear as it should be for a beginner, but I can't think of better ones.
>  Plus, it requires some knowledge of the ecosystem, for instance that
> pretty-printing is a common technique for producing textual output.
>
> In fact, my wish as a library author would be: please tell me what you, as
> a beginner to this library, would like to do with it when you first pick it
> up?  Then perhaps I could write a tutorial that answers the questions people
> actually ask, and tells them how to get the stuff done that they want to do.
>  I have tried writing documentation, but it seems that people do not know
> how to find, or use it.  Navigating an API you do not know is hard.  I'd
> like to signpost it better.
>
> Regards,
> Malcolm
>
> ___
> 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] regex-applicative library needs your help! (algorithmic challenge)

2011-09-13 Thread Roman Cheplyaka
* Roman Cheplyaka  [2011-09-14 00:29:55+0300]
> Then there's another issue: I specifically want a combinator library,
> and not every automaton-based algorithm can serve this purpose in a
> statically typed language (unless there's some clever trick I don't
> know).

Just to clarify: by "clever" trick I don't mean a "dirty" trick, like
using unsafeCoerce in frisby[1]. I guess I'm just too young and naive to
use that kind of stuff.

Glushkov automaton is nice because it can be used to implement parsing
combinators in pure Haskell + GADTs.

[1]: 
http://hackage.haskell.org/packages/archive/frisby/0.1/doc/html/src/Text-Parsers-Frisby.html

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

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


Re: [Haskell-cafe] regex-applicative library needs your help! (algorithmic challenge)

2011-09-13 Thread Roman Cheplyaka
* Chris Kuklewicz  [2011-09-13 08:21:55+0100]
> I wrote regex-tdfa, the efficient (though not yet lightning fast) Posix-like 
> engine.
> 
> You are not the first to want an efficient Perl-like engine.  The answer you
> seek flows from Russ Cox (though in C++):
> 
> > http://google-opensource.blogspot.com/2010/03/re2-principled-approach-to-regular.html
> 
> > http://code.google.com/p/re2/
> 
> Quoting relevant bit:
> 
> > It also finds the leftmost-first match, the same match that Perl would, and
> > can return submatch information. The one significant exception is that RE2
> > drops support for backreferences¹ and generalized zero-width assertions,
> > because they cannot be implemented efficiently.

Hi Chris, thanks for the response.

There's one thing about Cox's work that I don't understand. On the
page [1] he mentions that the algorithm falls back to direct NFA
simulation (search for "If all else fails" on that page).
This defeats his goal of defending against DoS attacks (the second
paragraph of that page).

And I wouldn't be comfortable with an algorithm that is worst-case
exponential either.

Then there's another issue: I specifically want a combinator library,
and not every automaton-based algorithm can serve this purpose in a
statically typed language (unless there's some clever trick I don't
know).

[1]: http://swtch.com/~rsc/regexp/regexp3.html

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

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


Re: [Haskell-cafe] Categorized Weaknesses from the State of Haskell 2011 Survey

2011-09-13 Thread Malcolm Wallace

On 13 Sep 2011, at 18:59, Michael Orlitzky wrote:

>> Malcolm Wallace and Colin Runciman's ICFP99 paper functioned well as a
>> tutorial for HaXml when I used it - maybe it is a bit out of date now?
>> HaXml is hardly a dire case.
> 
> The paper is out-of-date, so it's worse than useless: you'll waste your
> time figuring out that it's wrong, and you still won't know how to do
> anything.
> 
> There's not one single example anywhere that just shows you how to read
> or write a damned XML file.
> If there were anything approaching a physical manifestation of HaXml, I
> would've strangled it.

I am the first to admit that HaXml's documentation is not as good as it could 
be, and I am sorry that you have had a bad experience.

One thing I am puzzled about, is just how extremely difficult it must be, to 
click on "Detailed documentation of the HaXml APIs" from the HaXml homepage, 
look for a moment until you see "Text.XML.HaXml.Parse" in the list of modules, 
click on it, and find, right at the top of the page, a function that parses a 
String into an XML document tree.

It is absolutely true that finding the reverse conversion (XML tree to String) 
is more obscure, being either the two-stage process of first using 
"Text.XML.HaXml.Pretty" to convert to a Doc, then "Text.PrettyPrint.HughesPJ" 
to render to a String; or alternatively the one-shot conversion in 
"Text.XML.HaXml.Verbatim".  Neither module name is as clear as it should be for 
a beginner, but I can't think of better ones.  Plus, it requires some knowledge 
of the ecosystem, for instance that pretty-printing is a common technique for 
producing textual output.

In fact, my wish as a library author would be: please tell me what you, as a 
beginner to this library, would like to do with it when you first pick it up?  
Then perhaps I could write a tutorial that answers the questions people 
actually ask, and tells them how to get the stuff done that they want to do.  I 
have tried writing documentation, but it seems that people do not know how to 
find, or use it.  Navigating an API you do not know is hard.  I'd like to 
signpost it better.

Regards,
Malcolm

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


[Haskell-cafe] [Haskell] [ANNOUNCE] Haskdogs-0.1

2011-09-13 Thread Sergey Mironov
Hi! I am pleased to announce haskdogs - project-level ctag file generator.

haskdogs is a small shellscript-like tool which creates tag file for
entire haskell project directory. It takes into account first-level
dependencies by recursively scanning imports and adding matching
packages to the final tag list. As a result, programmer can use
his/her text editor supporting tags (vim, for example) to jump
directly to definition of any standard or foreign function he/she
uses. Note, that haskdogs calls some Unix shell commands like test or
mkdir so this tool will likely fail to work on pure Windows platforms.

To use it, do

0) cabal install hasktags haskdogs && mkdir -p ~/.cabal/var/haskdogs
1) cabal unpack TrickyProject-4.2 && cd TrickyProject-4.2
2) haskdogs
3) enjoy the tagfile with references to every function

http://hackage.haskell.org/package/haskdogs-0.1

Sergey

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


Re: [Haskell-cafe] Question about type families

2011-09-13 Thread Gábor Lehel
On Tue, Sep 13, 2011 at 4:58 PM, Grigory Sarnitskiy  wrote:
> Is there a way to make the following code working?
>
> {-# LANGUAGE TypeFamilies #-}
>
> data family Foo a
>
> data instance (Num a)        => Foo a = A a deriving Show
>
> data instance (Fractional a) => Foo a = B a deriving Show
>
>
> I want to have different constructors for 'Foo a' depending on a class of 
> 'a'. Note also, that in the example above I also meant constructor A to be 
> available for (Fractional a) => Foo, since in that case 'a' has Num too. How 
> can I achieve it, maybe not with TypeFamilies?

Thinking further... just guessing, but maybe you want a GADT?

data Foo a where
FooN :: Num a => a -> Foo a
FooF :: Fractional a => a -> Foo a

You use FooF for Fractionals, and either one for Nums. 'a' is required
to be an instance of the class, and the instance is made available
when pattern matching on the constructor (unlike with datatype
contexts). But, as I said, automating the choice based on whether 'a'
is or is not an instance of Fractional is impossible.* You have to
specify it explicitly.

* You can probably do it with Template Haskell, but you probably don't want to.

-- 
Work is punishment for failing to procrastinate effectively.

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


Re: [Haskell-cafe] Question about type families

2011-09-13 Thread Gábor Lehel
On Tue, Sep 13, 2011 at 4:58 PM, Grigory Sarnitskiy  wrote:
> Is there a way to make the following code working?
>
> {-# LANGUAGE TypeFamilies #-}
>
> data family Foo a
>
> data instance (Num a)        => Foo a = A a deriving Show
>
> data instance (Fractional a) => Foo a = B a deriving Show
>
>
> I want to have different constructors for 'Foo a' depending on a class of 
> 'a'. Note also, that in the example above I also meant constructor A to be 
> available for (Fractional a) => Foo, since in that case 'a' has Num too. How 
> can I achieve it, maybe not with TypeFamilies? Current error is
>
>    Conflicting family instance declarations:
>      data instance Foo a -- Defined at 1.hs:7:33-35
>      data instance Foo a -- Defined at 1.hs:5:33-35

Directly, with current GHC? Doubly, maybe triply impossible. Type and
data families aren't allowed to overlap, and there's no way to
dispatch over whether a type is or is not a member of a class. (You
can require that it be a member, but you can't say "if not, do this
other thing"). Also, you can't give type and data families superclass
contexts the way you can classes. I haven't actually encountered this
before, but I think that what you've written here is datatype contexts
for the various instances of the data family, which means you can only
construct a 'Foo a' if the 'a' is a member of the class - but it in no
way affects which instance is chosen. Datatype contexts are considered
a misfeature, besides.[1]

Anyway. What's your wider goal?

[1] http://hackage.haskell.org/trac/haskell-prime/wiki/NoDatatypeContexts

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



-- 
Work is punishment for failing to procrastinate effectively.

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


Re: [Haskell-cafe] Categorized Weaknesses from the State of Haskell 2011 Survey

2011-09-13 Thread Michael Orlitzky
On 09/12/11 17:48, Stephen Tetley wrote:
> Replying to someone's compliant in the first section:
> 
> Malcolm Wallace and Colin Runciman's ICFP99 paper functioned well as a
> tutorial for HaXml when I used it - maybe it is a bit out of date now?
> HaXml is hardly a dire case.

The paper is out-of-date, so it's worse than useless: you'll waste your
time figuring out that it's wrong, and you still won't know how to do
anything.

There's not one single example anywhere that just shows you how to read
or write a damned XML file. HaXml is what prompted me to start this page
(bad language warning, if it ain't obvious):

  http://michael.orlitzky.com/articles/fuck_you.php

If there were anything approaching a physical manifestation of HaXml, I
would've strangled it.

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


[Haskell-cafe] Question about type families

2011-09-13 Thread Grigory Sarnitskiy
Is there a way to make the following code working?

{-# LANGUAGE TypeFamilies #-}

data family Foo a

data instance (Num a)=> Foo a = A a deriving Show

data instance (Fractional a) => Foo a = B a deriving Show


I want to have different constructors for 'Foo a' depending on a class of 'a'. 
Note also, that in the example above I also meant constructor A to be available 
for (Fractional a) => Foo, since in that case 'a' has Num too. How can I 
achieve it, maybe not with TypeFamilies? Current error is

Conflicting family instance declarations:
  data instance Foo a -- Defined at 1.hs:7:33-35
  data instance Foo a -- Defined at 1.hs:5:33-35

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


Re: [Haskell-cafe] Haskell 101 on classes .... duh ..... :^)

2011-09-13 Thread Brandon Allbery
On Tue, Sep 13, 2011 at 00:08, Vasili I. Galchin wrote:

>   I am trying to model multigraphs but getting errors with ghci and
> can't figure out why I have a serious blind spot 
>

Why do you need to use classes for this?  (Note:  forget everything you know
about classes from OOP.  Haskell typeclasses have approximately nothing to
do with OOP.)

junk1.hs:19:12:
> Constructor `Arrow' should have 1 argument, but has been given 0
> In the pattern: Arrow
> In the definition of `source': source Arrow = fst Arrow
> In the instance declaration for `Graph Arrow Int'
>

It's asking "Arrow *what*?"  You specified Arrow as taking a tuple argument;
if you want to use it here, you need to provide that argument (or a
placeholder, but in this case you clearly want the tuple).

>   source (Arrow p) = fst p
>   target (Arrow p) = snd p

Or you can use pattern matching to deconstruct the tuple as well:

>   source (Arrow (f,_)) = f
>   target (Arrow (_,t)) = t

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can't resolve class dependences (making Boolean class)

2011-09-13 Thread Grigory Sarnitskiy
Thank you all guys, fromBool did the trick.

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


Re: [Haskell-cafe] Can't resolve class dependences (making Boolean class)

2011-09-13 Thread Felipe Almeida Lessa
The problem is that an implementation of (===) must return a result of
type b for *any* type b which is an instance of Boolean.  For example,
if I made

  data X = A | B

  instance Boolean X where
...

then I would be able to have:

  eqX :: MyEq a => a -> a -> X
  eqX = (===)

That's all fine and probably the reason why you are going through
these hoops.  However, look at your definition for MyEq Bool:

  a === b  =  a == b

Now, "a == b" has type Bool.  What would happen if I wanted an X instead?

You would need something like

  class Boolean a where
(/\) :: a -> a -> a
fromBool :: Bool -> a

Your instance would then become

  instance MyEq Bool where
a === b  =  fromBool (a == b)

You may want to take a look at the Awesome Prelude [1], which
implement this and much more.

Cheers! =)

[1] https://github.com/tomlokhorst/AwesomePrelude

-- 
Felipe.

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


Re: [Haskell-cafe] Can't resolve class dependences (making Boolean class)

2011-09-13 Thread Ivan Lazar Miljenovic
On 13 September 2011 23:04, Grigory Sarnitskiy  wrote:
> Hello! I'm trying to have a class for booleans called Boolean (the methods 
> are not complete):
>
> class MyEq a where
>    (===) :: (Boolean b) => a -> a -> b

This means that === potentially returns _any_ instance of Boolean.

Let's say for example that I define "data MyBool = T | F" and make it
an instance of MyEq and Boolean.

That means that T === F must be able to return either a Bool, MyBool
or any other instance of Boolean that the _caller_ chooses.

If this is what you want, then I suggest that you do something like:

class (MyEq a) => Boolean a where
   (/\) :: a -> a -> a

fromBool :: Bool -> a

Then the instance becomes:

instance  MyEq Bool where
x === y = fromBool $ x==y

instance Boolean Bool where
   (/\) = (&&)

   fromBool = id

-- 
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] Can't resolve class dependences (making Boolean class)

2011-09-13 Thread Grigory Sarnitskiy
Hello! I'm trying to have a class for booleans called Boolean (the methods are 
not complete):

class MyEq a where
(===) :: (Boolean b) => a -> a -> b

class (MyEq a) => Boolean a where
(/\) :: a -> a -> a

instance MyEq Bool where
x === y = x==y

instance Boolean Bool where
(/\) = (&&)

However, to make Bool an instance of Boolean I need to make it an instance of 
MyEq first, which I can't, because to define === I need Bool to be in Boolean. 
Indeed the code above give the error:

Could not deduce (b ~ Bool)
from the context (Boolean b)
  bound by the type signature for
 === :: Boolean b => Bool -> Bool -> b
  at 1.hs:8:5-18
  `b' is a rigid type variable bound by
  the type signature for === :: Boolean b => Bool -> Bool -> b
  at 1.hs:8:5
In the expression: x == y
In an equation for `===': x === y = x == y
In the instance declaration for `MyEq Bool'
Failed, modules loaded: none.


How can I overcome the issue?

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


Re: [Haskell-cafe] Categorized Weaknesses from the State of Haskell 2011 Survey

2011-09-13 Thread Heinrich Apfelmus

Stephen Tetley wrote:

Replying to someone's compliant in the first section:

Malcolm Wallace and Colin Runciman's ICFP99 paper functioned well as a
tutorial for HaXml when I used it - maybe it is a bit out of date now?
HaXml is hardly a dire case.


... for the right audience. I guess the point is that the person 
complaining could not understand the existing documentation. Quote:


"This type of documentation may seem to “fall out” from a 
mathematically-oriented understanding of the library (such as haxml’s 
combinator scheme, or the concept of “lenses” in fclabels), but an 
application programmer does not have time to work through proofs of lens 
properties and then figure out what they might be good for in a program. 
Instead, the application programmer needs cookbook-style documentation 
to get something up and running, and then s/he can come to understand 
and make use of the underlying math."


I'm not sure whether it's the job of library documentation to teach 
mathematical understanding, but cookbook-style examples seem very 
valuable to me. For instance, I think that the Happstack tutorial


  http://happstack.com/docs/crashcourse/index.html

is excellent in this regard.

(Personally, a good method for writing this kind of stuff is to assume 
that the reader has almost zero attention span. Then, I am forced to 
communicate the most useful points in the first few paragraphs, because 
my hypothetical reader probably won't read any further than that. Of 
course, the resulting text will be very useful to readers with a high 
attention span, too.)



Best 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] regex-applicative library needs your help! (algorithmic challenge)

2011-09-13 Thread Chris Kuklewicz
I wrote regex-tdfa, the efficient (though not yet lightning fast) Posix-like 
engine.

You are not the first to want an efficient Perl-like engine.  The answer you
seek flows from Russ Cox (though in C++):

> http://google-opensource.blogspot.com/2010/03/re2-principled-approach-to-regular.html

> http://code.google.com/p/re2/

Quoting relevant bit:

> It also finds the leftmost-first match, the same match that Perl would, and
> can return submatch information. The one significant exception is that RE2
> drops support for backreferences¹ and generalized zero-width assertions,
> because they cannot be implemented efficiently.

On 13/09/2011 06:40, Roman Cheplyaka wrote:
> Please help make the regex-based parsing library efficient!
> 
> https://github.com/feuerbach/regex-applicative/wiki/Call-For-Help
> 



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