Welcome to issue 191 of the HWN, a newsletter covering developments in
the Haskell community. This release covers the week of July 10 to
16, 2011.
[1] http://haskell.org/
You can find the HTML (and mobile) version of the issue at:
http://contemplatecode.blogspot.com/2011/07/hask
Hi Everybody,
I'm having some strange issues with Network.CGI's pathInfo action, or else
some other strangeness with pattern matching.
My "mainCGI" CGI action is:
mainCGI :: CGI CGIResult
mainCGI = pathInfo >>= outputSlotTHtml . packagesPage
outputSlotTHtml is irrelevant to my problem. package
Am 21.07.2011 21:19, schrieb Jeremy Shaw:
Nope. It is not related.
It is also not related to the GSM library:
http://www.programmersheaven.com/download/29760/download.aspx
or the decompiler:
http://boomerang.sourceforge.net/index.php
Perhaps picking an original name would have been a wise ch
Nope. It is not related.
It is also not related to the GSM library:
http://www.programmersheaven.com/download/29760/download.aspx
or the decompiler:
http://boomerang.sourceforge.net/index.php
Perhaps picking an original name would have been a wise choice. But it
was the only I idea I had :)
I
I'm new to Haskell and am trying to use the SAX module to parse an XML
file. I'm using the following code:
module FPHParser where
import Data.Text as Text
import Data.Maybe
import Text.XML.LibXML.SAX as SAX
import System.IO
f :: IO (Parser IO)
f =
do
let g = do
pu
Am 21.07.2011 20:45, schrieb Jeremy Shaw:
Hello,
I am pleased to announce the release of two new libraries: boomerang
and web-routes-boomerang.
Does this have anything to do with:
"Boomerang: A bidirectional programming language for ad-hoc data"
http://www.seas.upenn.edu/~harmony/
?
If not,
Hello,
I am pleased to announce the release of two new libraries: boomerang
and web-routes-boomerang.
boomerang is a library for general purpose, invertible parsing and
pretty printing. It provides combinators which allow you to specify a
grammar once and automatically extract a parser and pretty
Hello, Willem Van Lint, Thank you for help, it works.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Hi,
I think your main problem here is that you use Int in the pattern matching.
The point is that you are matching your value of type Tree k v to a pattern
such as:
- EmptyTree
- (Node (a, b) left right)
Patterns don't contain type information such as Int, but things like value
constructors and v
The documentation for the Show typeclass has this very example:
http://hackage.haskell.org/packages/archive/base/latest/doc/html/Prelude.html#t:Show
The summary? you need to define either showPrec or show, the latter of which is
simpler, it is just a -> String.
So:
instance Show (Tree Int Int)
Hello, thank you for reply. I know that i can derive this. But i want to know
how can i make it by hand.
Thank you.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Hi.
On 07/21/2011 04:45 PM, Александр wrote:
Hello,
I have binary tree, with every leaf tuple - (k,v):
data Tree k v = EmptyTree
| Node (k, v) (Tree k v) (Tree k v)
How can i make Show Instance for (Tree Int Int) ?
The easiest way is automatic derivation:
data Tree k v = EmptyTree
| Nod
Hello,
I have binary tree, with every leaf tuple - (k,v):
data Tree k v = EmptyTree
| Node (k, v) (Tree k v) (Tree k v)
How can i make Show Instance for (Tree Int Int) ?
I try:
instance Show (Tree k v) where
show EmptyTree = show "Empty"
show (Node (Int, Int) lef
Hi, Cafe,
My wife, a biologist, will attend a conference outside Helsinki in
mid-September. I've decided to accompany her on the trip to Finland.
Are there any Haskellers in the area who might be interested in an
informal meetup?
I'd also welcome any suggestions on what to see, do, eat, etc
On Thu, Jul 21, 2011 at 8:31 AM, Ivan Lazar Miljenovic
wrote:
> Well, for fmap vs liftM, you have that liftM is automatically defined
> for you rather than needing to make the Functor instance, so if you're
> quickly defining a Monad for internal use then you can just use liftM,
> etc. without nee
On 07/21/2011 02:15 PM, Alexey Khudyakov wrote:
Any examples for hangups of 'smartEq' are greatly appreciated, I couldn't
produce any so far.
Following sequences will hang smartEq. They are both infinite and aperiodic.
smartEq (fromList primes) (fromList primes)
smartEq (fromList pidigits)
> Any examples for hangups of 'smartEq' are greatly appreciated, I couldn't
> produce any so far.
>
Following sequences will hang smartEq. They are both infinite and aperiodic.
smartEq (fromList primes) (fromList primes)
smartEq (fromList pidigits) (fromList pidigits)
___
On Thu, Jul 21, 2011 at 1:22 AM, Olexander Kozlov wrote:
> Greetings Haskell community,
> I stuck with a space leak problem in simple task. I have a function
> described with a list of pairs:
> type Fn a b = [(a, b)]
> mapping values from a to b. And I have a composition operation which accepts
On 21 July 2011 11:10, Arlen Cuss wrote:
> Hi cafe!
>
> I feel a bit like I'm speaking out of turn for bringing this up -- and
> I'm sure it must have been brought up many times before -- but I hope
> there can be something fruitful had from a discussion.
>
> In my travels I've read several people
Hi cafe!
I feel a bit like I'm speaking out of turn for bringing this up -- and
I'm sure it must have been brought up many times before -- but I hope
there can be something fruitful had from a discussion.
In my travels I've read several people with much better grasp of Haskell
than I have mention
On 07/21/2011 10:30 AM, Pedro Vasconcelos wrote:
On Wed, 20 Jul 2011 12:48:48 -0300
Thiago Negri wrote:
Is it possible to implement (==) that first check these thunks before
evaluating it? (Considering both arguments has pure types).
E.g.,
Equivalent thunks, evaluates to True, does not ne
On Wed, 20 Jul 2011 12:48:48 -0300
Thiago Negri wrote:
> Is it possible to implement (==) that first check these thunks before
> evaluating it? (Considering both arguments has pure types).
>
>
> E.g.,
>
> Equivalent thunks, evaluates to True, does not need to evaluate its
> arguments: [1..] =
Greetings Haskell community,
I stuck with a space leak problem in simple task. I have a function
described with a list of pairs:
type Fn a b = [(a, b)]
mapping values from a to b. And I have a composition operation which accepts
two functions and returns
theirs composition:
compose :: Eq
23 matches
Mail list logo