I've run into an issue with inlining that I'm not sure how to work
around. I am instantiating some pre-existing type classes with
Vector-based types. There already exist generic functions in modules I
do not control that use this type class, and they are not tagged with
the INLINE pragma. I am
Here's a transcript from a conversation I had with Conal on IRC.
tl;dr: cross-module inlining is only possible because ghc
stashes a definition in a .hi, iuuc. i'm suggesting that the stashed
definition either (a) never include further inlinings, or (b) be
augmented by such a definition.
Full t
On 04/04/2010 06:35 PM, Ivan Miljenovic wrote:
I would wonder _why_ anyone would refuse to do so. Are they that
ashamed of their own software that they wouldn't want to be associated
with it, or is there some legal reason that they don't want to be
associated with it?
This seems to be orthogon
On 04/05/2010 11:32 PM, Ivan Miljenovic wrote:
4) The people who support the policy don't see why anyone has a problem with it.
I have seen no logical explanation of *why* anybody supports this
policy. I've only seen vague hand-wavy statements like "people who use
real names are more reliable
On Tue, Apr 6, 2010 at 6:08 AM, Serguey Zefirov wrote:
> http://lambda-the-ultimate.org is one lovely community that has that
> restriction: http://lambda-the-ultimate.org/policies#Policies
I quote the policy in full here:
> Many of us here post with our real, full names. Anonymity and the use o
On 05/23/2010 02:17 PM, Peter Verswyvelen wrote:
IMO: For AAA game programming? Definitely not.
Why not? I suppose it may depend on your definition of "AAA," since
there doesn't seem to be any consensus on it. I have seen it mean
various combinations of the following, but rarely, if ever, all
On 06/03/2010 10:14 AM, Gabriel Riba wrote:
No need for runtime errors or exception control
hd :: List!Cons a -> a
hd (Cons x _) = x
This is already doable using GADTs:
data Z
data S n
data List a n where
Nil :: List a Z
Cons :: a -> List a n -> List a (S n)
Sorry, I hit Reply instead of Reply To All.
-- Forwarded message --
From: Jake McArthur
Date: Tue, Jun 8, 2010 at 6:16 PM
Subject: Re: [Haskell-cafe] Rewriting a famous library and using the
same name: pros and cons
To: Don Stewart
Making a new name for an existing package
On Sun, Jun 27, 2010 at 4:44 PM, Alexey Khudyakov
wrote:
> Dependent types would be nice but there isn't anything usable out there.
> Newtype wrapper parametrized by type level number works fine so far.
>
> If you interested sources are available here:
> http://bitbucket.org/Shimuuar/nvector
> htt
michael rice wrote:
Just curious, what kind of super-cooled processor is this guy running
on? I got the same answer but it took almost three minutes (2:43:15).
Only took a few seconds on my machine (Core 2 Duo 2.53GHz).
- Jake
___
Haskell-Cafe mailin
Andrew Coppin wrote:
Jake McArthur wrote:
michael rice wrote:
Just curious, what kind of super-cooled processor is this guy running
on? I got the same answer but it took almost three minutes (2:43:15).
Only took a few seconds on my machine (Core 2 Duo 2.53GHz).
Maybe it's the versi
Sure, so hnf would give us a non-determined result, but I don't think
that makes unamb any less referentially transparent – the same value is
always returned, and always reduced at least to hnf.
I think it is hnf that Peter was talking about needing to be in IO, not
unamb.
- Jake
___
Christopher Lane Hinson wrote:
What we'd like to avoid is duplicate verification that a thunk is hnf.
Do we have evidence that this verification ever actually consumes a lot
of resources?
I think the OP is trying to avoid spawning unnecessary threads at the
cost of duplicate checks for HNF.
michael rice wrote:
Got it! I figured there must be some way to unpack it.
If you peek at the thread about getting a value out of IO [1], you will
see some similarities. If you look at my response [2], you will see that
the functions I suggested for IO are exactly the same as the functions
y
Patrick LeBoutillier wrote:
Hi all,
Is it possible with Haskell to call a function whose name is contained
in a String?
Something like:
five = call_func "add" [2, 3]
You could use Data.Map:
call_func = (funcMap !)
where funcMap = fromList [ ("add", add)
Günther Schmidt wrote:
data Container a = Single a | Many a [a]
but the problem above is that the data structure would allow to
construct a Many 5 [] :: Container Int.
I think you meant to do either
data Container a = Single a | Many a (Container a)
or
data Container a = Con
Keith Sheppard wrote:
Is there any reason that sum isn't strict? I can't think of any case
where that is a good thing.
Prelude> sum [0 .. 100]
*** Exception: stack overflow
As others have said, there are cases where non-strictness is what you
want. And if you are using a type that is stri
Rouan van Dalen wrote:
It is important to store only a reference to the parent and not a copy of the
entire parent for efficiency.
Others have already recommended the rosezipper package, which gives you
what you want, but I want to address one thing.
foo =
bar = foo
In most implem
Jon Strait wrote:
I'm reading the third (bind associativity) law for monads in this form:
m >>= (\x -> k x >>= h) = (m >>= k) >>= h
Arguably, that law would be better stated as:
(h <=< k) <=< m = h <=< (k <=< m)
This wouldn't be so unintuitive.
- Jake
___
Hans van Thiel wrote:
The only place I've ever seen Kleisli composition, or its flip, used is
in demonstrating the monad laws. Yet it is so elegant and, even having
its own name, it must have some practical use. Do you, or anybody else,
have some pointers?
I only just started finding places to
Jake McArthur wrote:
Generally, you can transform anything of the form:
baz x1 = a =<< b =<< ... =<< z x1
into:
baz = a <=< b <=< ... <=< z
I was just looking through the source for the recently announced Hyena
library and decided to give a mor
Hans van Thiel wrote:
Just to show I'm paying attention, there's an arrow missing, right?
(.) ::(b -> c) -> (a -> b) -> (a -> c)
Correct. I noticed that after I sent it but I figured that it would be
noticed.
I also used (>>>) where I meant (>=>) at the bottom. The
Paulo J. Matos wrote:
As you can see, I had just finished installing alex 2.3.1, so why does
cabal still request alex >=2.0.1 && <3?
Probably you don't have alex in your PATH.
- Jake
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.h
Linker wrote:
Hugs> [0,0.1..1]
[0.0,0.1,0.2,0.3,0.4,0.5,0.6,0.7,0.8,0.9,1.0]
>
Prelude> [0,0.1..1]
[0.0,0.1,0.2,0.30004,0.4,0.5,0.6,0.7,0.7999,0.8999,0.]
Just floating point errors. In this case, you may be able to get away
with something l
Michael Vanier wrote:
Haskell is a wonderful language (my favorite language by far) but it is
pretty difficult for a beginner. In fact, it is pretty difficult for
anyone to learn in my experience, because it has so many advanced
concepts that simply don't exist in other languages, and trying t
I think there are some basic equivalents in the TypeCompose and
category-extras packages, for the record, but a standalone version
wouldn't hurt either!
- Jake
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listi
Iain Barnett wrote:
data Task = Task { title :: String, completed :: Bool, subtasks :: [Task] }
This one looks the best to me. Remember, you can just use an empty list
if the task has no subtasks.
- Jake
___
Haskell-Cafe mailing list
Haskell-Cafe@h
Actually, how about this?
import Data.Tree
newtype Task = Task (Tree (String, Bool))
Now you already have that tree structure you wanted.
- Jake
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/has
Don Stewart wrote:
leaveye.guo:
Hi haskellers:
There is a mistake in http://www.haskell.org/haskellwiki/State_Monad
It post two functions like this :
evalState :: State s a -> s -> a
evalState act = fst $ runState act
execState :: State s a -> s -> s
execState act = snd $ runState ac
Job Vranish wrote:
What I am trying to do is hyper unusual and I really do need an
unsafeHorribleThings to do it.
Normally when I really, honestly think this, I'm wrong anyway.
- Jake
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.
The monoids package offers something similar to this:
mapReduce :: (Generator c, Reducer e m) => (Elem c -> e) -> c -> m
If we take (Elem c) to be (item), (e) to be (item'), (c) to be (full),
and (m) to be (full'), it's basically the same thing, and offers the
same advantages as the ones y
Jake McArthur wrote:
The monoids package offers something similar to this:
mapReduce :: (Generator c, Reducer e m) => (Elem c -> e) -> c -> m
If we take (Elem c) to be (item), (e) to be (item'), (c) to be (full),
and (m) to be (full'), it's basically the same
John Lato wrote:
This looks to be essentially the same as the 'map' function in
ListLike, and suffers from the same problem. It won't have the
performance characteristics of the native map functions. Using e.g.
ByteStrings, you're recreating a ByteString by snoc'ing elements.
Oh, I see now wh
Colin Paul Adams wrote:
One problem will be to get GHC ported to DragonFly BSD, but that can
wait until I have a test version of the site working on Linux.
I would love to see this. It's the biggest thing blocking me from trying
Dragonfly more seriously.
WASH attracts me, with it's guarante
I forgot to also mention this somewhat recent announcement for a
pedantically type safe HTML library:
http://www.haskell.org/pipermail/haskell-cafe/2009-August/064907.html
- Jake
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskel
staafmeister wrote:
Yes I know but there are a lot of problems requiring O(1) array updates
so then you are stuck with IO again
Or use ST. Or use IntMap (which is O(log n), but n is going to max out
on the integer size for your architecture, so it's really just O(32) or
O(64), which is really
On Nov 17, 2007, at 11:26 AM, Stefan O'Rear wrote:
The STG-machine was brilliant when it was designed, but times have
changed. In particular, indirect jumps are no longer cheap. Pointer
tagging has allowed STG to hobble into the 21st century, but really
the
air is ripe for a new abstract ma
On Dec 19, 2007, at 6:25 PM, John Meacham wrote:
On Tue, Dec 18, 2007 at 01:58:00PM +0300, Miguel Mitrofanov wrote:
I just want the sistem to be able to print one of these
expressions !
Its this too much to ask ?
Yes, 'cause it means you want to embed almost all source code
into the
compil
On Dec 28, 2007, at 10:18 PM, [EMAIL PROTECTED] wrote:
Quoting alex <[EMAIL PROTECTED]>:
I would like to do this:
class Foo t where
hi :: t -> Bool
class Foo t => Bar t where
hi x = True
This is arguably one of the most requested features in Haskell. The
only
reason
On Dec 30, 2007, at 8:24 AM, Joost Behrends wrote:
For adapting hws (one of the reasons for me to be here, not many
languages have
a native web server) to Windows i must work on time. In System.Time
i found
data ClockTime = TOD Integer Integer
2 questions arise here: Does this define "TOD"
On Dec 30, 2007, at 12:32 PM, Joost Behrends wrote:
Thanks to both fast answers.
there remain problems with Jakes mail for me. This:
When you define datatypes, you are essentially defining a type-level
constructors on the left hand side and (value-level) constructors on
the right hand side.
On Dec 31, 2007, at 6:50 AM, Cristian Baboi wrote:
On Mon, 31 Dec 2007 14:36:02 +0200, Joost Behrends <[EMAIL PROTECTED]
> wrote:
I forgot 2 things:
The distinction between '=' and '==' is much like in C, although
mixing
them up is not so dangerous like in C. ':=' and '=' like in Wirth
l
On Dec 31, 2007, at 9:53 AM, Paul Johnson wrote:
I'd advise against trying to make your program stricter because you
might suddenly find yourself building an entire 6GB structure in
memory before traversing it, which would not be a Good Thing.
I disagree. It might be the case that the _cont
On Dec 31, 2007, at 11:21 AM, Achim Schneider wrote:
Jake McArthur <[EMAIL PROTECTED]> wrote:
I disagree. It might be the case that the _contents_ of the data
structure are lazy, in which case I would say the relevant
constructor parameters should be made strict. As long as the
stru
On Jan 10, 2008, at 1:57 PM, Achim Schneider wrote:
Now don't make me think of using par on a beowolf cluster of ps3's.
Never in my life have I _literally_ drooled over using a programming
abstraction.
- Jake___
Haskell-Cafe mailing list
Haskell-
On Jan 20, 2008, at 1:03 PM, Yitzchak Gale wrote:
Generating an infinite list from a random generator "burns up"
the generator, making it unusable for any further calculations.
That's what the split function is for. ^_^
- Jake
___
Haskell-Cafe mail
On Jan 26, 2008, at 12:20 PM, jia wang wrote:
Graphics/HGL/Key.hs:57:7:
Could not find module `Graphics.Win32':
it is a member of package Win32-2.1.1.0, which is hidden
You need to install the Win32 package.
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Win32-2.1.0.0
-
Oops, I was hasty in typing those data definitions. They will not work
because they have no constructors. Sorry about that.
- Jake
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Let's try a different example. Let's start with a list designed to
hold numbers:
data NumericList a = Num a => [a]
Normally this would be fine. We can hold things like [1, 2, 3, 4, 5]
and [1.7, 5.3, 2.0, 99.1]. But what if we wanted to be able to hold
numbers with _different types_ in the
From: Jake McArthur <[EMAIL PROTECTED]>
Date: February 13, 2008 7:04:49 PM CST
To: Felipe Lessa <[EMAIL PROTECTED]>
Subject: Re: [Haskell-cafe] existential types
On Feb 13, 2008, at 11:15 AM, Felipe Lessa wrote:
On Feb 13, 2008 2:41 PM, Jake McArthur <[EMAIL PROTECTED]>
On 07/05/2010 04:48 PM, Yves Parès wrote:
3) Is there another library on hackage that handles images in a
functional way? (I mean not /all in IO/)
Check out graphics-drawingcombinators.
- Jake
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
ht
On 07/14/2010 05:01 PM, Victor Gorokhov wrote:
You can implement pure pointers on top of Data.Map with O(log n) time
Or on top of Data.IntMap with O(1) time. ;)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/list
On 07/15/2010 02:30 AM, Stephen Tetley wrote:
2010/7/15 Jake McArthur:
On 07/14/2010 05:01 PM, Victor Gorokhov wrote:
You can implement pure pointers on top of Data.Map with O(log n) time
Or on top of Data.IntMap with O(1) time. ;)
Unlikely...
From the docs, lookup is O(min(n,W
On 07/15/2010 05:33 PM, Victor Gorokhov wrote:
Thanks for an example! Probably, one can think about using Arrays
instead of Map or IntMap in order to achieve 'true' O(1) in pure. But
I suppose that there are some trouble with array expanding. Or
somebody would already make it.
Pure arrays hav
On 07/18/2010 08:27 AM, Ivan Lazar Miljenovic wrote:
When discussing a similar issue with Manuel Chakravarty, he convinced me
that cunning newtype deriving is actually rather bad in practice and
shouldn't be used as there's a lack of proofs or some such (I can't
remember the arguments, but I reme
Just wanted to let everybody know that there is an AI contest [1] that
started today. Everybody has about two months to create bots that
compete against each other 1-on-1 in a game based on Galcon [2].
A couple issues to mention for full disclosure: There is some
sponsorship by Google, but unf
On 09/18/2010 02:51 AM, Christopher Tauss wrote:
I am trying to write a function that takes a list and returns the last n
elements.
This may just be for the sake of learning, in which case this is fine,
but usually, needing to do this would be a sign that you are using lists
improperly (sinc
On 10/08/2010 04:23 PM, Alex Rozenshteyn wrote:
Does there exist a library which allows me to have maps whose elements
are maps whose elements ... with a convenient syntax.
It sounds like you might be looking for a trie of some sort. Would
something like the TrieMap package suit your needs? It
What you describe sounds like a perfect job for a trie, so that's what I
think you should look into.
- Jake
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
`return :: rec -> Query state rec`.
I hope this helps lead you in the right direction. I'm not giving you
the solution because it sounds like you want to solve this for
yourself and learn from it.
- Jake McArthur
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Sep 4, 2008, at 10:19 AM, Tim Chevalier wrote:
The master programmer does not add strictness annotations, for she has
not yet run the profiler.
My guess would be that a master usually adds strictness annotations as
documentation rather than as optimizations.
- Jake McArthur
On Sep 4, 2008, at 9:52 PM, Tim Chevalier wrote:
I'm no master, but I've never encountered a situation where strictness
annotations would be useful as documentation, nor can I imagine one.
I'm no master either, but how about these simple examples?
data Stream a = Cons !a (Stream a
On Sep 4, 2008, at 11:23 PM, Jake Mcarthur wrote:
To quote a blog article[1] I wrote in June,
And of course I would forget to link the article. My bad.
[1] http://geekrant.wordpress.com/2008/06/23/misconceptions/
- Jake McArthur
___
Haskell-Cafe
On Sep 4, 2008, at 12:50 PM, minh thu wrote:
I'd have thought you wanted "IORef (Maybe Thing)", which says that
the
pointer always exists, but may not point to anything. On the other
hand
"Maybe (IORef Thing)" says that the pointer may or may not exist.
Yes, someone else said it too. But
and strictness exist in strict languages, as
well. What if, as a thought experiment, you tried substituting
"laziness" for "strictness" in that paragraph of your essay?
I think the same points would apply, honestly. Do you believe they
would change in some way?
- Jake McArthur
On Sep 5, 2008, at 12:45 AM, Tim Chevalier wrote:
On 9/4/08, Jake Mcarthur <[EMAIL PROTECTED]> wrote:
Two lazy algorithms tend to compose well and result in a lazy
algorithm. A lazy algorithm can compose with a strict algorithm in
two
different ways. One way is for the lazy algori
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
Most people seem far more confused by what a "fold" might be.
A fold by any other name would smell as sweet. ;)
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.8 (Darwin)
iEYEARECAAYFAkjYE7kACgkQTkPEVFd3yxh7HwCfVzopoOCgg49YI0Y88g9rjXqI
DvcAn3Buv
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
The first thing I thought of was to try to apply one of the recursion
schemes
in the category-extras package. Here is what I managed using
catamorphism.
- - Jake
-
---
John Van Enk wrote:
I had a co-worker ask me how you'd shoot your self in the foot with
Haskell. [...] Some one please give me something more worth of the
original list.
Couldn't match expected type 'Deer' against inferred type 'Foot'
- Jake
___
Hask
Andrew Coppin wrote:
But on the other hand, that would seem to imply that every monad is
trivially applicative, yet studying the libraries this is not the
case. Indeed several of the libraries seem to go out of their way to
implement duplicate functionallity for monad and applicative. (Hence
t
Andrew Coppin wrote:
(As an aside, Control.Monad.ap is not a function I've ever heard of.
It seems simple enough, but what an unfortunate name...!)
I think it makes sense. It stands for "apply," or at least that is what
I think of when I see it. If we have a function f :: A -> B -> C -> D
and
Andrew Coppin wrote:
I was thinking more, why not just delete MonadPlus completely, and
have any function that needs a monad that's also a monoid say so in
its context? (Obviously one of the answers to that is "because it
would break vast amounts of existing code".)
Because they are not the sa
On Oct 8, 2008, at 1:36 AM, Luke Palmer wrote:
What's the background for this abstraction?
So like I said, I'm not too sure, I just stole the name and vague
idea from discussions about it.
I believe IVar or something similar used to be in the standard GHC
libraries a long time ago. Conal
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
On Oct 8, 2008, at 7:28 AM, Jake Mcarthur wrote:
I'm attaching one of the more well-known variants in case anybody
is interested, although to be honest I can't remember which one was
actually the best as I have moved on from this app
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
roger peppe wrote:
> I was wondering if it was possible to implement synchronous channels
> within STM. In particular, I'd like to have CSP-like send and recv primitives
> on a channel that each block until the other side arrives to complete
> the tran
On Oct 11, 2008, at 2:54 PM, Bit Connor wrote:
Smart constructors are nice but if your module doesn't also export the
regular constructor then you can't pattern match against it.
It would be cool if there was a way to export constructors from a
module, but only for use in pattern matching and
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
Jefferson Heard wrote:
> I have the following functions in C:
>
> OGRErrOGR_G_CreateFromWkb (unsigned char *, OGRSpatialReferenceH,
> OGRGeometryH *, int)
> OGRErrOGR_G_CreateFromWkt (char **, OGRSpatialReferenceH,
> OGRGeometryH *)
>
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
Jefferson Heard wrote:
> Sadly, nothing so awesome... OGR is part of GDAL, an open-source
> geographic information system suite.
>
> On Fri, Oct 17, 2008 at 3:22 PM, Jake McArthur <[EMAIL PROTECTED]> wrote:
>> Are these Og
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
On Nov 10, 2008, at 3:15 AM, Hugo Pacheco wrote:
Perhaps this effort could be targeted at creating a cabal package in
Hackage
It's already there. :)
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/frag
- - Jake
-BEGIN PGP SIGNATU
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
On Nov 11, 2008, at 10:45 AM, Colin Paul Adams wrote:
Is there a way to call Haskell code from other languages? I have
looked on
the wiki, and as far as I can see, it only talks about the other way
round (when Haskell is the main program).
http:
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
Actually, that's not the whole story. I didn't realize until I sent
it. There does exist good documentation for this, I promise.
- - Jake
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.8 (Darwin)
iEYEARECAAYFAkkZuHoACgkQye5hVyvIUKnGeACfZN+9nNy
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
On Nov 12, 2008, at 7:09 AM, Lennart Augustsson wrote:
It's possible that there's some more direct approach that represents
types as some kind of runtime values, but nobody (to my knowledge) has
done that.
I think JHC passes types at runtime, usin
Bulat Ziganshin wrote:
Just to note, the comment about md5 is incorrect. I switched to SHA512
as you can see in the code.
really? :)
Right s -> -- return . show . md5 . L.pack $ p ++ s
Yes, really. If you look carefully, it is commented out. ;)
- Jake
signature.asc
Description: OpenP
Andrew Coppin wrote:
Don Stewart wrote:
Noteworthy,
* lhc-20081121: “Lhc Haskell Compiler”
Interesting. I can't find out any information about this...
It is a fork of the JHC compiler, which should be easier to look up.
There is also Hugs, as you mentioned. In addition, yo
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
On Nov 30, 2008, at 9:03 AM, Andrew Coppin wrote:
OK, so here's something just for fun:
Given a list of items, find all possible *unique* permutations of
that list. (E.g., the input list is explicitly _allowed_ to contain
duplicates. The output
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
On Nov 30, 2008, at 10:17 AM, Luke Palmer wrote:
On Sun, Nov 30, 2008 at 9:06 AM, Jake Mcarthur <[EMAIL PROTECTED]>
wrote:
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
On Nov 30, 2008, at 9:03 AM, Andrew Coppin wrote:
OK, so here'
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
On Nov 30, 2008, at 10:17 AM, Luke Palmer wrote:
On Sun, Nov 30, 2008 at 9:06 AM, Jake Mcarthur <[EMAIL PROTECTED]>
wrote:
Seems a bit easy, I think.
Data.List.permutations . nub
That is not what he meant. Given:
[1,1,2,2]
The r
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
On Dec 19, 2008, at 7:40 AM, Daniel Kraft wrote:
data Fraction = Fraction Int Int
to hold rational numbers (maybe there's already some built-in type
for this in Haskell, much like for instance Scheme has a rational
type?),
There is one. It is
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
Paul Keir wrote:
> fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
This is a CAF (Constant Applicative Form). Since it is actually a
constant it is never garbage collected, and is always shared, so each
thread is only calculating it once. You have essenti
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
Paul Keir wrote:
> Thanks Luke, and everyone else. Ok, back to the drawing board.
You may be interested in this:
http://cgi.cse.unsw.edu.au/~dons/blog/2007/11/29
- - Jake
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.9 (GNU/Linux)
Comment: Using
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
Brent Yorgey wrote:
> 50. file://localhost/home/brent/hacking/hwn/20081225.html
:(
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.9 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org
iEYEARECAAYFAklVLPgACgkQye5hVyvIUKk2AQ
Hans van Thiel wrote:
However, some functions in Haskell may have side effects, like printing
something on the screen, updating a database, or producing a random
number. These functions are called 'actions' in Haskell.
Not really true (disregarding things like unsafePerformIO). I haven't
been
Tom Pledger wrote:
Andrew Wagner gmail.com> writes:
I'm sure there's a way to do this, but it's escaping me at present. I
want to do something like this:
data Foo = Bar a => Foo a Bool ...
That is, I want to create a new type, Foo, whose constructor takes
both a Boolean and a value of a
Andrew Wagner wrote:
Hmm, I actually simplified my problem too much. What I actually want is:
data Foo a = forall a. Bar a => Foo a Bool
...except I want the 'a' on the left to match the 'a' on the right, so
that you can only construct values out of values of the parameterized
type, which also
Henning Thielemann wrote:
In case someone cares - after some battles with functions that are less
lazy than expected, I have written a tutorial on how to get functions
lazy and how to test, whether they are actually lazy:
http://www.haskell.org/haskellwiki/Maintaining_laziness
This is exce
Henning Thielemann wrote:
I found it especially enlightening, that one can avoid a 'force'
function in a lazy parser by making the possibility of a parser failure
explicit in its type. I.e. a parser that cannot fail, need no 'force'.
(I learnt that in polyparse the 'force' function is hidden in
Günther Schmidt wrote:
And that I find to be the really tricky part, how do I *design* a DSL?
My favorite approach is something like as described in these:
http://lukepalmer.wordpress.com/2008/07/18/semantic-design/
http://conal.net/papers/type-class-morphisms/
It takes a little bit of ti
If you could throw it on Hackage or a public repo you will get more
exposure. :)
- Jake
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Tobias Bexelius wrote:
I've put a simple GPipe example (including a screenshot) on the
haskellwiki now, showing off an animated spinning box.
Nice to see Data.Vec.LinAlg.Transform3D! That will be a big help. I'm
having fun with GPipe. Thanks for the library!
- Jake
__
Martijn van Steenbergen wrote:
It doesn't work for this one:
newtype Split a = Split { runSplit :: [Either a (Char, Split a) ]}
But my handwritten instance remains identical.
The instance has the form [], not the form [Either _ (Char, Split _)].
Since they don't match exactly, it won't giv
1 - 100 of 216 matches
Mail list logo