> Also, I suspect I'm still missing something important here, for
> example I don't understand why, if it overlaps for [], it doesn't
> overlap with other instances (like Maybe for example). Or am I
> just not getting the error for Maybe because ghc stops after
> the first error?
One may think of
Dear all,
I am pleased to announce version 0.4 of Dimensional (working name).
Dimensional is a library providing data types for performing
arithmetic with physical quantities and units. Information about the
physical dimensions of the quantities/units is embedded in their types
and the validity
cyril.schmidt:
> I noticed recently that the website of CUFP conference (Commercial Uses of
> Function Programming), which used to be at http://www.galois.com/cufp,
> is not accessible anymore.
>
> Does anybody know where it moved?
Try http://cufp.galois.com/
-- Don
_
Albert Y. C. Lai wrote:
A native G-machine --- physical, or chemical, or biological, but not a
repressed simulation over the imperative cpu-memory architecture --- is
the dream of every lazy-functional programmer of great devotion. If only
it became the dominant computing architecture! People w
Hi
It is worded as biotech but may as
well be molecular computing or nanotech.
biotech machines tend to be inaccurate, but highly parallel.
Unfortunately the G machine is very un-parallel and requires 100%
precision. Things like speculative evaluation may be more interesting.
To add garbage
On Wed, May 16, 2007 at 03:47:07PM -0700, Stefan O'Rear wrote:
> On Wed, May 16, 2007 at 03:41:30PM -0700, John Meacham wrote:
> > I look forward to the day when the OS will notice that a binary was
> > compiled from haskell, and therefore is provably not buggy due to
> > haskells strong type syste
On Wed, May 16, 2007 at 03:41:30PM -0700, John Meacham wrote:
> I look forward to the day when the OS will notice that a binary was
> compiled from haskell, and therefore is provably not buggy due to
> haskells strong type system. So it happily turns off all
> memory protection and lets it run on t
I look forward to the day when the OS will notice that a binary was
compiled from haskell, and therefore is provably not buggy due to
haskells strong type system. So it happily turns off all
memory protection and lets it run on the bare hardware at full speed. :)
This is not entirely unreasonable,
A native G-machine --- physical, or chemical, or biological, but not a
repressed simulation over the imperative cpu-memory architecture --- is
the dream of every lazy-functional programmer of great devotion. If only
it became the dominant computing architecture! People would say, Haskell
is hig
I think that in every particular case you have to find out how to avoid
'reverse'. Especially if you have two 'reverse's like in
reverse . dropWhile p . reverse
there are more efficient solutions.
Just from curiosity, what *is* an efficient way to do rDropWhile?
Here's something which at lea
Rob Hoelz wrote:
item <- linked_list_getdata listPtr
next <- linked_list_next listPtr
cStr <- peek item
hStr <- peekCString cStr
t <- linkedListToStringList next
return (hStr : t)
item <- linked_list_getdata listPtr
next <-
David House wrote:
On 16/05/07, Sergey Perminov <[EMAIL PROTECTED]> wrote:
How to solve task of reversing big list with constant heap space used?
I think that as lists are singly-linked in Haskell, reversing a list
will always be O(n) space.
You can do it in O(n^2) time and constant space,
On Wed, May 16, 2007 at 12:38:55AM -0400, Brandon S. Allbery KF8NH wrote:
>
> On May 16, 2007, at 0:35 , Rob Hoelz wrote:
>
> >wrapping returns time_t. I see that this maps to CTime in
> >Foreign.C.Types, but I can't figure out how to convert it to an Int
> >(or
> >any other useful Haskell typ
Pixel wrote:
from http://pleac.sourceforge.net/pleac_haskell/numbers.html#AEN118 :
-- "read" handles both octal and hexadecimal when prefixed with 0x or 0o
-- here are versions adding the prefix and calling "read"
hex s = read ("0x" ++ s) :: Integer
oct s = read ("0o" ++ s) :: Integer
-- hex "45
Hi
Is Graham Hutton's book on Haskell Programming a good text for FP beginners?
Yes.
There is a review in The Monad Reader:
http://www.haskell.org/sitewiki/images/0/03/TMR-Issue7.pdf
From the abstract:
"Do we need another introductory Haskell book? Is there anything new to be said
or a b
Hi,
Is Graham Hutton's book on Haskell Programming a good text for FP beginners?
Paul
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 16/05/07, Sergey Perminov <[EMAIL PROTECTED]> wrote:
How to solve task of reversing big list with constant heap space used?
I think that as lists are singly-linked in Haskell, reversing a list
will always be O(n) space.
--
-David House, [EMAIL PROTECTED]
"Brandon S. Allbery KF8NH" <[EMAIL PROTECTED]> wrote:
>
> On May 16, 2007, at 12:23 , Rob Hoelz wrote:
>
> > And as long as I'm asking, is there some kind of monadic function
> > composition operator? I'd like to clean up the above with something
> > like peekCString . peek . linked_list_getdat
On May 16, 2007, at 12:23 , Rob Hoelz wrote:
And as long as I'm asking, is there some kind of monadic function
composition operator? I'd like to clean up the above with something
like peekCString . peek . linked_list_getdata...
(=<<)?
--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell
Hello everyone,
You may have seen my message about how I'm writing a binding to a C
library. This is another question related to that.
So, let's say I have a linked list implemented in C. Here's what its
definition looks like:
struct __linked_list {
void *data;
struct __linked_list *ne
Eric ukfsn.org> writes:
>
> Hi there,
>
> I've written the following program
>
> putchr = putChar ?d
>
> main = do
> { c <- getChar
> ; putchr with ?d = c}
>
I think you're supposed to use a let binding, like this:
putchr :: (?d::Char) => IO ()
putchr = putChar ?d
main = do
c
"ashutosh dimri" <[EMAIL PROTECTED]> writes:
> how to convert a hexadecimal into base 10 integer using haskell . I have
> written a code but its not working for large values , please help
from http://pleac.sourceforge.net/pleac_haskell/numbers.html#AEN118 :
-- "read" handles both octal and hexa
On Wed, May 16, 2007 at 06:34:53PM +0530,
ashutosh dimri <[EMAIL PROTECTED]> wrote
a message of 34 lines which said:
> how to convert a hexadecimal into base 10 integer using haskell . I
> have written a code but its not working for large values , please
> help
Not showing the code you wrote w
how to convert a hexadecimal into base 10 integer using haskell . I have
written a code but its not working for large values , please help
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Wed, 16 May 2007, Sergey Perminov wrote:
> How to solve task of reversing big list with constant heap space used?
By avoiding 'reverse'?
> Amount of heap space used grows exponentially in following examples:
>
> 1:
> main = putStrLn.show.head $reverse [1..1000]
Data.List.last
I think
Dirk Kleeblatt wrote:
> apfelmus wrote:
>> Dirk Kleeblatt wrote:
>>> apfelmus wrote:
I also think that having liftIO in the CodeGen-monad is plain wrong. I
mean, CodeGen is a monad that generates code without any execution
>>>
>>> note that runCodeGen runs the code _generation_, executing
Adrian Hey wrote:
[EMAIL PROTECTED] wrote:
Adrian Hey wrote:
-- Instances of GT are instances of Eq --
instance (GT map key, Eq a) => Eq (map a) where
map1 == map2 = assocsAscending map1 == assocsAscending map2
...
Overlapping instances for Eq [(key, a)]
arising from use of `==' a
[EMAIL PROTECTED] wrote:
Adrian Hey wrote:
-- Instances of GT are instances of Eq --
instance (GT map key, Eq a) => Eq (map a) where
map1 == map2 = assocsAscending map1 == assocsAscending map2
...
Overlapping instances for Eq [(key, a)]
arising from use of `==' at Test.hs:10:16-59
Brandon S. Allbery KF8NH wrote:
On May 16, 2007, at 0:57 , Adrian Hey wrote:
-- GT class --
class Ord key => GT map key | map -> key where
assocsAscending :: map a -> [(key,a)] -- Just 1 of many methods
-- Instances of GT are instances of Eq --
Instances of Ord are instances of Eq, so defi
Tomasz Zielonka wrote:
On Wed, May 16, 2007 at 09:28:31AM +0100, Jules Bean wrote:
Tomasz Zielonka wrote:
You mean using the (Monoid b) => Monoid (a -> b) instance ?
I can see that IO () makes a perfect Monoid, but there doesn't seem to
be a standard instance for that.
Indeed, al
On Wed, May 16, 2007 at 09:28:31AM +0100, Jules Bean wrote:
> Tomasz Zielonka wrote:
> >You mean using the (Monoid b) => Monoid (a -> b) instance ?
> >I can see that IO () makes a perfect Monoid, but there doesn't seem to
> >be a standard instance for that.
>
> Indeed, all Monads are Monoids (that
Tomasz Zielonka wrote:
On Tue, May 15, 2007 at 06:55:11AM -0700, Conal Elliott wrote:
You could also use mappend instead of concatStmts and keep the Database ->
IO () representation.- Conal
You mean using the (Monoid b) => Monoid (a -> b) instance ?
I can see that IO () makes a per
On Wed, May 16, 2007 at 12:38:55AM -0400, Brandon S. Allbery KF8NH wrote:
> On May 16, 2007, at 0:35 , Rob Hoelz wrote:
>
> >wrapping returns time_t. I see that this maps to CTime in
> >Foreign.C.Types, but I can't figure out how to convert it to an Int
> >(or
> >any other useful Haskell type,
Adrian Hey wrote:
> -- Instances of GT are instances of Eq --
> instance (GT map key, Eq a) => Eq (map a) where
> map1 == map2 = assocsAscending map1 == assocsAscending map2
> ...
> Overlapping instances for Eq [(key, a)]
>arising from use of `==' at Test.hs:10:16-59
> Matching
On Tue, May 15, 2007 at 06:55:11AM -0700, Conal Elliott wrote:
> You could also use mappend instead of concatStmts and keep the Database ->
> IO () representation.- Conal
You mean using the (Monoid b) => Monoid (a -> b) instance ?
I can see that IO () makes a perfect Monoid, but there doesn't
How to solve task of reversing big list with constant heap space used?
Amount of heap space used grows exponentially in following examples:
1:
main = putStrLn.show.head $reverse [1..1000]
2 (GHC):
import Data.List
main = putStrLn.show.head $foldl' (flip (:)) [] [1..1000]
3 (GHC):
impor
36 matches
Mail list logo