I am playing with using SYB to make generic indexed collections. The
current code is this:
data Syb = Syb [Dynamic] -- list of [Map val (Set a)]
empty item = Syb $ gmapQ (toDyn . emp item) item
where
emp::x->y->Map.Map y (Set.Set x)
emp x y = Map.empty
insert
Stefan O'Rear <[EMAIL PROTECTED]> wrote:
> On Thu, May 17, 2007 at 10:32:11PM -0500, Rob Hoelz wrote:
> > More questions from Rob regarding his mysterious bindings...
> >
> > So I've been reading the docs for the FFI, and it's my understanding
> > that foreign functions imported as "unsafe" are f
On Thu, May 17, 2007 at 10:32:11PM -0500, Rob Hoelz wrote:
> More questions from Rob regarding his mysterious bindings...
>
> So I've been reading the docs for the FFI, and it's my understanding
> that foreign functions imported as "unsafe" are faster, but they've got
> a problem with callbacks.
More questions from Rob regarding his mysterious bindings...
So I've been reading the docs for the FFI, and it's my understanding
that foreign functions imported as "unsafe" are faster, but they've got
a problem with callbacks. From what I read, I believe that I should
just make a foreign functio
Hello,
I just registered haskell-lang.org a week ago for 1 year. I was wondering if
anybody wants it, I am selling it for regular price i got it which is $8
from godaddy. If you have an account with godaddy, tranferring is easy and
free. If you dont have an account you can get one for free.
Than
eeoam:
> H|i,
>
> Does anyone know of a simple and straightforward way to use global
> variables in Haskell?
>
> E.
As other posters have said, you'll need to state what you're trying to
do. For one particular case, that of a program that needs access to
state over its lifetime, State monads ar
Jason Dagit wrote:
> On 5/17/07, Adrian Hey <[EMAIL PROTECTED]> wrote:
>> Jules Bean wrote:
>> >> BTW, this is the commonly the subject of flame wars on the Haskell
>> >> mailing lists because there appear to be many who passionately believe
>> >> and assert that so called "global variables" are (a
On Thu, 17 May 2007, Jason Dagit wrote:
Well, it seems to me that Haskell modules are actually very similar to
singletons. Perhaps all these problems with modules having top level
mutable state could be solved if Haskell modules were parameterizable
at "instantiation"? I'm not saying we should
On 5/17/07, Adrian Hey <[EMAIL PROTECTED]> wrote:
Jules Bean wrote:
>> BTW, this is the commonly the subject of flame wars on the Haskell
>> mailing lists because there appear to be many who passionately believe
>> and assert that so called "global variables" are (at best) unnecessary
>> and (at
Isaac Dupree <[EMAIL PROTECTED]> wrote:
>
> Isaac Dupree wrote:
> >> liftM2 (:)
> >> (peekCString =<< (linked_list_getdata ptr))
> >> (linkedListToHaskellStringList =<< linked_list_next ptr)
>
> formerly missing parenthesis fixed in the above before it bites you :(
>
> Isaac
Thanks for the
Isaac Dupree wrote:
>> liftM2 (:)
>> (peekCString =<< (linked_list_getdata ptr))
>> (linkedListToHaskellStringList =<< linked_list_next ptr)
formerly missing parenthesis fixed in the above before it bites you :(
Isaac
___
Haskell-Cafe mailing list
Rob Hoelz wrote:
> The problem I have with that is that I'd have to do something like this:
>
> str <- peekCString =<< (linked_list_getdata ptr)
> next <- linked_list_next ptr
> rest <- linkedListToHaskellStringList next
> return (str : rest)
Exactly! That's normal Haskell code!
>
> I don't like
Isaac Dupree <[EMAIL PROTECTED]> wrote:
> > linkedListToHaskellStringList :: LinkedList -> IO [String]
> > linkedListToHaskellStringList listPtr =
> > let convertList' ptr =
> convertList' :: LinkedList -> [IO String], I infer?
Correct.
> > if listIsNull ptr
> > then
> >
On Friday 18 May 2007 09:42, Dougal Stanton wrote:
> I just did a fresh pull of hpodder to see if there was still a bug in
> it that I just found in the feisty version. I ran
>
> > $ darcs get --partial http://darcs.changelog.org/hpodder
> > $ darcs annotate Commands/SetTitle.hs
> >
> > darcs faile
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
> linkedListToHaskellStringList :: LinkedList -> IO [String]
> linkedListToHaskellStringList listPtr =
> let convertList' ptr =
convertList' :: LinkedList -> [IO String], I infer?
> if listIsNull ptr
> then
> []
On 17/05/07, Brandon S. Allbery KF8NH <[EMAIL PROTECTED]> wrote:
just to cover the bases: cd hpodder?
Yes, did that! ;-) I realise it wasn't very clear from the snippet I
provided. This, however, is a direct copy-n-paste:
[EMAIL PROTECTED] hpodder $ ls
Commands COPYINGDB.hs Downloa
On May 17, 2007, at 17:42 , Dougal Stanton wrote:
$ darcs get --partial http://darcs.changelog.org/hpodder
$ darcs annotate Commands/SetTitle.hs
darcs failed: There is no file or directory named 'Commands/
SetTitle.hs'
just to cover the bases: cd hpodder?
--
brandon s. allbery [solaris,f
Hello again,
I'm still working on that binding, and I've come to a problem that I
just can't figure out. I'm sure it's staring me right in the face, so
I think another pair of eyes to take a look.
So if you look at my previous message, I defined a linked list data
type in C. I'm trying to conve
Albert Y. C. Lai wrote:
There is no reality about global variables. Global variables are
syntactic sugar for local variables. That is the reality we need to
think through. This syntactic sugar streamlines many practical programs
and is indeed valuable.
I agree that the use of the term "global
Well, actually, this was scanned from a book but the OCR process
wasn't 100% effective. So, I was hoping the list would easily
identify and replace the erronious characters.
Thanks for trying, anyway.
Paul
...would it not be faster to pick up the book and check what the OCR
got wrong? ;-)
N
Adrian Hey wrote:
We've been talking about
this problem for years, but nothing is ever done about it (a solution to
this problem isn't even on the agenda for Haskell' AFIAK).
The problem needs talking about, it's important.
My objection was the implication that top-level mutable state was the
I just did a fresh pull of hpodder to see if there was still a bug in
it that I just found in the feisty version. I ran
$ darcs get --partial http://darcs.changelog.org/hpodder
$ darcs annotate Commands/SetTitle.hs
darcs failed: There is no file or directory named 'Commands/SetTitle.hs'
Ther
There is no reality about global variables. Global variables are
syntactic sugar for local variables. That is the reality we need to
think through. This syntactic sugar streamlines many practical programs
and is indeed valuable.
___
Haskell-Cafe maili
You could also look at
http://haskell.org/haskellwiki/Introduction#Quicksort_in_Haskell
if the algorithm is all you're interested in, and not the particular
implementation.
On 5/17/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:
PR Stanley wrote:
> Well, actually, this was scanned from a book but t
PR Stanley wrote:
Well, actually, this was scanned from a book but the OCR process
wasn't 100% effective. So, I was hoping the list would easily identify
and replace the erronious characters.
Thanks for trying, anyway.
Paul
...would it not be faster to pick up the book and check what the OCR
Well, actually, this was scanned from a book but the OCR process
wasn't 100% effective. So, I was hoping the list would easily
identify and replace the erronious characters.
Thanks for trying, anyway.
Paul
At 20:46 17/05/2007, you wrote:
Well, I don't know if it is by encoding of letters in your
Hmm. I think you're going to have problems with thermodynamics here.
While it is possible to perform computations using chemical reactions,
an *energy source* is required to drive the process. The word
"nutrients" implies a substance containing chemical energy, but in that
case no garbage-colle
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
Adrian Hey wrote:
>>> They are necessary because they are the only way to ensure important
>>> safety properties of many IO APIs.
>>
>> That's a bold claim. It's very hard to prove that things don't exist.
>> (That is, that other ways to ensure these s
Well, I don't know if it is by encoding of letters in your e-mail, but
what do you expect that
[a | a . xs, a x ]
would do?
Dusan
PR Stanley wrote:
Yes, sorry, I missed the firt line of the algorithm when I was pasting
it into the email. Okay
qSort [] = [x]
-- and even
qSort [x] = x
The code
Yes, sorry, I missed the firt line of the algorithm when I was
pasting it into the email. Okay
qSort [] = [x]
-- and even
qSort [x] = x
The code fragment below still doesn't work.
qSort (x:xs) =
qSort smaller ++ [x] ++ qSort larger
where
smaller = [a | a . xs, a x ]
larger = [b
[EMAIL PROTECTED] wrote:
Incidentally, Hugs reports the overlapping errors eagerly. It would
still complain about the changed code, because the error is with
instances rather with their use.
Thankyou for your patience. I think I'm getting what's going on now.
The flags that allow undecidable or
What if the list is empty? You should take into account even this situation.
Dusan
PR Stanley wrote:
Hi folks
qSort (x:xs) =
qSort smaller ++ [x] ++ qSort larger
where
smaller = [a | a . xs, a x ]
larger = [b | b . xs, b > x ]
Any idea why I can't get this to work?
Thanks,
Paul
Hi folks
qSort (x:xs) =
qSort smaller ++ [x] ++ qSort larger
where
smaller = [a | a . xs, a x ]
larger = [b | b . xs, b > x ]
Any idea why I can't get this to work?
Thanks,
Paul
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http
Thanks, I had forgotten about multiple let bindings as something it
might be looking for. I guess in this case the curly braces aren't too
bad, given that this situation doesn't come up so much, and it would
let me keep the indentation consistent.
And yes, this is just a boiled-down version of th
On 17/05/07, Chad Scherrer <[EMAIL PROTECTED]> wrote:
But GHC complains of "Empty 'do' construct".
Because it takes the indented following lines as being new bindings in
the let-block. The trick is to intent them past the 'sum':
let b = sum $ do
y <- [0..x + 1]
return y
Or t
I've gotten into a habit of preceding most "do"s in my code with a
"$", and indenting the next line. I kind of like this, since it makes
the indentation more uniform. But it seems to have bitten me now. I'd
like to write something like this
s = sum $ do
x <- [1,2,3]
let b = sum $ do
y <- [0.
Jules Bean wrote:
BTW, this is the commonly the subject of flame wars on the Haskell
mailing lists because there appear to be many who passionately believe
and assert that so called "global variables" are (at best) unnecessary
and (at worst) are "evil". These people are quite simply wrong and
sho
On Thu, 17 May 2007 13:50:15 -0300
Maurício <[EMAIL PROTECTED]> wrote:
> Hi,
>
> Haskell language reference says the special -
> operator translates to negate. However, this:
>
> (+ negate 5) 5
Function application binds tightest, so this is equivalent to:
(+ (negate 5)) 5
>
> works but this
Eric <[EMAIL PROTECTED]> writes:
> H|i,
>
> Does anyone know of a simple and straightforward way to use
> global variables in Haskell?
No, no-one does. Global variables are neither simple nor
straightforward. :-P
In addition to what others have said (assuming you don't
just mean providing a nam
Hi,
Haskell language reference says the special -
operator translates to negate. However, this:
(+ negate 5) 5
works but this:
(+ -5) 5
is not valid. Why?
Thanks,
Maurício
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.o
On 17/05/07, Jules Bean <[EMAIL PROTECTED]> wrote:
I'd be willing to take a sportsman's bet that the original poster
does not actually need to use this hack; I doubt his application falls
into the categories you have outlined. I would discourage people from
using this hack unless it is, in fact,
Please take this message in the fashion that is intended. My criticism
is light hearted, as I believe yours is.
Adrian Hey wrote:
[hack snipped]
BTW, this is the commonly the subject of flame wars on the Haskell
mailing lists because there appear to be many who passionately believe
and assert
Eric wrote:
H|i,
Does anyone know of a simple and straightforward way to use global
variables in Haskell?
I assume what you're looking for is to be able to have IORefs,MVars
Chans etc at the top level. The standard (for want of a better word)
way to do this is known commonly known as the "uns
Eric wrote:
H|i,
Does anyone know of a simple and straightforward way to use global
variables in Haskell?
(Perhaps annoyingly) the answer to this question, like so many other
questions on this list, is a question. "What are you trying to do?".
The reason for this is that haskell's abstract
On Thu, May 17, 2007 at 02:41:33PM +0100, Eric wrote:
> Does anyone know of a simple and straightforward way to use global
> variables in Haskell?
Just declare them at the top level, as a function but without
arguments:
===
x =
On Thu, 17 May 2007 14:41:33 +0100
Eric <[EMAIL PROTECTED]> wrote:
> H|i,
>
> Does anyone know of a simple and straightforward way to use global
> variables in Haskell?
>
> E.
Another alternative, for "write-once variables", is implicit parameters.
--
Robin
__
You can also use mutable variables (MVars) found in Control.Concurrent.MVar
http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Concurrent-MVar.html
They might work depending on your implementation. The reading and
writing of MVars returns IO actions.
On 5/17/07, Dougal Stanton <[EM
On 17/05/07, Eric <[EMAIL PROTECTED]> wrote:
H|i,
Does anyone know of a simple and straightforward way to use global
variables in Haskell?
You can pass around an environment with the State or Reader monads
(read/write and read-only respectively). If you want to do IO with the
data you'll prob
eeoam:
> H|i,
>
> Does anyone know of a simple and straightforward way to use global
> variables in Haskell?
>
> E.
The usual way is to run the code that needs a global variable in a State monad.
The next answer is: you don't really need global variables, since you
don't have mutable variables
H|i,
Does anyone know of a simple and straightforward way to use global
variables in Haskell?
E.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Thu, May 17, 2007 at 11:22:34AM +0100, Simon Marlow wrote:
> sequence still isn't tail-recursive, although sequence_ is. If you want a
> tail-recursive sequence, the only way to do it is like this:
>
> sequence' :: [IO a] -> IO [a]
> sequence' ms = do
> let as = map unsafePerformIO ms
> f
Thanks a lot Mr. jules now the code is working perfectly for higher values
, the problem was with ord .
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
ashutosh dimri wrote:
func [] = []
func (x:xs)
|(ord x > 57) = ((ord x)-87):func xs
|otherwise = ((ord x)-48):func xs
Your problem is with the type of 'func'.
*Main> :t func
func :: [Char] -> [Int]
'Int' is a 32-bit type, on most systems. The thing that has forced your
type to I
Rob Hoelz wrote:
"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_getd
I have written a code to convert hexadecimal numbers into base 10 number
but its working only for 32 bits and I need it to work upto 160 bits , code
is given below. please help.
--its a program to convert hexadecimal numbers into base 10 numbers
import Char
-- the function "func" takes a list
Evan Laforge wrote:
>> 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 rDropWh
> From: [EMAIL PROTECTED]
> [mailto:[EMAIL PROTECTED] On Behalf Of John Meacham
> >
> > But then GHC would be faster then JHC! (Nobody cares about jhc,
> > certainly not enough to implement a recognizer for it...)
>
> Ah, but think of how much faster jhc development would be if it didn't
> take
| > But then GHC would be faster then JHC! (Nobody cares about jhc,
| > certainly not enough to implement a recognizer for it...)
|
| Ah, but think of how much faster jhc development would be if it didn't
| take ghc 20 minutes to compile it every time I made a change :)
Oh! A cruel jibe!
Simon
58 matches
Mail list logo