HPath is a command line utility to grab the Haskell source
for a given identifier:
:; dist/build/hpath/hpath HPath.Path.parse 2>/dev/null
parse :: String -> Either ParseError Path
parse s = Text.ParserCombinators.Parsec.parse (qualified []) s s
This is an alpha relea
2009/12/29 Luke Palmer :
> > They are another group, too -- the group with `*':
> >
> > Group* = (*, 1, 1 / _)
>
> Ignoring 0 for sake of discussion.
Doh.
--
Jason Dusek
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/m
Am Mittwoch 30 Dezember 2009 01:23:32 schrieb Will Ness:
> Daniel Fischer web.de> writes:
> > Gee, seems my mail server reads your posts very thoroughly today :)
>
> I hope it's not a bad thing. :)
>
It means, twenty minutes after I replied to the previous, I got your hours old
post which
menti
Am Mittwoch 30 Dezember 2009 01:04:34 schrieb Will Ness:
>
> > While I haven't detected that with the primes code, I find that in my
> > ghci your code is approximately 2.5 times faster than ONeill or Bayer
> > when interpreted (no difference in scaling observed), while when compiled
> > with -O2,
I couldn't resist the opportunity for some ascii abstract art. Emacs
turns the backquoted bits blue.
f `o` g = ( f) . g
f `oo` g = (o f) . g
f `ooo` g = (oo f) . g
f `` g = (ooo f) . g
f `o` g = ( f) . g
f `oo` g = (o f) . g
f `ooo` g = (oo f) . g
f `` g = (
On Tue, Dec 29, 2009 at 6:22 PM, Jason Dusek wrote:
> Consider the real numbers. They "are" a group. We have an
> identity element `0', inverses and closure under the associative
> operation `+'.
>
> Group+ = (+, 0, -1 * _)
>
> They are another group, too -- the group with `*':
>
> Group
On Tuesday 29 December 2009 8:22:15 pm Jason Dusek wrote:
> Consider the real numbers. They "are" a group. We have an
> identity element `0', inverses and closure under the associative
> operation `+'.
>
> Group+ = (+, 0, -1 * _)
>
> They are another group, too -- the group with `*':
On Wed, 2009-12-30 at 00:45 +, Conor McBride wrote:
> Hi Maciej
>
> On 30 Dec 2009, at 00:07, Maciej Piechotka wrote:
>
> > On Tue, 2009-12-29 at 23:00 +, Conor McBride wrote:
> >> Hi Maciej
> >>
> >> On 29 Dec 2009, at 20:52, Maciej Piechotka wrote:
> >>
> >>> On Tue, 2009-12-29 at 18:20
Consider the real numbers. They "are" a group. We have an
identity element `0', inverses and closure under the associative
operation `+'.
Group+ = (+, 0, -1 * _)
They are another group, too -- the group with `*':
Group* = (*, 1, 1 / _)
This seems like a real problem with the w
Hi Maciej
On 30 Dec 2009, at 00:07, Maciej Piechotka wrote:
On Tue, 2009-12-29 at 23:00 +, Conor McBride wrote:
Hi Maciej
On 29 Dec 2009, at 20:52, Maciej Piechotka wrote:
On Tue, 2009-12-29 at 18:20 +, Conor McBride wrote:
ala AppLift foldMap
What is benefit of it over:
concat
Daniel Fischer web.de> writes:
>
>
> Gee, seems my mail server reads your posts very thoroughly today :)
I hope it's not a bad thing. :)
>
> Am Dienstag 29 Dezember 2009 14:58:10 schrieb Will Ness:
> >
> > If I realistically needed primes generated in a real life setting, I'd
> > probably ha
Martijn van Steenbergen writes:
> Gregory Collins wrote:
>> Martijn van Steenbergen writes:
>>
>>> Hello,
>>>
>>> Above error is one of those that appear when using GHC on the 64-bit Snow
>>> Leopard. I've already patched my /usr/bin/ghc to mention -optc-m32 -opta-m32
>>> -optl-m32. However, the
On Tue, 2009-12-29 at 23:00 +, Conor McBride wrote:
> Hi Maciej
>
> On 29 Dec 2009, at 20:52, Maciej Piechotka wrote:
>
> > On Tue, 2009-12-29 at 18:20 +, Conor McBride wrote:
> >>
> >> ala AppLift foldMap
> >
> > What is benefit of it over:
> > concatMapA f = foldr (liftA2 mappend . f)
Daniel Fischer web.de> writes:
>
>
> Am Dienstag 29 Dezember 2009 14:34:03 schrieb Will Ness:
> > Daniel Fischer web.de> writes:
> > > Am Dienstag 29 Dezember 2009 04:38:21 schrieb Will Ness:
> > > > Now _this_, when tested as interpreted code in GHCi, runs about 2.5x
> > > > times faster than
Hi guys,
any suggestions on how to go about it then?
I'm really still no step further on the DSL for Relational Algebra
thingy, and I'd even settle for a "comprehension" DSL.
I've spent months now, trying to figure it out by myself, studying
HaskellDB, HList and many others. Yeah, I even had
Hi Maciej
On 29 Dec 2009, at 20:52, Maciej Piechotka wrote:
On Tue, 2009-12-29 at 18:20 +, Conor McBride wrote:
ala AppLift foldMap
What is benefit of it over:
concatMapA f = foldr (liftA2 mappend . f) (pure mempty)
Given that applicative functors take monoids to monoids, it's
nice
For the record...
The regex-posix package also failed to build for me with GHC 6.12.1 on
Windows with Cygwin due to >> undefined reference to `_impure_ptr' <<
errors.
Again this builds fine with MinGW once you have the GNU regex library
installed (its not installed as a default MSys package). Wit
Gregory Collins wrote:
Martijn van Steenbergen writes:
Hello,
Above error is one of those that appear when using GHC on the 64-bit Snow
Leopard. I've already patched my /usr/bin/ghc to mention -optc-m32 -opta-m32
-optl-m32. However, the error still occurs when doing 'cabal haddock' in *some*
Martijn van Steenbergen writes:
> Hello,
>
> Above error is one of those that appear when using GHC on the 64-bit Snow
> Leopard. I've already patched my /usr/bin/ghc to mention -optc-m32 -opta-m32
> -optl-m32. However, the error still occurs when doing 'cabal haddock' in
> *some*
> packages.
>
The code we "want" to write is that which matches the way we think
[snip]
My way is to think hard about what the best way to think about things is.
I'm in two minds. On the one hand, we're in violent agreement:
The code we /want/ to write is that which matches the way we /want/ to
think,
g
2009/12/29 Dominic Steinitz :
> And oo = (.).(.) and ooo = (.).(.).(.)
>
> There was a suggestion a few years back to standardise these as I recall
> something like:
>
> $0 = $
> $1 = .
> $2 = (.).(.)
>
> and so on but nothing came of it.
Hi Dominic
Hmm, name-wise I would have to be dishonour
Hello,
Above error is one of those that appear when using GHC on the 64-bit
Snow Leopard. I've already patched my /usr/bin/ghc to mention -optc-m32
-opta-m32 -optl-m32. However, the error still occurs when doing 'cabal
haddock' in *some* packages.
For example, a local project of mine builds
Hi Günther
The Lambda Calculus Abroad - is Daan Leijen's PhD (so you do already
know it...).
Best wishes
Stephen
2009/12/29 Günther Schmidt :
> Hi Stephen,
>
> no I haven't, I only know of 2 papers on HaskellDB, chapter 5 from "The
> lambda calculus abroad" and a longer version, "Domain specifi
Stephen Tetley gmail.com> writes:
> -- | Compose an arity 1 function with an arity 2 function.
> -- B1 - blackbird
> oo :: (c -> d) -> (a -> b -> c) -> a -> b -> d
> oo f g = (f .) . g
>
> Extending the arity works quite nicely too:
>
> -- | Compose an arity 1 function with an arity 3 function.
Hi Stephen,
no I haven't, I only know of 2 papers on HaskellDB, chapter 5 from "The
lambda calculus abroad" and a longer version, "Domain specific embedded
compilers", both co-authored with Erik Meijer.
Is there another one?
Günther
Am 29.12.09 22:03, schrieb Stephen Tetley:
Hi Günther
Hi Günther
Have you looked at Daan Leijen's PhD thesis? There's a lot more stuff
in it, than was covered in the "HaskellDB" paper.
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haske
On Tue, 2009-12-29 at 18:20 +, Conor McBride wrote:
> Hi Tony
>
> On 29 Dec 2009, at 12:10, Tony Morris wrote:
>
> > Can (liftM join .) . mapM be improved?
> > (Monad m) => (a -> m [b]) -> [a] -> m [b]
>
> You can
>
>(a) generalize m from Monad to Applicative
>(b) generalize [b] to
On Tue, Dec 29, 2009 at 6:36 AM, Kim-Ee Yeoh wrote:
> Conal gives a lot of useful advice on DSL design.
> One way to start is to articulate existing pain. Where and why is SQL
> painful?
> Another trick is to work backwards: What kind of code do you really want to
> write?
A bit of unsolicited op
On Tue, Dec 29, 2009 at 11:34 AM, Gregory Propf wrote:
>
> I'm trying out the dynamic linking in GHC 6.12 and getting this message a lot
> for different libraries. I assume I need to rebuild them with different ghc
> options in the cabal files and have tried -shared, -dynamic and -fPIC but
> w
OK -- I've managed to build it as follows.
1. Got the readline from the source at ftp.gnu.org. Always fun to ftp to the
mothership, got the patches while at it. Always fun to remember where to cd to
patch and which -p level to supply.
2. Built and installed readline 6.004 with default /usr/
Gee, seems my mail server reads your posts very thoroughly today :)
Am Dienstag 29 Dezember 2009 14:58:10 schrieb Will Ness:
> Eugene Kirpichov gmail.com> writes:
> > 2009/12/29 Will Ness yahoo.com>:
> > > Daniel Fischer web.de> writes:
> > >> Am Dienstag 29 Dezember 2009 04:38:21 schrieb Will
I'm trying out the dynamic linking in GHC 6.12 and getting this message a lot
for different libraries. I assume I need to rebuild them with different ghc
options in the cabal files and have tried -shared, -dynamic and -fPIC but with
no luck. Is there something I'm missing.
___
Am Dienstag 29 Dezember 2009 14:34:03 schrieb Will Ness:
> Daniel Fischer web.de> writes:
> > Am Dienstag 29 Dezember 2009 04:38:21 schrieb Will Ness:
> > > Now _this_, when tested as interpreted code in GHCi, runs about 2.5x
> > > times faster than Priority Queue based code from Melissa O'Neill's
On Tue, Dec 29, 2009 at 12:26 PM, David Fox wrote:
>>> "xyz" =~ "^[^-]*$" :: Bool
>> *** Exception: Explict error in module Text.Regex.TDFA.String :
>> Text.Regex.TDFA.String died: parseRegex for Text.Regex.TDFA.String
>> failed:"^[^-]*$" (line 1, column 5):
>> unexpected "]"
>> expecting Failed t
Hi Stefan
The bird names for combinators stem from Raymond Smullyan's book - To
Mock a Mockingbird (this is second-hand knowledge as I don't have my
own copy - though I think I've just obliged to get myself one as a
post-Christmas treat).
The other names B1 B2 and the more common S K I C W etc -
Oh, I forgot to "reply-to-all".
-- Forwarded message --
From: Paulo Tanimoto
Date: Tue, Dec 29, 2009 at 9:39 AM
Subject: Re: [Haskell-cafe] ghc 6.12.1 and regex
To: David Fox
Hi David,
On Tue, Dec 29, 2009 at 9:28 AM, David Fox wrote:
> Is anyone else seeing this problem:
>
>
On Tue, Dec 29, 2009 at 10:23 AM, David Fox wrote:
> On Tue, Dec 29, 2009 at 7:28 AM, David Fox wrote:
>> Is anyone else seeing this problem:
>>
>>> :m +Text.Regex.Posix
>>> "\250" =~ "\250" :: Bool
>> True
>>> "\250" =~ "[\250]" :: Bool
>> False
>>
>
> Paul Tanimoto suggested TDFA, which gets me
On Tue, Dec 29, 2009 at 7:28 AM, David Fox wrote:
> Is anyone else seeing this problem:
>
>> :m +Text.Regex.Posix
>> "\250" =~ "\250" :: Bool
> True
>> "\250" =~ "[\250]" :: Bool
> False
>
Paul Tanimoto suggested TDFA, which gets me most of the way there.
However, it can't seem to handle "match a
Hi Tony
On 29 Dec 2009, at 12:10, Tony Morris wrote:
Can (liftM join .) . mapM be improved?
(Monad m) => (a -> m [b]) -> [a] -> m [b]
You can
(a) generalize m from Monad to Applicative
(b) generalize [b] to any Monoid
(c) generalize [a] to f a for any Foldable f
and write
ala AppLi
Stephen,
oo f g = (f .) . g
ooo f g = ((f .) .) . g
Why are these also called blackbird and bunting?
Thanks,
Stefan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
2009/12/29 David Menendez :
> Why restrict yourself to functions? You can generalize this to
> arbitrary stacks of functors.
>
> oo :: (Functor f, Functor g) => (a -> b) -> f (g a) -> f (g b)
> oo = fmap . fmap
Hi David
Nice! this seems to be taking things into TypeCompose territory, cf. fmapFF.
On Tue, 2009-12-29 at 14:47 +, pbrowne wrote:
> Hi,
> I am studying the underlying semantics behind Haskell and to what degree
> those semantics are actually implemented. I need to clarify what a *type
> synonym* actual means in relation to Haskell's logic (or formal
> semantics). I used the fo
On Tue, Dec 29, 2009 at 12:24 PM, Stephen Tetley
wrote:
> oo is one of of a family of functions I use often to avoid
> sectioning/composing mania. It's known to Raymond Smullyan fans as
> 'blackbird', though I call it oo as a pun on Standard MLs o (which is
> Haskells (.) of course).
>
> -- | Comp
On Tue, 2009-12-29 at 00:14 -0800, Judah Jacobson wrote:
> > Downloaded the package and do configure manually:
> >
> > ./configure --with-readline-includes=/opt/local/include
> > --with-readline-libraries=/opt/local/lib
>
> You should use:
>
> cabal install readline
> --configure-option=--with
Thanks for the replies, they helped me understand lazy evaluation a little
better.
--
Gautam
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
2009/12/29 Tony Morris :
> Can (liftM join .) . mapM be improved?
> (Monad m) => (a -> m [b]) -> [a] -> m [b]
Hi Tony
I count this as a personal preference rather than an improvement:
joinything2 :: (Monad m) => (a -> m [b]) -> [a] -> m [b]
joinything2 = liftM join `oo` mapM
oo is one of of
Ah, I see now. Thanks for going deeper on that.
I did eventually find the RPC stuff for Go, and thought that that might be
interesting to implement.
On Tue, Dec 29, 2009 at 8:31 AM, Joan Miller wrote:
> "Each component runs in its own private address space. Inter-component
> communication is b
Daniel Fischer web.de> writes:
>
>
> Am Dienstag 29 Dezember 2009 04:38:21 schrieb Will Ness:
> > Now _this_, when tested as interpreted code in GHCi, runs about 2.5x times
> > faster than Priority Queue based code from Melissa O'Neill's ZIP package
> > mentioned at the haskellwiki/Prime_Number
Hello Kim-Ee,
well right now I would even go for an abstract comprehension DSL.
I do think there's a big difference between the various DSL techniques,
most are designed with a particular evaluation in mind, tagless-style
ones are focused on constructing typed terms first, and the evaluation /
"Each component runs in its own private address space. Inter-component
communication is based on Native Client’s reliable datagram service,
the IMC (Inter-Module Communications). For communications between the
browser and a NaCl module, Native Client provides two options: a
Simple RPC facility (SRP
Dear Patrick,
From the responses to my query, it seems that I cannot rely totally on
the compiler for my research question which is concerned with the
meaning of Haskell constructs I will have to consult the Haskell
Report.
For both practical and theoretical matters, GHC provides a very dece
Use operator precedence: infixr . I don't remember exactly how it is
used, but it should do the trick and let you get rid of the
parentheses.
2009/12/29 Jonathan Fischoff :
> Thirst will work I think. I tested a demo and the only problem I can see is
> the unwieldiness of the syntax, i.e
> testThi
Stefan Holdermans wrote:
>> It seems that I need to distinguish between a theory for Haskell and a
>> given implementation (GHCi).
> What do you mean by this?
>From the responses to my query, it seems that I cannot rely totally on
the compiler for my research question which is concerned with the
I guess I'm confused by what it means to "support" this in a language.
My understanding is this is using lightweight virtualization technology
(perhaps via segment register hacks on x86, and something else on ARM) to
provide a safe sandbox to run native code in a browser. If I had to guess,
I'd s
On Tue, Dec 29, 2009 at 2:48 AM, Alexy Khrabrov wrote:
> I've tried to do cabal install readline on Snow Leopard with MacPorts and it
> fails with the infamous:
>
> $ cabal install readline
> ...
>
> How should I properly tell cabal install readline where my readline is?
As a Mac user, I've p
Patrick,
It seems that I need to distinguish between a theory for Haskell and a
given implementation (GHCi).
What do you mean by this?
Obviously I get two different types
Wrong. You get exactly the same type, it's just that GHCi detected
that you have a fancy name for this type, so it giv
1)
Obviously I get two different types
Wrong. You get exactly the same type, it's just that GHCi detected that you
have a fancy name for this type, so it gives you that name. It's not type
system, it's just GHCi.
Are you saying there is just one type? (not two isomorphic types because
there i
Thirst will work I think. I tested a demo and the only problem I can see is
the unwieldiness of the syntax, i.e
testThirst = f `Cons` (g `Cons` (h `Cons` Nil))
Maybe there is a way to sugar up the syntax to get rid of the parentheses?
On Mon, Dec 28, 2009 at 7:43 PM, Antoine Latter wrote:
> On
forward Id a = a
forward (ICons f _ r) a = forward r (f a)
backward Id a = a
backward (ICons _ f r) a = f (backward r a)
2009/12/29 Eugene Kirpichov :
> data IList a b where
> Id :: IList a a
> ICons :: (a -> b) -> (b -> a) -> IList b c -> IList a c
>
> 2009/12/29 Jonathan Fischoff :
>> Thi
data IList a b where
Id :: IList a a
ICons :: (a -> b) -> (b -> a) -> IList b c -> IList a c
2009/12/29 Jonathan Fischoff :
> This seems like exactly what I want, but there are two problems: I can't
> access the paper and it requires Generic Haskell. I'm just too much of newb
> to jump int
This seems like exactly what I want, but there are two problems: I can't
access the paper and it requires Generic Haskell. I'm just too much of newb
to jump into generic Haskell :).
On Mon, Dec 28, 2009 at 7:41 PM, Dan Weston wrote:
> This might be pertinent:
>
> Alimarine et al, "There and Back
Hi,
It seems that I need to distinguish between a theory for Haskell and a
given implementation (GHCi). I have two further queries based on the
replies;
1)
> Obviously I get two different types
> Wrong. You get exactly the same type, it's just that GHCi detected that you
> have a fancy name for
Is anyone else seeing this problem:
> :m +Text.Regex.Posix
> "\250" =~ "\250" :: Bool
True
> "\250" =~ "[\250]" :: Bool
False
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Tue, Dec 29, 2009 at 2:47 PM, pbrowne wrote:
> Hi,
> I am studying the underlying semantics behind Haskell and to what degree
> those semantics are actually implemented. I need to clarify what a *type
> synonym* actual means in relation to Haskell's logic (or formal
> semantics). I used the fo
pbrowne wrote:
Hi,
I am studying the underlying semantics behind Haskell and to what degree
those semantics are actually implemented. I need to clarify what a *type
synonym* actual means in relation to Haskell's logic (or formal
semantics). I used the following type synonym:
type Name = String
* pbrowne wrote:
> semantics). I used the following type synonym:
type String = [Char]
type Name = String
String, Name and [Char] are synonyms, which means every expression is
identically to the others. There is no difference besides that String and
Name are type aliases while [Char] is a type co
Hi,
I am studying the underlying semantics behind Haskell and to what degree
those semantics are actually implemented. I need to clarify what a *type
synonym* actual means in relation to Haskell's logic (or formal
semantics). I used the following type synonym:
type Name = String
getName(n) = n
I
Hello,
is it possible to distiguish which package is included at Haskell
Platform directly from Hackage web interface or `cabal info` ?
So anybody can recognize if the dependecy of his package is going from
platform or not without platform installed.
Thanks,
Rado
__
Eugene Kirpichov gmail.com> writes:
>
> 2009/12/29 Will Ness yahoo.com>:
> > Daniel Fischer web.de> writes:
> >
> >>
> >>
> >> Am Dienstag 29 Dezember 2009 04:38:21 schrieb Will Ness:
> >> > Now _this_, when tested as interpreted code in GHCi, runs about 2.5x
> >> > times
> >> > faster than P
2009/12/29 Will Ness :
> Daniel Fischer web.de> writes:
>
>>
>>
>> Am Dienstag 29 Dezember 2009 04:38:21 schrieb Will Ness:
>> > Now _this_, when tested as interpreted code in GHCi, runs about 2.5x times
>> > faster than Priority Queue based code from Melissa O'Neill's ZIP package
>> > mentioned a
Günther Schmidt wrote:
>
> Initially I had simply imported the CSV files into empty tables in a
> database and done the calculations directly in SQL, never ever again!
>
> [snip]
>
> But my 1st goal here is to express the algorithm.
>
Sounds like you want a better DSL than SQL. You're in ma
Daniel Fischer web.de> writes:
>
>
> Am Dienstag 29 Dezember 2009 04:38:21 schrieb Will Ness:
> > Now _this_, when tested as interpreted code in GHCi, runs about 2.5x times
> > faster than Priority Queue based code from Melissa O'Neill's ZIP package
> > mentioned at the haskellwiki/Prime_Number
Native CLient (NaCl) [1] is a technology very cool which lets to run
native code in web applications, and it's being integrated in some
languages as Python [2]. Go [3] already has rudimentary support for
Native Client (and it's logical since that both technologies are from
Google)
I hope that Hask
> imo, the most import ingredient to understand monads, is to understand
> lazy evaluation. In Haskell, everything is about values. If you have a
> function f :: a -> b, then f x stands for a value of type b (nothing
> is evaluated yet).
> Now, if you have another function g :: a -> M b, then g x s
I'd write it as
foo f = join .<$> sequence . (f <$>)
where
(.<$>) :: (.<$>) :: Functor f => (a -> b) -> ((x -> f a) -> (x -> f b))
x .<$> y = (x <$>) . y
is part of my line-noise toolbox.
This join .* sequence family of functions is quite common.
Should really have a name for them.
Tony Mo
imo, the most import ingredient to understand monads, is to understand
lazy evaluation. In Haskell, everything is about values. If you have a
function f :: a -> b, then f x stands for a value of type b (nothing
is evaluated yet).
Now, if you have another function g :: a -> M b, then g x stands for
* Tony Morris wrote:
> Can (liftM join .) . mapM be improved?
> (Monad m) => (a -> m [b]) -> [a] -> m [b]
a) liftM concat . mapM -- list handling . monad handling
b) (sequence .) . map -- monad handling . list handling
___
Haskell-Cafe mailing list
H
CK Kashyap writes:
> What are the benefits of making it an instance of Functor?
The ability to use fmap rather than liftM.
> I'd appreciate it very much if you could give me some pointers on the
> usages of guard, when and msum.
You can use when to have an operation occur only when a condition
Can (liftM join .) . mapM be improved?
(Monad m) => (a -> m [b]) -> [a] -> m [b]
--
Tony Morris
http://tmorris.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Tue, 2009-12-29 at 02:07 -0800, CK Kashyap wrote:
> Thanks Jason,
>
>
> >
> > You should make a `Functor' instance since monads are all
> > functors (though the typeclass does not enforce this).
> >
> What are the benefits of making it an instance of Functor?
>
1. For example to use fu
Am Dienstag 29 Dezember 2009 04:38:21 schrieb Will Ness:
> Now _this_, when tested as interpreted code in GHCi, runs about 2.5x times
> faster than Priority Queue based code from Melissa O'Neill's ZIP package
> mentioned at the haskellwiki/Prime_Numbers page, with
> about half used memory reported,
Gautam bt wrote:
> Svein Ove Aas wrote:
>
>> Lazyness can be considered to be a controlled form of mutation
>
>
> Can someone explain why this is true (or link me to an explanation)?
You may want to have a look at
R. Bird, G. Jones, O. de Moor.
More haste, less speed: lazy versus eager eva
Thanks Jason,
>
> You should make a `Functor' instance since monads are all
> functors (though the typeclass does not enforce this).
>
What are the benefits of making it an instance of Functor?
> You can use `guard' and `when' and other monadic operations.
> The `MonadPlus' instance g
On Tue, Dec 29, 2009 at 7:58 AM, CK Kashyap wrote:
> I'd appreciate answers to the following queries -
> 1. Comments about the functions I've written
{-# LANGUAGE UnicodeSyntax #-}
import Monad ( MonadPlus(..) )
data List α = Cons α (List α) | Empty
deriving Show
If you look at y
2009/12/29 Alexander Solla :
> Every Monad defines a "join" and "eval" function in terms of
> bind and return, and the Monad type class does this for you.
> You can use "join" to construct queries against a monad, and
> eval to "run" a monad, like a state machine. (Conceptually,
> the Haskell runti
I happen to think that the only good way to approach monads is
mathematically. Uses come out naturally, once you understand what it
is that a monad "does". I'll make a short speech and then comment on
your questions.
First, an example. I will assume that there are some things you will
On Mon, Dec 28, 2009 at 11:48 PM, Alexy Khrabrov wrote:
> I've tried to do cabal install readline on Snow Leopard with MacPorts and it
> fails with the infamous:
>
> $ cabal install readline
> ...
> checking for GNUreadline.framework... checking for readline... no
> checking for tputs in -lncurse
2009/12/28 CK Kashyap :
> 1. Comments about the functions I've written
Maybe your indentation was eaten by your mailer; but please
indent the operations within a `do' block and the definitions
under a `where'.
You should make a `Functor' instance since monads are all
functors (though th
88 matches
Mail list logo