Am Mittwoch 03 Juni 2009 06:12:46 schrieb Michael Snoyman:
> I made two changes:
>
> 1. You had the arguments to M.lookup backwards.
> 2. lookup does not return any generalized Monad, just Maybe (I think that
> should be changed).
Data.Map.lookup used to return a value in any monad you wanted, I
Henk-Jan van Tuyl wrote:
On Tue, 02 Jun 2009 23:45:18 +0200, Philippa Cowderoy
wrote:
Anglohaskell 2009 is go!
F.A.B. :)
Yes, excellent news, and this time I'll make sure to attend, especially since
it's back in Cambridge again.
/M
--
Magnus Therning(OpenPGP:
G'day Vasili.
This should do it:
remLookupFwd :: (ReVars m t) => SimplRe t -> ReM m t (ReInfo t)
remLookupFwd re
= do fwd <- gets resFwdMap
let { Just reinfo = fromJust (M.lookup re fwd) }
return reinfo
The FiniteMap lookup operation took its arguments in the opposite order.
Tha
Hi Michael,
Let me look tomorrow morning. In any case, many thanks!
Kind regards,
Vasili
On Tue, Jun 2, 2009 at 11:12 PM, Michael Snoyman wrote:
> > remLookupFwd :: (ReVars m t) => SimplRe t -> ReM m t (ReInfo t)
> > remLookupFwd re
> > = do fwd <- gets resFwdMap
> > -- let { Jus
> remLookupFwd :: (ReVars m t) => SimplRe t -> ReM m t (ReInfo t)
> remLookupFwd re
> = do fwd <- gets resFwdMap
> -- let { Just reinfo = M.lookup fwd re }--
PROBLEM
>reinfo <- liftMaybe $ M.lookup re fwd --
PROBLEM
>return reinfo
>
>
Hello Haskellers,
I isolated to a not so small piece:
> {-# OPTIONS -fglasgow-exts #-}
> {-# LANGUAGE UndecidableInstances #-}
> import Control.Monad.Identity
> import Control.Monad.Reader
> import Control.Monad.State
> import qualified Data.List as L
> import qualified Data.Map as M
> impo
Luke's answer is great (although it changes argument order). Hint:
http://www.haskell.org/haskellwiki/Things_to_avoid#Avoid_explicit_recursion
I also like the "pattern guards" GHC extension; I tend to use it over
"maybe" and "either". I find the resulting code more readable:
> {-# LANGUAGE Patte
Ryan Ingram wrote:
Dan wrote:
> I figured there would be a clever Haskell idiom that would give me a
> similarly concise route. Does it really require Template Haskell? I can
> barely parse regular Haskell as it is..
[...]
Alternatively, you can define a fold[1] once:
myval :: MyVal -> (Bool
michael rice wrote:
> Finally got adventurous enough to get Cabal working, downloaded the
> primes package, and got the following error message when trying
> isPrime. Am I missing something here?
The Data.Numbers.Primes module of the primes package does not implement
'isPrime'. The Numbers packag
> where next = probePhase ...
> key = ...
>
Argh, I really wish Gmail would allow me to compose in a fixed with
width font! Does anyone know of a setting or something that I'm
missing?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
h
Finally got adventurous enough to get Cabal working, downloaded the primes
package, and got the following error message when trying isPrime. Am I missing
something here?
Michael
==
[mich...@localhost ~]$ ghci
GHCi, version 6.10.1: http://www.haskell.org/ghc/ :? for help
Loadin
On Wed, Jun 3, 2009 at 8:59 AM, Nico Rolle wrote:
> hi there
>
> heres a code snipped, don't care about the parameters.
> the thing is i make a lookup on my map "m" and then branch on that return
> value
>
> probePhase is sc [] m = []
> probePhase is sc (x:xs) m
> | val == Nothing = probePhas
I just noticed that my suggestion doesn't work. You're testing whether
val is Nothing and in my code snipped val has a different type.
On 6/3/09, Raynor Vliegendhart wrote:
> If you're absolutely certain that the lookup always succeeds, then you
> can use pattern matching as follows:
>
>
>
On Tue, Jun 2, 2009 at 4:59 PM, Nico Rolle wrote:
> hi there
>
> heres a code snipped, don't care about the parameters.
> the thing is i make a lookup on my map "m" and then branch on that return
> value
>
> probePhase is sc [] m = []
> probePhase is sc (x:xs) m
>| val == Nothing = probePhas
If you're absolutely certain that the lookup always succeeds, then you
can use pattern matching as follows:
where
jr = joinTuples sc x val
key = getPartialTuple is x
Just val = Map.lookup key m
On 6/3/09, Nico Rolle wrote:
> hi there
>
> heres a code s
hi there
heres a code snipped, don't care about the parameters.
the thing is i make a lookup on my map "m" and then branch on that return value
probePhase is sc [] m = []
probePhase is sc (x:xs) m
| val == Nothing = probePhase is sc xs m
| otherwise = jr ++ probePhase is sc xs m
On Tue, 02 Jun 2009 23:45:18 +0200, Philippa Cowderoy
wrote:
Anglohaskell 2009 is go!
F.A.B. :)
--
Regards,
Henk-Jan van Tuyl
--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
ht
We're pleased to announce the second release of the Haskell Platform: a
single, standard Haskell distribution for everyone.
The specification, along with installers (including Windows and Unix
installers for a full Haskell environment) are available.
Download the Haskell Platform 2009.2.0.1:
Anglohaskell 2009 is go! I'm taking on the mantle of organiser, and
Microsoft Research have offered us space for talks in Cambridge again.
The event will be held on the 7th and 8th of August. More info at
http://www.haskell.org/haskellwiki/AngloHaskell/2009 , planning and
discussion in #anglohaskel
On Tue, Jun 2, 2009 at 2:07 PM, David Leimbach wrote:
>
>
> On Tue, Jun 2, 2009 at 1:56 PM, Thomas DuBuisson <
> thomas.dubuis...@gmail.com> wrote:
>
>> Again, I can't reproduce your problem. Are you getting data through
>> some previous Binary instance before calling the routines you show us
>>
It will run the instance of the inferred type (or you can provide a
type signature to force it). I've done this often before with lists -
trying to read in some arbitrary, typically high, number of elements
causes issues :-)
Thomas
On Tue, Jun 2, 2009 at 2:07 PM, David Leimbach wrote:
>
>
> On
On Tue, Jun 2, 2009 at 1:56 PM, Thomas DuBuisson wrote:
> Again, I can't reproduce your problem. Are you getting data through
> some previous Binary instance before calling the routines you show us
> here?
Ah good question... I'm calling "decode", but it's not clear that it's even
running my i
0.5.0.1
On Tue, Jun 2, 2009 at 1:56 PM, John Van Enk wrote:
> Just so we know that it's not the issue, what version of binary are
> you using? The most current one is 0.5.0.1.
>
> On Tue, Jun 2, 2009 at 4:46 PM, David Leimbach wrote:
> >
> >
> > On Tue, Jun 2, 2009 at 1:36 PM, John Van Enk wrot
Just so we know that it's not the issue, what version of binary are
you using? The most current one is 0.5.0.1.
On Tue, Jun 2, 2009 at 4:46 PM, David Leimbach wrote:
>
>
> On Tue, Jun 2, 2009 at 1:36 PM, John Van Enk wrote:
>>
>> What happens if you use `getRemainingLazyByteString' in your error
Again, I can't reproduce your problem. Are you getting data through
some previous Binary instance before calling the routines you show us
here? The code I tested with is below - I've tried it with both
'getSpecific' paths by commenting out one path at a time. Both
methods work, shown below.
Tho
On Tue, Jun 2, 2009 at 1:36 PM, John Van Enk wrote:
> What happens if you use `getRemainingLazyByteString' in your error
> branch instead of `getLazyByteString'?
>
I actually am using getRemainingLazyByteString right now, and it still
thinks I'm asking for a 20th byte.
if I delete the other gua
On Tue, Jun 2, 2009 at 1:32 PM, John Van Enk wrote:
> Perhaps there's some place in your code that's forcing the lazy read
> to consume more. Perhaps you could replace it with an explict (and
> strict) getBytes[1] in combination with remaining[2]?
Unfortunately, I'm using a Lazy ByteString netw
Hello Gu?nther,
Wednesday, June 3, 2009, 12:11:15 AM, you wrote:
> Hi all,
> is it possible to make ghc embedd a particular manifest in the .exe
> during the compilation process?
add to .rc file:
1 24 "app.manifest"
and put manifect into app.manifest
--
Best regards,
Bulat
Dear Haskellers,
Will you have a few spare hours this summer?
The Darcs team needs your help!
Summary
---
We need two volunteers to help us review the standalone hashed-storage
module, which will be used by Darcs in the future.
Background
--
Darcs supports 'hashed' repositories in wh
What happens if you use `getRemainingLazyByteString' in your error
branch instead of `getLazyByteString'?
On Tue, Jun 2, 2009 at 4:31 PM, David Leimbach wrote:
>
>
> On Tue, Jun 2, 2009 at 1:28 PM, John Van Enk wrote:
>>
>> I think Thomas' point was that some other branch in `getSpecific' is
>>
Perhaps there's some place in your code that's forcing the lazy read
to consume more. Perhaps you could replace it with an explict (and
strict) getBytes[1] in combination with remaining[2]?
Is there a reason you want to use lazy byte strings rather than
forcing full consumption? Do the 9P packets
On Tue, Jun 2, 2009 at 1:28 PM, John Van Enk wrote:
> I think Thomas' point was that some other branch in `getSpecific' is
> running. Is there a chance we can see the rest of `getSpecific'?
Sure: (In the meantime, I'll try the suggested code from before)
get = do s <- getWord32le
On Tue, Jun 2, 2009 at 10:24 AM, Thomas DuBuisson <
thomas.dubuis...@gmail.com> wrote:
> > I think getRemainingLazyByteString expects at least one byte
> No, it works with an empty bytestring. Or, my tests do with binary
> 0.5.0.1.
>
> The specific error means you are requiring more data than pro
I think Thomas' point was that some other branch in `getSpecific' is
running. Is there a chance we can see the rest of `getSpecific'?
On Tue, Jun 2, 2009 at 4:20 PM, David Leimbach wrote:
> The thing is I have 19 bytes in the hex string I provided:
> 13006500040600395032303030
> That'
The thing is I have 19 bytes in the hex string I provided:
13006500040600395032303030
That's 38 characters or 19 bytes.
The last 4 are 9P2000
1300 = 4 bytes for 32bit message payload, This is little endian for 19
bytes total.
65 = 1 byte for message type. 65 is "Rversion" or
Hi all,
is it possible to make ghc embedd a particular manifest in the .exe
during the compilation process?
Günther
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Tue, Jun 2, 2009 at 3:50 AM, Dan wrote:
> You hit the nail on the head. "Why I am doing this" is because of
> boilerplate. Boilerplate gives me rashes and bulbous spots on the nose.
>
> Consider the following Ruby code:
>
> def check(zeClass, zeValue)
> zeValue.is_a? zeCl
Thomas,
You're correct. For some reason, I based my advice on the thought that
19 was the minimum size instead of 13.
On Tue, Jun 2, 2009 at 1:24 PM, Thomas DuBuisson
wrote:
>> I think getRemainingLazyByteString expects at least one byte
> No, it works with an empty bytestring. Or, my tests do
> I think getRemainingLazyByteString expects at least one byte
No, it works with an empty bytestring. Or, my tests do with binary 0.5.0.1.
The specific error means you are requiring more data than providing.
First check the length of the bytestring you pass in to the to level
decode (or 'get') ro
I think getRemainingLazyByteString expects at least one byte (this,
perhaps, is not the appropriate behavior). You'll want to wrap your
call to getRemainingLazyByteString with a call to
Data.Binary.Get.remaining[1] like this:
foo = do
r <- remaining
rbs <- case r of
0
I've got the following "printHex" string as a response from a 9P server
running on the Inferno Operating System. (thanks to a friendly mailing list
contributor who sent a nice example of using Data.Binary)
13006500040600395032303030
This is a little endian encoded ByteString with the
The Dutch government has been trying to get something like this for
years; parliament is asking every new minister why the promised heaven
has not yet arrived, only to hear that more consultants are needed. I
have been to hearings of our parliament and I can tell you such events
are extreme
On Tue, Jun 2, 2009 at 12:12 AM, Antoine Latter wrote:
> A good place to start is http://en.wikipedia.org/wiki/HL7 , which is a
> not-for-profit organization which tries to define interfacing
> standards between medical devices and medical records providers. I
> haven't worked much with their stan
Hello Gu?nther,
Tuesday, June 2, 2009, 4:47:55 PM, you wrote:
> is it possible to make ghc embedd an application icon in the .exe during
> the compilation process?
i've found that answer may be googled as "gcc icon":
1) create icon.rc containing one line:
100 ICON "freearc.ico"
2) compile it u
Sorry for all the repeated messages, my e-mail client exploded.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Hi,
I have developed some simple TH code to automatically derive
XmlPickler instances for my types and if there is interest, I will
clean it up and submit a patch. Its not complete, but is a start.
Any interest?
Max
___
Haskell-Cafe mailing l
Hi all,
is it possible to make ghc embedd an application icon in the .exe during
the compilation process?
Günther
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Janis Voigtlaender wrote:
Hi all,
If you are anyway near Halle/Saale in June, be sure not to miss out on:
I meant "anywhere near", of course :-)
And even if you are not anyway or anywhere near, you might still want to
come just for the occasion :-)
--
Dr. Janis Voigtlaender
http://wwwtcs.inf
Hi all,
If you are anyway near Halle/Saale in June, be sure not to miss out on:
http://iba-cg.de/hal4.html
We have already close to 50 registered participants, so expect a very
lively meeting. See you there? (Late registration still possible.)
Ciao,
Janis.
--
Dr. Janis Voigtlaender
http://w
Hi Richard,
> Yeek. Why do you want to do _that_?
Heh. I've got a parser and I want to check what I've parsed (it's an
exercise in Write Yourself a Scheme in 48 Hours).
> check (Atom _) (Atom _) = True
> check (Bool _) (Bool _) = True
> check __= False
Yes I
Tom Hawkins wrote:
At the core, the fundamental problem is not that complicated. It's
just storing and retrieving a person's various health events:
checkups, prescriptions, procedures, test results, etc. The main
technical challenges are database distribution and patient security.
Both are fun
Vladimir Reshetnikov wrote:
Hi Daniel,
Could you please explain what does mean 'monomorphic' in this context?
I thought that all type variables in Haskell are implicitly
universally quantified, so (a -> a) is the same type as (forall a. a
-> a)
At the top level (i.e. definition level), yes. Ho
On Mon, Jun 01, 2009 at 08:27:05PM +0200, S. Doaitse Swierstra wrote:
> And rename "empty" to "fail"? You managed to confuse me since I always
> use pSucceed to recognise the empty string.
That would clash with the existing and widely used "fail". One could
view "empty" as the parser for the em
53 matches
Mail list logo