On Wed, 12 Mar 2008, Don Stewart wrote:
I am under the restriction that I need to write Haskell programs using
Double which mimic existing C/C++ programs or generated data sets, and
get the same answers. (It's silly, but take it as a given
requirement.) If the C programs are using "log2", the
On Wed, 12 Mar 2008, Donn Cave wrote:
On Mar 12, 2008, at 2:10 PM, Henning Thielemann wrote:
On Wed, 12 Mar 2008, Donn Cave wrote:
On Mar 12, 2008, at 12:32 PM, Brandon S. Allbery KF8NH wrote:
On Mar 12, 2008, at 14:17 , Donn Cave wrote:
Sure. It isn't a lot of code, so I subjected it t
On Wed, Mar 12, 2008 at 4:45 PM, Donn Cave <[EMAIL PROTECTED]> wrote:
> Well, the problem inherently requires a certain order of
> evaluation. But if you will just handle pattern match failure
> in the IO monad, then you can write a simple functional
> expression of the problem instead,
>
>
schmong.org> writes:
> Hello,
> My name is Michael Litchard. I'm a techie living in silicon
> valley, and I want to move into tech writing. I've got the
> background, now I need a portfolio. I figured the best way to go
> is to attach myself to some open source projects,
Martin Hofmann wrote:
> Thanks a lot, this helps a bit, but access to function bodies is exactly
> what I need.
Then perhaps you might like the method of reconstructing bodies (of
possibly compiled) functions
http://okmij.org/ftp/Computation/Generative.html#diff-th
in the form of AST --
* Manuel M T Chakravarty <[EMAIL PROTECTED]> [2008-03-13 12:30:40+1100]
>> Indeed, a matrix library would be really nice. Before getting serious
>> about this, please take a very close look at how PETSc
>> (http://www-unix.mcs.anl.gov/petsc/) handles matrices. The
>> abstraction
>> is very impo
vigalchin:
>Hello,
>
> I have made modifications against an existing Haskell library and
>installed in my --prefix=$HOME. How do I specify to link against this test
>.a and not the "global" archive?
>
>Regards, vasili
Install with cabal and use the --user flag
Hello,
I have made modifications against an existing Haskell library and
installed in my --prefix=$HOME. How do I specify to link against this test
.a and not the "global" archive?
Regards, vasili
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.or
> I am under the restriction that I need to write Haskell programs using
> Double which mimic existing C/C++ programs or generated data sets, and
> get the same answers. (It's silly, but take it as a given
> requirement.) If the C programs are using "log2", then I need "log2"
> in the Haskell, or
On Mar12, [EMAIL PROTECTED] wrote:
> G'day all.
>
> Quoting David Menendez <[EMAIL PROTECTED]>:
>
> >Adrian is arguing that compare a b == EQ should imply compare (f a) (f
> >b) == EQ for all functions f (excluding odd stuff). Thus, the problem
> >with your example would be in the Ord instance, n
Hugo Pacheco:
Hi have tried with all versions until ghci-6.9.20080303 (from the
nightly builds), is that the one?
Yep, that one is fine.
I'm sorry but where in the darcs repo can I find it? I cannot find a
ghc-6.9 branch.
6.9 is not a branch, it is the main repository; ie,
http://darcs.h
G'day all.
Quoting David Menendez <[EMAIL PROTECTED]>:
Adrian is arguing that compare a b == EQ should imply compare (f a) (f
b) == EQ for all functions f (excluding odd stuff). Thus, the problem
with your example would be in the Ord instance, not the sort function.
Understood, and the Schwar
On Wed, Mar 12, 2008 at 7:48 PM, <[EMAIL PROTECTED]> wrote:
> Adrian Hey wrote:
>
> >> This might be a reasonable thing to say about *sortBy*, but not sort
> >> as the ordering of equal elements should not be observable (for any
> >> correct instance of Ord). It should be impossible to impleme
Roman Leshchinskiy:
Bas van Dijk wrote:
A bit offtopic but slightly related:
I just added a GSoC project proposal about adding a nVidia CUDA
backend to Data Parallel Haskell:
http://hackage.haskell.org/trac/summer-of-code/ticket/1537
It would be great if this physics engine or matrix library cou
Jed Brown:
On 12 Mar 2008, [EMAIL PROTECTED] wrote:
I don't think there are a great deal of Haskell users who _really_
need a physics engine right now. However, there seem to be a massive
number who are working with matrices. I am informed that a lot of
physics is just matrix stuff underneath (b
chak:
> Don Stewart:
> >I'd chime in here -- actually getting arrays and parallel arrays with
> >list-like interfaces, and then onto matrices, will impact a lot of
> >people's work, in a good way.
>
> I am not quite sure what you mean with a list-like interface. NDP/DPH-
> style arrays are exac
quark:
> I have two questions about using the Double data type and the
> operations in the Floating typeclass on a computer that uses IEEE
> floating point numbers.
>
> I notice that the Floating class only provides "log" (presumably log
> base 'e') and "logBase" (which, in the latest source that
Hi have tried with all versions until ghci-6.9.20080303 (from the nightly
builds), is that the one?
I'm sorry but where in the darcs repo can I find it? I cannot find a
ghc-6.9branch.
Thanks,
hugo
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
ht
Don Stewart:
I'd chime in here -- actually getting arrays and parallel arrays with
list-like interfaces, and then onto matrices, will impact a lot of
people's work, in a good way.
I am not quite sure what you mean with a list-like interface. NDP/DPH-
style arrays are exactly like Haskell lis
Hi Hugo,
I have found a bug on the compiler (at least ghc >6.8.2). For some
module (yes, the example does nothing at all):
module Test where
data Type a where
Func :: Type a -> Type b -> Type (a -> b)
PF :: Type a -> Type (PF a)
data PF a where
ID :: PF (a -> a)
test :: Type a
G'day all.
Quoting askyle <[EMAIL PROTECTED]>:
If you use this presentation you also need the following law:
(a . b) >=> c = (a >=> c) . b
that is, compatibility with ordinary function composition. I like to call
this "naturality", since it's instrumental in proving return and bind to be
natu
I have two questions about using the Double data type and the
operations in the Floating typeclass on a computer that uses IEEE
floating point numbers.
I notice that the Floating class only provides "log" (presumably log
base 'e') and "logBase" (which, in the latest source that I see for
GHC is de
There's an effort going on to use techniques from Lava (the Haskell-
based hardware description language) to target GPUs. Joel Svensson
[1] has written his Master's thesis on this and is now working on
this for his PhD, so if you ask kindly he might tell you more about
this or send you the
In OCaml you have sort and fastsort - the latter doesn't have to be stable.
It currently is, because fastsort = sort.
I think it is a good thing to leave people an option, if there is something
important to choose.
On Thu, Mar 13, 2008 at 12:48 AM, <[EMAIL PROTECTED]> wrote:
> G'day all.
>
> Adri
G'day all.
Adrian Hey wrote:
This might be a reasonable thing to say about *sortBy*, but not sort
as the ordering of equal elements should not be observable (for any
correct instance of Ord). It should be impossible to implement a
function which can discriminate between [a,a],[a,b],[b,a],[b,b]
Bas van Dijk wrote:
A bit offtopic but slightly related:
I just added a GSoC project proposal about adding a nVidia CUDA
backend to Data Parallel Haskell:
http://hackage.haskell.org/trac/summer-of-code/ticket/1537
It would be great if this physics engine or matrix library could run
on a CUDA en
Neil Mitchell wrote:
Hi
I'm looking for interesting project to work on during Google Summer of
Code. So I found [1]"A data parallel physics engine" ticket and got
excited about it. I'd like to know interested mentors and community
opinion about the complexity of such project.
I don't think
On Wed, Mar 12, 2008 at 3:49 PM, Adam Langley <[EMAIL PROTECTED]> wrote:
> The OpenID example is running in EC2[4] at the moment if anyone wants to
> play.
Well, thanks to all the people who hit it, there's nothing like users
to find the stupid bugs ;)
* Caching was wrong on the front page, s
On Wed, Mar 5, 2008 at 12:25 PM, Adam Langley <[EMAIL PROTECTED]> wrote:
> I'm
> working towards, is an OpenID consumer. Once I have that working, I'll
> do a second release. It's not that far off, it's just a question of
> time.
The darcs release of minihttp[1] can now do this. It's not a Hac
On 3/12/08, Don Stewart <[EMAIL PROTECTED]> wrote:
> One of the best things you could do would be to submit patches against
> the core library set where documentation is missing. Starting
> with things in base, array, containers, directory, filepath, pretty,
> time etc.
>
> That would likely h
On Mar 12, 2008, at 2:10 PM, Henning Thielemann wrote:
On Wed, 12 Mar 2008, Donn Cave wrote:
On Mar 12, 2008, at 12:32 PM, Brandon S. Allbery KF8NH wrote:
On Mar 12, 2008, at 14:17 , Donn Cave wrote:
Sure. It isn't a lot of code, so I subjected it to Either-ization
as an experiment, and I
On Wed, Mar 12, 2008 at 2:33 PM, Andrew Coppin
<[EMAIL PROTECTED]> wrote:
> Hanging around here, you really feel like you're at the cutting edge
> of... something... heh.
Another approach isn't to target a CUDA back end for Haskell but to
write an array library that builds computations that can
On Wed, Mar 12, 2008 at 10:27 PM, Don Stewart <[EMAIL PROTECTED]> wrote:
> Note there's already a project at UNSW, with a PhD student attached,
> doing an nvidia CUDA backend to Data Parallel Haskell.
Great, do you perhaps have a link to a page describing that project?
Then I can link to it from
On Wed, Mar 12, 2008 at 02:30:41PM -0700, Taral wrote:
> On 3/12/08, Neil Mitchell <[EMAIL PROTECTED]> wrote:
> > However, I don't believe this expression is type safe in Haskell.
>
> Using higher-order polymorphism:
>
> f (x :: forall a. a -> a) = x x
Interestingly, this doesn't work - f is a
On Wed, Mar 12, 2008 at 09:05:03PM +, Neil Mitchell wrote:
> Hi
>
> I'm trying to show that a system of rules for manipulating Haskell
> expressions is terminating. The rules can be applied in any order, to
> any subexpression - and there is a problem if there is any possible
> infinite sequen
Don Stewart wrote:
Note there's already a project at UNSW, with a PhD student attached,
doing an nvidia CUDA backend to Data Parallel Haskell.
Perhaps this could be factored in somehow? At least there's a source
of mentors here.
Aa... I'd forgotten what an exciting place the Haskell wor
On 3/12/08, Neil Mitchell <[EMAIL PROTECTED]> wrote:
> However, I don't believe this expression is type safe in Haskell.
Using higher-order polymorphism:
f (x :: forall a. a -> a) = x x
--
Taral <[EMAIL PROTECTED]>
"Please let me know if there's any further trouble I can give you."
-- Unkn
v.dijk.bas:
> 2008/3/10 Roman Cheplyaka <[EMAIL PROTECTED]>:
> > I'm looking for interesting project to work on during Google Summer of
> > Code. So I found [1]"A data parallel physics engine" ticket and got
> > excited about it. I'd like to know interested mentors and community
> > opinion abou
ndmitchell:
> Hi
>
> > I'm looking for interesting project to work on during Google Summer of
> > Code. So I found [1]"A data parallel physics engine" ticket and got
> > excited about it. I'd like to know interested mentors and community
> > opinion about the complexity of such project.
>
> I
Don Stewart wrote:
Oh, you want another process in the system to read the file while GHC is
writing to it?
That's the one. ;-)
[Well, not GHC but my GHC-compiled binary, but anyway...]
This works fine on unix systems -- and perhaps Neil, or
one of the other windows experts, can explain what
andrewcoppin:
>
> Nope. Just WriteMode. I'm trying to read the file from Notepad.exe while
> my Haskell program is still running - which takes about an hour.
>
Oh, you want another process in the system to read the file while GHC is
writing to it? This works fine on unix systems -- and perhaps
Lennart Augustsson wrote:
> Yes, I wish Haskell had a 1-tuple. The obvious syntax is already taken,
> but I could accept something different, like 'One a'.
Python's one-tuple syntax is (1,). The obvious difficulty with adapting
this notation to Haskell lies in how one might write the constructor
On Wed, 12 Mar 2008, Donn Cave wrote:
On Mar 12, 2008, at 12:32 PM, Brandon S. Allbery KF8NH wrote:
On Mar 12, 2008, at 14:17 , Donn Cave wrote:
Sure. It isn't a lot of code, so I subjected it to Either-ization
as an experiment, and I did indeed take the monad procedural route.
Monad !=
2008/3/12 Jed Brown <[EMAIL PROTECTED]>:
> It would be a shame to ...miss the very important point that a
> matrix is nothing more than a linear transformation between finite
> dimensional spaces.
I rate this obvious seeming fact as one of the most important things
I've learnt about numerical l
Don Stewart wrote:
andrewcoppin:
Don Stewart wrote:
Hey Andrew,
What are you trying to do? Read and write to the same file (if so, you
need to use strict IO), or are you trying something sneakier?
I have a long-running Haskell program that writes status information to
a log f
marco-oweber:
> Hi,
>
> I've read on haskell org about
> gcjni
> Haskel/Java VM bridge
> Lambada (< ghc 6.6.1)
>
> Do you know wether any of them can be compiled with ghc-6.8 ?
> If not does it need much effort to patch them?
>
None of these are maintained, as far as I'm aware, but the J
Hi
I'm trying to show that a system of rules for manipulating Haskell
expressions is terminating. The rules can be applied in any order, to
any subexpression - and there is a problem if there is any possible
infinite sequence.
The rule that is giving me particular problems is:
(\v -> x) y =>
andrewcoppin:
> Don Stewart wrote:
> >Hey Andrew,
> >
> >What are you trying to do? Read and write to the same file (if so, you
> >need to use strict IO), or are you trying something sneakier?
> >
>
> I have a long-running Haskell program that writes status information to
> a log file. I'd like
Hi,
I've read on haskell org about
gcjni
Haskel/Java VM bridge
Lambada (< ghc 6.6.1)
Do you know wether any of them can be compiled with ghc-6.8 ?
If not does it need much effort to patch them?
Sincerly
Marc Weber
___
Haskell-Cafe mailing list
H
Don Stewart wrote:
Hey Andrew,
What are you trying to do? Read and write to the same file (if so, you
need to use strict IO), or are you trying something sneakier?
I have a long-running Haskell program that writes status information to
a log file. I'd like to be able to open and read that
michael:
>
> Hello,
> My name is Michael Litchard. I'm a techie living in silicon
> valley, and I want to move into tech writing. I've got the
> background, now I need a portfolio. I figured the best way to go
> is to attach myself to some open source projects, and haskell
andrewcoppin:
> Hi Cafe.
>
> There's good news and there's bad news.
>
> The bad news is... I'm back. [Did I miss anything good?]
>
> The good news is... I have an actual question to ask as well.
>
> When I write to a file using System.IO, the file is locked for exclusive
> access. I gather th
On 2008-03-12, Adrian Hey <[EMAIL PROTECTED]> wrote:
> Aaron Denney wrote:
>> On 2008-03-11, Adrian Hey <[EMAIL PROTECTED]> wrote:
>>> Having tried this approach myself too (with the clone) I can confirm
>>> that *this way lies madness*, so in future I will not be making
>>> any effort to define or
Bas van Dijk wrote:
A bit offtopic but slightly related:
I just added a GSoC project proposal about adding a nVidia CUDA
backend to Data Parallel Haskell:
http://hackage.haskell.org/trac/summer-of-code/ticket/1537
It would be great if this physics engine or matrix library could run
on a CUDA ena
2008/3/10 Roman Cheplyaka <[EMAIL PROTECTED]>:
> I'm looking for interesting project to work on during Google Summer of
> Code. So I found [1]"A data parallel physics engine" ticket and got
> excited about it. I'd like to know interested mentors and community
> opinion about the complexity of su
Yes, I wish Haskell had a 1-tuple. The obvious syntax is already taken, but
I could accept something different, like 'One a'.
On Mon, Mar 10, 2008 at 11:17 PM, Dan Weston <[EMAIL PROTECTED]>
wrote:
> I understand the lack of distinction between a unit type and a 0-tuple,
> since they are isomorp
On Mar 12, 2008, at 12:32 PM, Brandon S. Allbery KF8NH wrote:
On Mar 12, 2008, at 14:17 , Donn Cave wrote:
Sure. It isn't a lot of code, so I subjected it to Either-ization
as an experiment, and I did indeed take the monad procedural route.
Monad != procedural, unless you insist on do not
I'd say that any polymorphic code that assumes that x==y implies x=y is
broken.
But apart from that, floating point numbers break all kinds of laws that we
might expect to hold. Even so, they are convenient to have instances of
various classes.
On Wed, Mar 12, 2008 at 7:31 PM, Adrian Hey <[EMAIL
Hello,
> >Prelude Data.Typeable> typeOf (\a -> (Just (a:"")))
> >(\a -> (Just (a:""))) :: Char -> Maybe [Char]
> >
> >Prelude Data.Typeable> getDomain $ typeOf (\a -> (Just (a:"")))
> >[Char]
> >
> >Prelude Data.Typeable>getCodomain $ typeOf (\a -> (Just (a:"")))
> >(May
Duncan Coutts <[EMAIL PROTECTED]> writes:
> To get something really compact we could use an index composed of three
> unboxed Int arrays.
To get something *really* compact, we could build a (kind of) suffix
array. That is, we do a lexical sort of the lines, and store the
sorted offsets of the l
Aaron Denney wrote:
On 2008-03-11, Adrian Hey <[EMAIL PROTECTED]> wrote:
Having tried this approach myself too (with the clone) I can confirm
that *this way lies madness*, so in future I will not be making
any effort to define or respect "sane", unambiguous and stable behaviour
for "insane" Eq/O
On Wed, Mar 12, 2008 at 12:12 PM, Krzysztof Kościuszkiewicz
<[EMAIL PROTECTED]> wrote:
> I have tried both Poly.StateLazy and Poly.State and they work quite well
> - at least the space leak is eliminated. Now evaluation of the parser
> state blows the stack...
>
> The code is at http://hpaste.o
On Mar 12, 2008, at 14:17 , Donn Cave wrote:
Sure. It isn't a lot of code, so I subjected it to Either-ization
as an experiment, and I did indeed take the monad procedural route.
Monad != procedural, unless you insist on do notation. Think of it
as composition (it may be easier to use (=<
Remi Turk wrote:
I wouldn't bet on it either:
Prelude> 0.0 == -0.0
True
Prelude> isNegativeZero 0.0 == isNegativeZero (-0.0)
False
Although isNegativeZero might be considered a ``private,
"internal" interface that exposes implementation details.''
Interesting example.
So is the correct concl
Jules Bean wrote:
Adrian Hey wrote:
This might be a reasonable thing to say about *sortBy*, but not sort
as the ordering of equal elements should not be observable (for any
correct instance of Ord). It should be impossible to implement a
function which can discriminate between [a,a],[a,b],[b,a],
On 12 Mar 2008, [EMAIL PROTECTED] wrote:
>> I'm looking for interesting project to work on during Google Summer of
>> Code. So I found [1]"A data parallel physics engine" ticket and got
>> excited about it. I'd like to know interested mentors and community
>> opinion about the complexity of such p
Hello,
> Thanks a lot, this helps a bit, but access to function bodies is exactly
> what I need. Or being more precise, I need the functionality of ghci's
> command ':t'. So functions that behave as follows, where everything is
> of course meta-represented in some way as ADT:
>
>Prelude Data.
On Mon, Mar 03, 2008 at 05:20:09AM +0100, Bertram Felgenhauer wrote:
> > Another story from an (almost) happy Haskell user that finds himself
> > overwhelmed by laziness/space leaks.
> >
> > I'm trying to parse a large file (>600MB) with a single S-expression
> > like structure. With the help of
Hi Cafe.
There's good news and there's bad news.
The bad news is... I'm back. [Did I miss anything good?]
The good news is... I have an actual question to ask as well.
When I write to a file using System.IO, the file is locked for exclusive
access. I gather this is as specified in the Haskell
I agree, I view == as some kind of equivalence relation in Haskell, and not
a congruence relation (which would force x==y => f x == f y).
Of course, the Haskell type system isn't strong enough to enforce anything
more than it being a function returning a boolean.
-- Lennart
On Wed, Mar 12, 2008
On Mar 12, 2008, at 6:34 AM, Brandon S. Allbery KF8NH wrote:
On Mar 11, 2008, at 14:27 , Donn Cave wrote:
readLDAPMessage s = let [(_, msgID), (tag, body)] = berList s in
LDAPMessage (berInt msgID) (readResponse tag body)
I go on to account for all the LDAP stuff I need in about
Hac4
4th Haskell Hackathon
April 11-13, 2008
Gothenburg, Sweden
http://haskell.org/haskellwiki/Hac4
Sponsored by Credit Suisse and Galois.
This is a
Ketil Malde wrote:
Adrian Hey <[EMAIL PROTECTED]> writes:
So really I think the docs have this backwards. It's sortBy that
implements a stable sort (assuming a suitably sane comparison function
I guess) and apparently sort is whatever you get from (sortBy compare).
But this is unduly restrictiv
Derek Gladding wrote:
Speaking as someone who often has to answer questions along the lines of
"why isn't my code generating the results I want on your system?", I
wouldn't call it evil, just "commonly mistaken for Real".
Yes, of course.
Double is an excellent example since it indicates that
Adrian Hey wrote:
Denis Bueno wrote:
On Tue, Mar 11, 2008 at 4:01 AM, Adrian Hey <[EMAIL PROTECTED]> wrote:
> and sorting is
> meant to be a permutation, so we happily have the situation where
this
> has a correct answer: 2.
> Anything else is incorrect.
Isn't 3 also a permutation? Why
On Mar 11, 2008, at 14:27 , Donn Cave wrote:
readLDAPMessage s = let [(_, msgID), (tag, body)] = berList s in
LDAPMessage (berInt msgID) (readResponse tag body)
I go on to account for all the LDAP stuff I need in about 60 lines
of that kind of thing, 1/3 of it devoted to declaration
Hi
> I'm looking for interesting project to work on during Google Summer of
> Code. So I found [1]"A data parallel physics engine" ticket and got
> excited about it. I'd like to know interested mentors and community
> opinion about the complexity of such project.
I don't think there are a grea
On Tue, 11 Mar 2008, Donn Cave wrote:
On Mar 10, 2008, at 5:48 PM, Jonathan Cast wrote:
On 10 Mar 2008, at 12:37 AM, Donn Cave wrote:
...
An exception is, for me, any state that isn't properly accounted for in
its
immediate context. openFile could return 'Maybe Handle', but it doesn't,
Dan Licata schrieb:
Does that help?
Yeah, it did - Thanks!
-
Philip
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
We are pleased to announce the first release candidate of wxHaskell
0.10.3.
This is the first update with binary packages available since June 2005,
and is the result of a great deal of work by a new team of contributors.
We are hoping to make a full release shortly, and issues and bug reports
ei
Adrian Hey <[EMAIL PROTECTED]> writes:
> So really I think the docs have this backwards. It's sortBy that
> implements a stable sort (assuming a suitably sane comparison function
> I guess) and apparently sort is whatever you get from (sortBy compare).
> But this is unduly restrictive on possible
"Dave Tapley" <[EMAIL PROTECTED]> writes:
> I've upgraded to bytestring-0.9.0.5 from Darcs, no improvement.
> Also this morning I tried using Data.HashMap with Bytestring's readInt
> and HashMap's hashInt.. The result was a Stack space overflow :(
That's not so good.
>> It works as required, lo
> Data.Typeable gives you most of what you want except for access to
> function bodies.
Thanks a lot, this helps a bit, but access to function bodies is exactly
what I need. Or being more precise, I need the functionality of ghci's
command ':t'. So functions that behave as follows, where everyt
Henning Thielemann wrote:
On Mon, 10 Mar 2008, Neil Mitchell wrote:
I would like to know if in fact there's any difference in practice
between (), [()], i.e. if in practice the difference matters.
Usually, not so much. A lot of Monad functions have _ variants, i.e.
mapM and mapM_. If you d
Hello,
Data.Typeable gives you most of what you want except for access to
function bodies.
-Jeff
On Tue, Mar 11, 2008 at 6:17 AM, Martin Hofmann
<[EMAIL PROTECTED]> wrote:
> I am trying to port a programme written in Maude, which is a reflective
> language based on rewriting logic ( http://ma
Hi guys,
I have found a bug on the compiler (at least ghc >6.8.2). For some module
(yes, the example does nothing at all):
*module Test where
data Type a where
Func :: Type a -> Type b -> Type (a -> b)
PF :: Type a -> Type (PF a)
data PF a where
ID :: PF (a -> a)
test :: Type a ->
On 2008-03-11, Adrian Hey <[EMAIL PROTECTED]> wrote:
> Neil Mitchell wrote:
>> Hi
>>
>>> (sort [a,b]) in the case we have: (compare a b = EQ)
>>>
>>> Which of the following 4 possible results are correct/incorrect?
>>> 1- [a,a]
>>> 2- [a,b]
>>> 3- [b,a]
>>> 4- [b,b]
>>
>> Fortunately the Ha
On Tue, 2008-03-11 at 11:13 +, Dave Tapley wrote:
> Just a few updates on this one:
>
> I've upgraded to bytestring-0.9.0.5 from Darcs, no improvement.
> Also this morning I tried using Data.HashMap with Bytestring's readInt
> and HashMap's hashInt.. The result was a Stack space overflow :(
>
dave.a.tapley:
> Hi all,
>
> I've been plugging away at this all day and some discussion in
> #haskell has been fruitless. Perhaps you have the inspiration to see
> what's happening!
>
> Concerning this minimal example:
> http://hpaste.org/6268
>
> It works as required, loading K/V pairs into a
I'm not sure whether this is the right branch of the thread for this post.
Maybe it belongs to a different thread altogether.
But here goes:
Maybe most of our gripes with floating point arithmetic (besides broken
implementations) is that we expect it to behave like Real arithmetic, and
when it do
> My favorite presentation of the monad laws is associativity of Kliesli
> composition:
> (a1 >=> a2) x = a1 x >>= a2 -- predefined in 6.8 control.monad
> -- The laws
> return >=> a= a
> a >=> return= a
> a >=> (b >=> c) = (a >=> b) >=> c
If you use this presentation you also nee
On Tue, Mar 11, 2008 at 4:13 AM, Dave Tapley <[EMAIL PROTECTED]> wrote:
> I've upgraded to bytestring-0.9.0.5 from Darcs, no improvement.
> Also this morning I tried using Data.HashMap with Bytestring's readInt
> and HashMap's hashInt.. The result was a Stack space overflow :(
Map is probably a
Hello,
My name is Michael Litchard. I'm a techie living in silicon
valley, and I want to move into tech writing. I've got the
background, now I need a portfolio. I figured the best way to go
is to attach myself to some open source projects, and haskell
has h
On Tue, Mar 11, 2008 at 01:43:36AM -0400, Brandon S. Allbery KF8NH wrote:
> On Mar 11, 2008, at 0:20 , Chaddaï Fouché wrote:
>> 2008/3/11, David Menendez <[EMAIL PROTECTED]>:
>>> I think Adrian is just arguing that a == b should imply f a == f b,
>>> for all definable f, in which case it doesn't *
Speaking as someone who often has to answer questions along the lines of
"why isn't my code generating the results I want on your system?", I
wouldn't call it evil, just "commonly mistaken for Real".
NaN breaks most assumptions about ordering:
(NaN <= _) == false
(NaN == _) == false
(NaN >= _)
On Mar 10, 2008, at 5:48 PM, Jonathan Cast wrote:
On 10 Mar 2008, at 12:37 AM, Donn Cave wrote:
...
An exception is, for me, any state that isn't properly accounted
for in its
immediate context. openFile could return 'Maybe Handle', but it
doesn't,
so the context demands a Handle or a
On Mon, Mar 10, 2008 at 11:48 PM, Manuel M T Chakravarty <
[EMAIL PROTECTED]> wrote:
> Roman Cheplyaka:
> > I'm looking for interesting project to work on during Google Summer of
> > Code. So I found [1]"A data parallel physics engine" ticket and got
> > excited about it. I'd like to know interest
That's simple Tom.
Imagine the factorial function for Int written as a paramorphism:
type instance F Int = Either One
instance (Mu Int) where
inn (Left _) = 0
inn (Right n) = succ n
out 0 = Left ()
out n = Right (pred n)
instance Functor (F Int) where
fmap _ (Left ()) = Left
Denis Bueno wrote:
On Tue, Mar 11, 2008 at 4:01 AM, Adrian Hey <[EMAIL PROTECTED]> wrote:
> and sorting is
> meant to be a permutation, so we happily have the situation where this
> has a correct answer: 2.
> Anything else is incorrect.
Isn't 3 also a permutation? Why is it incorrect?
B
On Tue, 11 Mar 2008, Hugo Pacheco wrote:
Yes, I have tried both implementations at the start and solved it by
choosing for the following:
type family F a :: * -> *
type FList a x = Either () (a,x)
type instance F [a] = FList a
instance (Functor (F [a])) where
fmap _ (Left _) = Left ()
fmap f (R
1 - 100 of 102 matches
Mail list logo