Re: [Haskell-cafe] type checking that I can't figure out ....

2009-06-02 Thread Daniel Fischer
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 believe until 
6.8 
inclusive. 
I don't think it's going to change again soon.

> I added the simple liftMaybe function to convert the
> Maybe result into something that will work with your state monad.
>
> Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Anglohaskell 2009

2009-06-02 Thread Magnus Therning

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: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type checking that I can't figure out ....

2009-06-02 Thread ajb

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.
That's really the only problem here AFAICT.

Wow, this brings back memories.  I wrote this module about ten years ago,
and I'm shocked that it's still getting use.  I'd appreciate a copy when
you're done updating it for the modern era.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type checking that I can't figure out ....

2009-06-02 Thread Vasili I. Galchin
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 { Just reinfo = M.lookup fwd re }--
> PROBLEM
> >reinfo <- liftMaybe $ M.lookup re fwd  --
> PROBLEM
> >return reinfo
> >
> > liftMaybe :: Monad m => Maybe a -> m a
> > liftMaybe Nothing = fail "Nothing"
> > liftMaybe (Just x) = return x
>
> 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). I added the simple liftMaybe function to convert the
> Maybe result into something that will work with your state monad.
>
> Michael
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type checking that I can't figure out ....

2009-06-02 Thread Michael Snoyman
> 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
>
> liftMaybe :: Monad m => Maybe a -> m a
> liftMaybe Nothing = fail "Nothing"
> liftMaybe (Just x) = return x

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). I added the simple liftMaybe function to convert the
Maybe result into something that will work with your state monad.

Michael
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] type checking that I can't figure out ....

2009-06-02 Thread Vasili I. Galchin
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
> import Data.Array

import IOExts


The type of a regular expression.

> data Re t
>   = ReOr [Re t]
>   | ReCat [Re t]
>   | ReStar (Re t)
>   | RePlus (Re t)
>   | ReOpt (Re t)
>   | ReTerm [t]
>   deriving (Show)


The internal type of a regular expression.

> type SimplRe t = Int
> data SimplRe' t
>   = SReOr (SimplRe t) (SimplRe t)
>   | SReCat (SimplRe t) (SimplRe t)
>   | SReStar (SimplRe t)
>   | SReLambda
>   | SReNullSet
>   | SReTerm t
>   deriving (Eq, Ord, Show)


The regular expression builder monad.

> data (Ord t) => ReRead t
>  = ReRead {
>   rerNullSet  :: SimplRe t,
>   rerLambda   :: SimplRe t
>  }

> data (Ord t) => ReState t
>   = ReState {
>   resFwdMap   :: M.Map (SimplRe t) (ReInfo t),
>   resBwdMap   :: M.Map (SimplRe' t) (SimplRe t),
>   resNext :: Int,
>   resQueue:: ([SimplRe t], [SimplRe t]),
>   resStatesDone   :: [SimplRe t]
> }

> type ReM m t a = StateT (ReState t) (ReaderT (ReRead t) m) a

TEMP  WNH
Dfa construction

> data ReDfaState t
>   = ReDfaState {
> dfaFinal :: Bool,
>   dfaTrans :: [(t, SimplRe t)]
>   }
>   deriving (Show)

TEMP WNH
The ReInfo type

> data ReInfo t
>   = ReInfo {
>   reiSRE  :: SimplRe' t,
>   reiNullable :: Bool,
>   reiDfa  :: Maybe (ReDfaState t)
> }
>   deriving (Show)

TEMP WNH


> class (Monad m, Ord t) => ReVars m t where { }
> instance (Monad m, Ord t) => ReVars m t where { }

TEMP WNH

> 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 <- M.lookup fwd re -- PROBLEM
>return reinfo


When I "compile" with ghci I get:


Dfa_exp.lhs:91:32:
Couldn't match expected type `M.Map
(M.Map (SimplRe t) (ReInfo t)) t1'
   against inferred type `SimplRe t2'
In the second argument of `M.lookup', namely `re'
In a 'do' expression: reinfo <- M.lookup fwd re
In the expression:
do fwd <- gets resFwdMap
   reinfo <- M.lookup fwd re
   return reinfo

I trimmed the original code down a lot! But still can't why I am getting
type check errors!!! Help!

Kind regards,

Vasili
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] beginners question about fromMaybe

2009-06-02 Thread Ryan Ingram
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 PatternGuards #-}

> probePhase is sc xs m = concatMap prefix xs where
> prefix x
> | Just val <- Map.lookup (getPartialTuple is x) m = joinTuples sc x 
> val
> | otherwise = []

Alternatively, I might write it like this:

> import Control.Monad

> maybeM :: MonadPlus m => Maybe a -> m a
> maybeM = maybe mzero return

> probePhase is sc xs m = do
> x <- xs
> val <- maybeM $ Map.lookup (getPartialTuple is x) m
> joinTuples sc x val

This now works for any xs that is an instance of MonadPlus (assuming
joinTuples is also polymorphic).

Both of these examples are more wordy than Luke's quick two-liner,
but, to me, it's worth it for the additional "maintainability" of that
code.  I am perhaps in the minority on this issue, though :)

  -- ryan

On Tue, Jun 2, 2009 at 4:20 PM, Luke Palmer  wrote:
>
>
> 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  = probePhase is sc xs m
>>    | otherwise       = jr ++ probePhase is sc xs m
>>        where
>>            jr  = joinTuples sc x (fromMaybe [] val)
>>            key = getPartialTuple is x
>>            val = Map.lookup key m
>
> Here's my take.   This ought to be equivalent, but I haven't tested.
> probePhase is sc m = concatMap prefix
>     where
>     prefix x = let key = getPartialTuple is x in
>                maybe [] (joinTuples sc x) $ Map.lookup key m
>>
>>
>>
>> the line "jr  = joinTuples sc x (fromMaybe [] val)" is kind of ugly
>> because i know that it is not Nothing.
>> is there a better way to solve this?
>> regards
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Checking a value against a passed-in constructor?

2009-06-02 Thread wren ng thornton

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 -> a) -> (String -> a) -> a
myval (Bool b) bool atom = bool b
myval (Atom s) bool atom = atom s

f x = myval bool atom where
   bool b = ...
   atom s = ...


In terms of boilerplate, this is often far and away the cleanest 
solution. I highly recommend if for Write Yourself A Scheme.



The one place where it falls down is when, for whatever reason, you end 
up having collections of MyVals which can't sensibly use some set of 
constructors. One common example is for type-checking compilers where 
you guarantee that ill-typed MyVals cannot be constructed (rather than 
doing a verification pass after construction to ensure they're well-typed).


If your type has this problem, using the fold approach often means 
writing dummy functions to throw errors on invalid inputs, which in turn 
means sacrificing much of the type safety you'd like (even if you use 
something like the Maybe or Error monads instead of _|_). A canonical 
Haskell trick here is to use GADTs to maintain your type invariants, 
rather than using plain ADTs. This technique isn't really suitable for a 
first pass at learning Haskell though.




[1] "fold" here is the general term for this type of function.  Examples are
foldr: 
http://haskell.org/ghc/docs/latest/html/libraries/base/src/GHC-Base.html#foldr
maybe: 
http://haskell.org/ghc/docs/latest/html/libraries/base/src/Data-Maybe.html#maybe
either: 
http://haskell.org/ghc/docs/latest/html/libraries/base/src/Data-Either.html#either


Two more good resources for folds are:


* http://knol.google.com/k/edward-kmett/catamorphisms/

This has an implementation in Control.Morphism.Cata from 
category-extras[1], though the documentation is scarce. If you're 
interested in the theory of why folds look and work the way they do, 
then this knol is the best starting point. If you're familiar with OOP, 
a catamorphism is extremely similar to the recursive Visitor pattern.


The big difference you'll see between this generic solution and 
specialized catamorphisms (foldr, maybe, either,...) is that the 
specialized versions unpack the Algebra into separate arguments. Also, 
this generic solution defines MyVal types with open-recursive functors 
and explicit fixed-point operators, whereas the specialized versions 
just use Haskell's regular ability to define recursive types (since the 
result of |fmap (cata f)| is consumed immediately). Don't let these 
trees obscure the forest.



* http://www.cs.nott.ac.uk/~wss/Publications/DataTypesALaCarte.pdf

This paper presents an innovative solution to the "expression problem" 
of defining an open set of constructors for a type. It uses the same 
open-recursive functor trick as above and may provide some illustration 
of why we may want to bother with it. If you're hungry for more details, 
there's an interesting discussion of the paper at [2].



[1] http://hackage.haskell.org/packages/archive/category-extras/
[2] http://wadler.blogspot.com/2008/02/data-types-la-carte.html

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cabal/primes

2009-06-02 Thread Bertram Felgenhauer
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 package is probably the one you want.

Bertram
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] beginners question about fromMaybe

2009-06-02 Thread Toby Hutton
>  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
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Cabal/primes

2009-06-02 Thread michael rice
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
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
Prelude> import Data.Numbers.Primes
Prelude Data.Numbers.Primes> take 10 primes
Loading package syb ... linking ... done.
Loading package base-3.0.3.0 ... linking ... done.
Loading package primes-0.1.1 ... linking ... done.
[2,3,5,7,11,13,17,19,23,29]
Prelude Data.Numbers.Primes> isPrime 7

:1:0: Not in scope: `isPrime'
Prelude Data.Numbers.Primes> 




  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] beginners question about fromMaybe

2009-06-02 Thread Toby Hutton
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  = probePhase is sc xs m
>    | otherwise       = jr ++ probePhase is sc xs m
>        where
>            jr  = joinTuples sc x (fromMaybe [] val)
>            key = getPartialTuple is x
>            val = Map.lookup key m
>
>
> the line "jr  = joinTuples sc x (fromMaybe [] val)" is kind of ugly
> because i know that it is not Nothing.

Although pattern matching is probably nicer, there's also fromJust
which will throw an exception if you pass it Nothing.

I prefer:
case Map.lookup key m of
 Nothing -> next
 Just val -> (joinTuples sc x val) ++ next
  where next = probePhase ...
key = ...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] beginners question about fromMaybe

2009-06-02 Thread Raynor Vliegendhart
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:
>
>
>   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 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
> >where
> >jr  = joinTuples sc x (fromMaybe [] val)
> >key = getPartialTuple is x
> >val = Map.lookup key m
> >
> >
> > the line "jr  = joinTuples sc x (fromMaybe [] val)" is kind of ugly
> > because i know that it is not Nothing.
> > is there a better way to solve this?
> > regards
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] beginners question about fromMaybe

2009-06-02 Thread Luke Palmer
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  = probePhase is sc xs m
>| otherwise   = jr ++ probePhase is sc xs m
>where
>jr  = joinTuples sc x (fromMaybe [] val)
>key = getPartialTuple is x
>val = Map.lookup key m


Here's my take.   This ought to be equivalent, but I haven't tested.

probePhase is sc m = concatMap prefix
where
prefix x = let key = getPartialTuple is x in
   maybe [] (joinTuples sc x) $ Map.lookup key m


>
>
> the line "jr  = joinTuples sc x (fromMaybe [] val)" is kind of ugly
> because i know that it is not Nothing.
> is there a better way to solve this?
> regards
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] beginners question about fromMaybe

2009-06-02 Thread Raynor Vliegendhart
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 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
>where
>jr  = joinTuples sc x (fromMaybe [] val)
>key = getPartialTuple is x
>val = Map.lookup key m
>
>
> the line "jr  = joinTuples sc x (fromMaybe [] val)" is kind of ugly
> because i know that it is not Nothing.
> is there a better way to solve this?
> regards
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] beginners question about fromMaybe

2009-06-02 Thread Nico Rolle
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
where
jr  = joinTuples sc x (fromMaybe [] val)
key = getPartialTuple is x
val = Map.lookup key m


the line "jr  = joinTuples sc x (fromMaybe [] val)" is kind of ugly
because i know that it is not Nothing.
is there a better way to solve this?
regards
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Anglohaskell 2009

2009-06-02 Thread Henk-Jan van Tuyl
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
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: The Haskell Platform 2009.2.0.1

2009-06-02 Thread Don Stewart

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:

http://hackage.haskell.org/platform/

The Haskell Platform is a blessed library and tool suite for Haskell
distilled from Hackage, along with installers for a wide variety of
systems. It saves developers work picking and choosing the best Haskell
libraries and tools to use for a task. Distro maintainers that support
the Haskell Platform can be confident they're fully supporting Haskell
as the developers intend it. Developers targetting the platform can be
confident they have a trusted base of code to work with.

What you get:

http://hackage.haskell.org/platform/contents.html

With regular time-based releases, we expect the platform will grow into
a rich, indispensable development environment for all Haskell projects.

Please note that this is a beta release. We do not expect all the
installers to work perfectly, nor every developer need met, and we would
appreciate feedback.  You can help out by packaging the platform for
your distro, or reporting bugs and feature requests, or installing
Haskell onto your friends' machines.  The process for adding new tools
and libraries will be outlined in coming weeks.

The Haskell Platform would not have been possible without the hard work
of the Cabal development team, the Hackage developers and maintainers,
the individual compiler, tool and library authors who contributed to the
suite, and the distro maintainers who build and distribute the Haskell
Platform.

Thanks!

-- The Platform Infrastructure Team
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: Anglohaskell 2009

2009-06-02 Thread Philippa Cowderoy
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 #anglohaskell on freenode.

For those not familiar with Anglohaskell, it's a somewhat-informal
get-together featuring a mixture of talks, discussion and socialising
with topics from the hobbyist to the pragmatic to the theoretical. All
are welcome, regardless of experience, and best of all - it's free!

If anyone wants to offer a talk, help with running the event,
accomodation for haskellers from out of town or some ideas, please feel
free to edit the wiki page appropriately and/or give us a yell in
#anglohaskell.

-- 
Philippa Cowderoy 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread David Leimbach
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
>> here?
>
>
> Ah good question... I'm calling "decode", but it's not clear that it's even
> running my instance of Get
>
> If I have a lazy bytestring, and call "decode", which instance of "Get"
> runs?  Probably not my 9P message version I'll bet...
>
> geeze...  :-(
>

ANd... that was it.  I totally didn't decode with the right decoder.  By
the expression I had, it appears it was trying to decode a ByteString as a
String, and that was causing a big darned mess.

Thanks for all the help guys.  I'm glad it's not a bug in the library, just
my dumb code

Dave


>
>
>
>> 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.
>>
>> Thomas
>>
>> *Main> decode test :: RV
>> Rversion {size = 19, mtype = 101, tag = 65535, msize = 1024, ssize =
>> 6, version = Chunk "9P2000" Empty}
>> *Main> :q
>> Leaving GHCi.
>> [... edit ...]
>> [1 of 1] Compiling Main ( p.hs, interpreted )
>> Ok, modules loaded: Main.
>> *Main> decode test :: RV
>> Rerror {size = 19, mtype = 101, tag = 65535, ssize = 1024, ename =
>> Chunk "\NUL\NUL\ACK\NUL9P2000" Empty}
>> *Main>
>>
>>
>>
>> import Data.ByteString.Lazy
>> import Data.Binary
>> import Data.Binary.Get
>>
>> data RV =
>>  Rversion { size:: Word32,
>>mtype   :: Word8,
>>tag :: Word16,
>>msize   :: Word32,
>>ssize   :: Word16,
>>version :: ByteString}
>>  | Rerror { size:: Word32,
>>mtype   :: Word8,
>>tag :: Word16,
>>ssize   :: Word16,
>>ename :: ByteString}
>> deriving (Eq, Ord, Show)
>>
>> instance Binary RV where
>>  put = undefined
>>  get = do s <- getWord32le
>>  mtype <- getWord8
>>  getSpecific s mtype
>>where
>>  getSpecific s mt
>> {-  = do t <- getWord16le
>>   ms <- getWord32le
>>   ss <- getWord16le
>>   v <- getRemainingLazyByteString
>>   return $ Rversion {size=s,
>>  mtype=mt,
>>  tag=t,
>>  msize=ms,
>>  ssize=ss,
>>  version=v}
>> -}
>>   = do t <- getWord16le
>>   ss <- getWord16le
>>   e <- getLazyByteString $ fromIntegral ss
>>return $ Rerror {size=s,
>> mtype=mt,
>>tag=t,
>>ssize=ss,
>>   ename=e}
>>
>> test = pack
>>[ 0x13
>>, 0x00
>>, 0x00
>>, 0x00
>>, 0x65
>>, 0xff
>>, 0xff
>>, 0x00
>>, 0x04
>>, 0x00
>>, 0x00
>>, 0x06
>>, 0x00
>>, 0x39
>>, 0x50
>>, 0x32
>>, 0x30
>>, 0x30
>>, 0x30 ]
>>
>> On Tue, Jun 2, 2009 at 1: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
>> >> 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
>> >  mtype <- getWord8
>> >  getSpecific s mtype
>> > where
>> >   getSpecific s mt
>> >   | mt == mtRversion = do t <- getWord16le
>> >   ms <- getWord32le
>> >   ss <- getWord16le
>> >   v <-
>> > getRemainingLazyByteString
>> >   return $ MessageClient $
>> > Rversion {size=s,
>> >
>> > mtype=mt,
>> >
>> > tag=t,
>> >
>> > msize=ms,
>> >
>> > ssize=ss,
>> >
>> > version=v}
>> >   | mt == mtRerror = do t <- getWord16le
>> > ss <- getWord16le
>> > e <- getLazyByteString $
>> > fromIntegral ss
>> > return $ MessageClient $
>> Rerror
>> > {size=s,
>> >
>> > mtype=mt,
>> >
>> > 

Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread Thomas DuBuisson
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 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 instance of Get
> If I have a lazy bytestring, and call "decode", which instance of "Get"
> runs?  Probably not my 9P message version I'll bet...
> geeze...  :-(
>
>>
>> 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.
>>
>> Thomas
>>
>> *Main> decode test :: RV
>> Rversion {size = 19, mtype = 101, tag = 65535, msize = 1024, ssize =
>> 6, version = Chunk "9P2000" Empty}
>> *Main> :q
>> Leaving GHCi.
>> [... edit ...]
>> [1 of 1] Compiling Main             ( p.hs, interpreted )
>> Ok, modules loaded: Main.
>> *Main> decode test :: RV
>> Rerror {size = 19, mtype = 101, tag = 65535, ssize = 1024, ename =
>> Chunk "\NUL\NUL\ACK\NUL9P2000" Empty}
>> *Main>
>>
>>
>>
>> import Data.ByteString.Lazy
>> import Data.Binary
>> import Data.Binary.Get
>>
>> data RV =
>>  Rversion {     size    :: Word32,
>>                mtype   :: Word8,
>>                tag     :: Word16,
>>                msize   :: Word32,
>>                ssize   :: Word16,
>>                version :: ByteString}
>>  | Rerror {     size    :: Word32,
>>                mtype   :: Word8,
>>                tag     :: Word16,
>>                ssize   :: Word16,
>>                ename :: ByteString}
>>        deriving (Eq, Ord, Show)
>>
>> instance Binary RV where
>>  put = undefined
>>  get = do s <- getWord32le
>>          mtype <- getWord8
>>          getSpecific s mtype
>>        where
>>          getSpecific s mt
>> {-                      = do t <- getWord16le
>>                           ms <- getWord32le
>>                           ss <- getWord16le
>>                           v <- getRemainingLazyByteString
>>                           return $ Rversion {size=s,
>>                                              mtype=mt,
>>                                              tag=t,
>>                                              msize=ms,
>>                                              ssize=ss,
>>                                              version=v}
>> -}
>>                      = do t <- getWord16le
>>                           ss <- getWord16le
>>                           e <- getLazyByteString $ fromIntegral ss
>>                           return $ Rerror {size=s,
>>                                                            mtype=mt,
>>                                                            tag=t,
>>                                                            ssize=ss,
>>                                                           ename=e}
>>
>> test = pack
>>        [ 0x13
>>        , 0x00
>>        , 0x00
>>        , 0x00
>>        , 0x65
>>        , 0xff
>>        , 0xff
>>        , 0x00
>>        , 0x04
>>        , 0x00
>>        , 0x00
>>        , 0x06
>>        , 0x00
>>        , 0x39
>>        , 0x50
>>        , 0x32
>>        , 0x30
>>        , 0x30
>>        , 0x30 ]
>>
>> On Tue, Jun 2, 2009 at 1: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
>> >> 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
>> >              mtype <- getWord8
>> >              getSpecific s mtype
>> >         where
>> >           getSpecific s mt
>> >                       | mt == mtRversion = do t <- getWord16le
>> >                                               ms <- getWord32le
>> >                                               ss <- getWord16le
>> >                                               v <-
>> > getRemainingLazyByteString
>> >                                               return $ MessageClient $
>> > Rversion {size=s,
>> >
>> >     mtype=mt,
>> >
>> >     tag=t,
>> >
>> >     msize=ms,
>> >
>> >     ssize=ss,
>> >
>> >     version=v}
>> >                       | mt == mtRerror = do t <- getWord16le
>> >                                             ss <- getWord16le
>> >                                             e <- getLazyByteString $
>> > fromIntegral ss
>> >                                             return $ MessageClient $
>> > Rerror
>> > {size=s,
>> >
>> > mtype=mt,
>> >
>> > tag=t,
>> >
>> > ssize=ss,
>> >
>> > ename=e}
>> >
>> >>
>> >> On Tue, Jun 2, 2009 at 4:20 PM, David Lei

Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread David Leimbach
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 instance of Get

If I have a lazy bytestring, and call "decode", which instance of "Get"
runs?  Probably not my 9P message version I'll bet...

geeze...  :-(



> 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.
>
> Thomas
>
> *Main> decode test :: RV
> Rversion {size = 19, mtype = 101, tag = 65535, msize = 1024, ssize =
> 6, version = Chunk "9P2000" Empty}
> *Main> :q
> Leaving GHCi.
> [... edit ...]
> [1 of 1] Compiling Main ( p.hs, interpreted )
> Ok, modules loaded: Main.
> *Main> decode test :: RV
> Rerror {size = 19, mtype = 101, tag = 65535, ssize = 1024, ename =
> Chunk "\NUL\NUL\ACK\NUL9P2000" Empty}
> *Main>
>
>
>
> import Data.ByteString.Lazy
> import Data.Binary
> import Data.Binary.Get
>
> data RV =
>  Rversion { size:: Word32,
>mtype   :: Word8,
>tag :: Word16,
>msize   :: Word32,
>ssize   :: Word16,
>version :: ByteString}
>  | Rerror { size:: Word32,
>mtype   :: Word8,
>tag :: Word16,
>ssize   :: Word16,
>ename :: ByteString}
> deriving (Eq, Ord, Show)
>
> instance Binary RV where
>  put = undefined
>  get = do s <- getWord32le
>  mtype <- getWord8
>  getSpecific s mtype
>where
>  getSpecific s mt
> {-  = do t <- getWord16le
>   ms <- getWord32le
>   ss <- getWord16le
>   v <- getRemainingLazyByteString
>   return $ Rversion {size=s,
>  mtype=mt,
>  tag=t,
>  msize=ms,
>  ssize=ss,
>  version=v}
> -}
>   = do t <- getWord16le
>   ss <- getWord16le
>   e <- getLazyByteString $ fromIntegral ss
>return $ Rerror {size=s,
> mtype=mt,
>tag=t,
>ssize=ss,
>   ename=e}
>
> test = pack
>[ 0x13
>, 0x00
>, 0x00
>, 0x00
>, 0x65
>, 0xff
>, 0xff
>, 0x00
>, 0x04
>, 0x00
>, 0x00
>, 0x06
>, 0x00
>, 0x39
>, 0x50
>, 0x32
>, 0x30
>, 0x30
>, 0x30 ]
>
> On Tue, Jun 2, 2009 at 1: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
> >> 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
> >  mtype <- getWord8
> >  getSpecific s mtype
> > where
> >   getSpecific s mt
> >   | mt == mtRversion = do t <- getWord16le
> >   ms <- getWord32le
> >   ss <- getWord16le
> >   v <-
> > getRemainingLazyByteString
> >   return $ MessageClient $
> > Rversion {size=s,
> >
> > mtype=mt,
> >
> > tag=t,
> >
> > msize=ms,
> >
> > ssize=ss,
> >
> > version=v}
> >   | mt == mtRerror = do t <- getWord16le
> > ss <- getWord16le
> > e <- getLazyByteString $
> > fromIntegral ss
> > return $ MessageClient $
> Rerror
> > {size=s,
> >
> > mtype=mt,
> >
> > tag=t,
> >
> > ssize=ss,
> >
> > ename=e}
> >
> >>
> >> 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'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 the response type
> for
> >> > a
> >> > Tversion request
> >> >  = 2 bytes f

Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread David Leimbach
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  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 guarded branch of that function, it still fails
> saying
> > I'm asking for the 20th byte.
> > Dave
> >
> >>
> >> 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
> >> >> 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
> >> >  mtype <- getWord8
> >> >  getSpecific s mtype
> >> > where
> >> >   getSpecific s mt
> >> >   | mt == mtRversion = do t <- getWord16le
> >> >   ms <- getWord32le
> >> >   ss <- getWord16le
> >> >   v <-
> >> > getRemainingLazyByteString
> >> >   return $ MessageClient $
> >> > Rversion {size=s,
> >> >
> >> > mtype=mt,
> >> >
> >> > tag=t,
> >> >
> >> > msize=ms,
> >> >
> >> > ssize=ss,
> >> >
> >> > version=v}
> >> >   | mt == mtRerror = do t <- getWord16le
> >> > ss <- getWord16le
> >> > e <- getLazyByteString $
> >> > fromIntegral ss
> >> > return $ MessageClient $
> >> > Rerror
> >> > {size=s,
> >> >
> >> > mtype=mt,
> >> >
> >> > tag=t,
> >> >
> >> > ssize=ss,
> >> >
> >> > ename=e}
> >> >
> >> >>
> >> >> 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'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 the response
> type
> >> >> > for
> >> >> > a
> >> >> > Tversion request
> >> >> >  = 2 bytes for 16bit message "tag".
> >> >> >
> >> >> > 0004 = 4 bytes for the 32 bit maximum message payload size I'm
> >> >> > negotiating with the 9P server.  This is little endian for 1024
> >> >> > 0600 =  2 bytes for 16 bit value for the length of the "string" I'm
> >> >> > sending.
> >> >> >  The strings are *NOT* null terminated in 9p, and this is little
> >> >> > endian
> >> >> > for
> >> >> > 6 bytes remaining.
> >> >> > 5032303030 = 6 bytes the ASCII or UTF-8 string "9P2000" which is 6
> >> >> > bytes
> >> >> > 4 + 1 + 2 + 4 + 2 + 6 = 19 bytes.
> >> >> > As far as I can see, my "get" code does NOT ask for a 20th byte, so
> >> >> > why
> >> >> > am I
> >> >> > getting that error?
> >> >> > get = do s <- getWord32le  -- 4
> >> >> >  mtype <- getWord8  -- 1
> >> >> >  getSpecific s mtype
> >> >> > where
> >> >> >   getSpecific s mt
> >> >> >   | mt == mtRversion = do t <- getWord16le -- 2
> >> >> >   ms <- getWord32le  --
> 4
> >> >> >   ss <- getWord16le --
> 2
> >> >> >   v <-
> >> >> > getRemainingLazyByteString  -- remaining should be 6 bytes.
> >> >> >   return $
> MessageClient
> >> >> > $
> >> >> > Rversion {size=s,
> >> >> >
> >> >> > mtype=mt,
> >> >> >
> >> >> > tag=t,
> >> >> >
> >> >> > msize=ms,
> >> >> >
> >> >> > ssize=ss,
> >> >> >
> >> >> > version=v}
> >> >> > Should I file a bug?  I don't believe I should be seeing an error
> >> >> > message
> >> >> > claiming a failure at the 20th byte when I've never asked for one.
> >> >> > Dave
> >> >> >
> >> >> > On Tue, Jun 2, 2009 at 10:51 AM, John Van Enk 
> >> >> > wrote:
> >> >> >>
> >> >> >> 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 e

Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread John Van Enk
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
>> 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 guarded branch of that function, it still fails saying
> I'm asking for the 20th byte.
> Dave
>
>>
>> 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
>> >> 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
>> >              mtype <- getWord8
>> >              getSpecific s mtype
>> >         where
>> >           getSpecific s mt
>> >                       | mt == mtRversion = do t <- getWord16le
>> >                                               ms <- getWord32le
>> >                                               ss <- getWord16le
>> >                                               v <-
>> > getRemainingLazyByteString
>> >                                               return $ MessageClient $
>> > Rversion {size=s,
>> >
>> >     mtype=mt,
>> >
>> >     tag=t,
>> >
>> >     msize=ms,
>> >
>> >     ssize=ss,
>> >
>> >     version=v}
>> >                       | mt == mtRerror = do t <- getWord16le
>> >                                             ss <- getWord16le
>> >                                             e <- getLazyByteString $
>> > fromIntegral ss
>> >                                             return $ MessageClient $
>> > Rerror
>> > {size=s,
>> >
>> > mtype=mt,
>> >
>> > tag=t,
>> >
>> > ssize=ss,
>> >
>> > ename=e}
>> >
>> >>
>> >> 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'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 the response type
>> >> > for
>> >> > a
>> >> > Tversion request
>> >> >  = 2 bytes for 16bit message "tag".
>> >> >
>> >> > 0004 = 4 bytes for the 32 bit maximum message payload size I'm
>> >> > negotiating with the 9P server.  This is little endian for 1024
>> >> > 0600 =  2 bytes for 16 bit value for the length of the "string" I'm
>> >> > sending.
>> >> >  The strings are *NOT* null terminated in 9p, and this is little
>> >> > endian
>> >> > for
>> >> > 6 bytes remaining.
>> >> > 5032303030 = 6 bytes the ASCII or UTF-8 string "9P2000" which is 6
>> >> > bytes
>> >> > 4 + 1 + 2 + 4 + 2 + 6 = 19 bytes.
>> >> > As far as I can see, my "get" code does NOT ask for a 20th byte, so
>> >> > why
>> >> > am I
>> >> > getting that error?
>> >> > get = do s <- getWord32le  -- 4
>> >> >              mtype <- getWord8  -- 1
>> >> >              getSpecific s mtype
>> >> >         where
>> >> >           getSpecific s mt
>> >> >                       | mt == mtRversion = do t <- getWord16le -- 2
>> >> >                                               ms <- getWord32le  -- 4
>> >> >                                               ss <- getWord16le -- 2
>> >> >                                               v <-
>> >> > getRemainingLazyByteString  -- remaining should be 6 bytes.
>> >> >                                               return $ MessageClient
>> >> > $
>> >> > Rversion {size=s,
>> >> >
>> >> >                         mtype=mt,
>> >> >
>> >> >                         tag=t,
>> >> >
>> >> >                         msize=ms,
>> >> >
>> >> >                         ssize=ss,
>> >> >
>> >> >                         version=v}
>> >> > Should I file a bug?  I don't believe I should be seeing an error
>> >> > message
>> >> > claiming a failure at the 20th byte when I've never asked for one.
>> >> > Dave
>> >> >
>> >> > On Tue, Jun 2, 2009 at 10:51 AM, John Van Enk 
>> >> > wrote:
>> >> >>
>> >> >> 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 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

Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread Thomas DuBuisson
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.

Thomas

*Main> decode test :: RV
Rversion {size = 19, mtype = 101, tag = 65535, msize = 1024, ssize =
6, version = Chunk "9P2000" Empty}
*Main> :q
Leaving GHCi.
[... edit ...]
[1 of 1] Compiling Main ( p.hs, interpreted )
Ok, modules loaded: Main.
*Main> decode test :: RV
Rerror {size = 19, mtype = 101, tag = 65535, ssize = 1024, ename =
Chunk "\NUL\NUL\ACK\NUL9P2000" Empty}
*Main>



import Data.ByteString.Lazy
import Data.Binary
import Data.Binary.Get

data RV =
 Rversion { size:: Word32,
mtype   :: Word8,
tag :: Word16,
msize   :: Word32,
ssize   :: Word16,
version :: ByteString}
 | Rerror { size:: Word32,
mtype   :: Word8,
tag :: Word16,
ssize   :: Word16,
ename :: ByteString}
deriving (Eq, Ord, Show)

instance Binary RV where
 put = undefined
 get = do s <- getWord32le
  mtype <- getWord8
  getSpecific s mtype
where
  getSpecific s mt
{-  = do t <- getWord16le
   ms <- getWord32le
   ss <- getWord16le
   v <- getRemainingLazyByteString
   return $ Rversion {size=s,
  mtype=mt,
  tag=t,
  msize=ms,
  ssize=ss,
  version=v}
-}
  = do t <- getWord16le
   ss <- getWord16le
   e <- getLazyByteString $ fromIntegral ss
   return $ Rerror {size=s,
mtype=mt,
tag=t,
ssize=ss,
   ename=e}

test = pack
[ 0x13
, 0x00
, 0x00
, 0x00
, 0x65
, 0xff
, 0xff
, 0x00
, 0x04
, 0x00
, 0x00
, 0x06
, 0x00
, 0x39
, 0x50
, 0x32
, 0x30
, 0x30
, 0x30 ]

On Tue, Jun 2, 2009 at 1: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
>> 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
>              mtype <- getWord8
>              getSpecific s mtype
>         where
>           getSpecific s mt
>                       | mt == mtRversion = do t <- getWord16le
>                                               ms <- getWord32le
>                                               ss <- getWord16le
>                                               v <-
> getRemainingLazyByteString
>                                               return $ MessageClient $
> Rversion {size=s,
>
>     mtype=mt,
>
>     tag=t,
>
>     msize=ms,
>
>     ssize=ss,
>
>     version=v}
>                       | mt == mtRerror = do t <- getWord16le
>                                             ss <- getWord16le
>                                             e <- getLazyByteString $
> fromIntegral ss
>                                             return $ MessageClient $ Rerror
> {size=s,
>
> mtype=mt,
>
> tag=t,
>
> ssize=ss,
>
> ename=e}
>
>>
>> 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'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 the response type for
>> > a
>> > Tversion request
>> >  = 2 bytes for 16bit message "tag".
>> >
>> > 0004 = 4 bytes for the 32 bit maximum message payload size I'm
>> > negotiating with the 9P server.  This is little endian for 1024
>> > 0600 =  2 bytes for 16 bit value for the length of the "string" I'm
>> > sending.
>> >  The strings are *NOT* null terminated in 9p, and this is little endian
>> > for
>> > 6 bytes remaining.
>> > 5032303030 = 6 bytes the ASCII or UTF-8 string "9P2000" which is 6 bytes
>> > 4 + 1 + 2 + 4 + 2 + 6 = 19 bytes.
>> > As far as I can see, my "get" code does NOT ask for a 20th byte, so why

Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread David Leimbach
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 guarded branch of that function, it still fails saying
I'm asking for the 20th byte.

Dave


>
> 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
> >> 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
> >  mtype <- getWord8
> >  getSpecific s mtype
> > where
> >   getSpecific s mt
> >   | mt == mtRversion = do t <- getWord16le
> >   ms <- getWord32le
> >   ss <- getWord16le
> >   v <-
> > getRemainingLazyByteString
> >   return $ MessageClient $
> > Rversion {size=s,
> >
> > mtype=mt,
> >
> > tag=t,
> >
> > msize=ms,
> >
> > ssize=ss,
> >
> > version=v}
> >   | mt == mtRerror = do t <- getWord16le
> > ss <- getWord16le
> > e <- getLazyByteString $
> > fromIntegral ss
> > return $ MessageClient $
> Rerror
> > {size=s,
> >
> > mtype=mt,
> >
> > tag=t,
> >
> > ssize=ss,
> >
> > ename=e}
> >
> >>
> >> 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'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 the response type
> for
> >> > a
> >> > Tversion request
> >> >  = 2 bytes for 16bit message "tag".
> >> >
> >> > 0004 = 4 bytes for the 32 bit maximum message payload size I'm
> >> > negotiating with the 9P server.  This is little endian for 1024
> >> > 0600 =  2 bytes for 16 bit value for the length of the "string" I'm
> >> > sending.
> >> >  The strings are *NOT* null terminated in 9p, and this is little
> endian
> >> > for
> >> > 6 bytes remaining.
> >> > 5032303030 = 6 bytes the ASCII or UTF-8 string "9P2000" which is 6
> bytes
> >> > 4 + 1 + 2 + 4 + 2 + 6 = 19 bytes.
> >> > As far as I can see, my "get" code does NOT ask for a 20th byte, so
> why
> >> > am I
> >> > getting that error?
> >> > get = do s <- getWord32le  -- 4
> >> >  mtype <- getWord8  -- 1
> >> >  getSpecific s mtype
> >> > where
> >> >   getSpecific s mt
> >> >   | mt == mtRversion = do t <- getWord16le -- 2
> >> >   ms <- getWord32le  -- 4
> >> >   ss <- getWord16le -- 2
> >> >   v <-
> >> > getRemainingLazyByteString  -- remaining should be 6 bytes.
> >> >   return $ MessageClient $
> >> > Rversion {size=s,
> >> >
> >> > mtype=mt,
> >> >
> >> > tag=t,
> >> >
> >> > msize=ms,
> >> >
> >> > ssize=ss,
> >> >
> >> > version=v}
> >> > Should I file a bug?  I don't believe I should be seeing an error
> >> > message
> >> > claiming a failure at the 20th byte when I've never asked for one.
> >> > Dave
> >> >
> >> > On Tue, Jun 2, 2009 at 10:51 AM, John Van Enk 
> wrote:
> >> >>
> >> >> 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 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') routine and walk though that to figure out how
> much
> >> >> > it should be consuming.  I notice you have a guard on the
> >> >> > 'getSpecific' function, hopefully you're sure the case you gave us
> is
> >> >> > the branch being taken.
> >> >> >
> >> >> > I think the issue isn't with the code provided.  I cleaned up the
> >> >> > code
> >> >> > (which did change behavio

Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread David Leimbach
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 network IO lib.  So I don't think
going to a strict ByteString is going to be possible.


>
>
> Is there a reason you want to use lazy byte strings rather than
> forcing full consumption? Do the 9P packets generally have a lot of
> trailing useless data?


Nope.  Just I noticed that there was a Network ByteString package that
utilized lazy bytestrings :-).

Even if that's why it's going for a 20th byte, shouldn't that be a bug?  :-)


>
>
> 1.
> http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/Data-Binary-Get.html#v%3AgetBytes
> 2.
> http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/Data-Binary-Get.html#v%3Aremaining
>
> On Tue, Jun 2, 2009 at 4:28 PM, David Leimbach  wrote:
> >
> >
> > On Tue, Jun 2, 2009 at 10:24 AM, Thomas DuBuisson
> >  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 providing.
> >
> > I've shown that I am not trying to decode more than I'm providing.  I've
> > asked, expliciitly, for 13 bytes, and then "remaining", and the library
> is
> > complaining about the 20th byte.
> >
> >>
> >> First check the length of the bytestring you pass in to the to level
> >> decode (or 'get') routine and walk though that to figure out how much
> >> it should be consuming.  I notice you have a guard on the
> >> 'getSpecific' function, hopefully you're sure the case you gave us is
> >> the branch being taken.
> >
> > The other branch is Rerror, which is a shorter message decode stream.
> >  Unfortunately, I can't get Debug.Trace to show anything to prove it's
> > taking this fork of the code.  I suppose I could unsafePerformIO :-)
> > Perhaps I just need a new version of "binary"??  I'll give it a go and
> try
> > your version.  But I need to decode over a dozen message types, so I will
> > need a case or guard or something.
> > Dave
> >>
> >>
> >> I think the issue isn't with the code provided.  I cleaned up the code
> >> (which did change behavior due to the guard and data declarations that
> >> weren't in the mailling) and it works fine all the way down to the
> >> expected minimum of 13 bytes.
> >>
> >>
> >> > import Data.ByteString.Lazy
> >> > import Data.Binary
> >> > import Data.Binary.Get
> >> >
> >> > data RV =
> >> > Rversion { size   :: Word32,
> >> >mtype  :: Word8,
> >> >tag:: Word16,
> >> >msize  :: Word32,
> >> >ssize  :: Word16,
> >> >version :: ByteString}
> >> >   deriving (Eq, Ord, Show)
> >>
> >> > instance Binary RV where
> >> >  get = do s <- getWord32le
> >> >  mtype <- getWord8
> >> >  getSpecific s mtype
> >> >   where
> >> >getSpecific s mt = do t <- getWord16le
> >> >  ms <- getWord32le
> >> >  ss <- getWord16le
> >> >  v <- getRemainingLazyByteString
> >> >  return $ Rversion {size=s,
> >> > mtype=mt,
> >> > tag=t,
> >> > msize=ms,
> >> > ssize=ss,
> >> > version=v }
> >> >  put _ = undefined
> >
> >
>
>
>
> --
> /jve
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Compiling a windows app - embedding a manifest

2009-06-02 Thread Bulat Ziganshin
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,
 Bulatmailto:bulat.zigans...@gmail.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] code reviewers wanted for hashed-storage (darcs)

2009-06-02 Thread Eric Kow
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 which each file in the pristine
cache is associated with a cryptographic hash.  Hashed repositories help
Darcs to resist some forms of corruption and also allow for nice
features such as a global patch cache and lazy patch fetching.
Unfortunately, our implementation can be rather slow.

Petr has some nice ideas for making these repositories work a lot
faster.  He will be producing a library he calls 'hashed-storage' which
generalises the idea of storing files associating them with a
cryptographic hash and furthermore improves on the current
implementation used by Darcs.  The hashed-storage library is general
purpose and may find a use in other applications that need to manage a
large number of files.

I'm excited about this project because if it succeeds, we can finally
start hammering home the point that yes, Darcs *can* be a fast revision
control system.  It may not fix all our problems -- we'll still need a
Darcs 3 -- but it should alleviate at least some of the practical day to
day issues.

I want to ensure that Petr's project is a success.  One thing in
particular is that I would like him to get regular code review from the
Haskell community, perhaps from folks who aren't already on the Darcs
team.  Do you think you can help?

Two volunteers needed
-
I'm looking for just two volunteers this summer:

1. Do you have one hour per week this summer?

   We need somebody to track and make comments on changes to
   hashed-storage over this summer.  The current library has only 8
   modules, with less than 1400 lines of code, so it should be
   relatively easy to get started :-)

2. Do you have a spare weekend in August?

   Towards the end of the summer, it would be nice to have somebody
   examine the "final" version of hashed-storage and give us their
   thoughts.

Again, no Darcs experience is needed, as this is a standalone module.
In fact, a fresh perspective would be very helpful.

More information

You can download hashed-storage from hackage from his darcs repository:
  darcs get http://repos.mornfall.net/hashed-storage
For more information about his project, see
  http://web.mornfall.net/blog/summer_of_code.html

Please get in touch with me if you can help.

Thanks!

Eric

-- 
Eric Kow 
PGP Key ID: 08AC04F9


pgphUQDmGStl4.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread John Van Enk
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
>> 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
>              mtype <- getWord8
>              getSpecific s mtype
>         where
>           getSpecific s mt
>                       | mt == mtRversion = do t <- getWord16le
>                                               ms <- getWord32le
>                                               ss <- getWord16le
>                                               v <-
> getRemainingLazyByteString
>                                               return $ MessageClient $
> Rversion {size=s,
>
>     mtype=mt,
>
>     tag=t,
>
>     msize=ms,
>
>     ssize=ss,
>
>     version=v}
>                       | mt == mtRerror = do t <- getWord16le
>                                             ss <- getWord16le
>                                             e <- getLazyByteString $
> fromIntegral ss
>                                             return $ MessageClient $ Rerror
> {size=s,
>
> mtype=mt,
>
> tag=t,
>
> ssize=ss,
>
> ename=e}
>
>>
>> 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'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 the response type for
>> > a
>> > Tversion request
>> >  = 2 bytes for 16bit message "tag".
>> >
>> > 0004 = 4 bytes for the 32 bit maximum message payload size I'm
>> > negotiating with the 9P server.  This is little endian for 1024
>> > 0600 =  2 bytes for 16 bit value for the length of the "string" I'm
>> > sending.
>> >  The strings are *NOT* null terminated in 9p, and this is little endian
>> > for
>> > 6 bytes remaining.
>> > 5032303030 = 6 bytes the ASCII or UTF-8 string "9P2000" which is 6 bytes
>> > 4 + 1 + 2 + 4 + 2 + 6 = 19 bytes.
>> > As far as I can see, my "get" code does NOT ask for a 20th byte, so why
>> > am I
>> > getting that error?
>> > get = do s <- getWord32le  -- 4
>> >              mtype <- getWord8  -- 1
>> >              getSpecific s mtype
>> >         where
>> >           getSpecific s mt
>> >                       | mt == mtRversion = do t <- getWord16le -- 2
>> >                                               ms <- getWord32le  -- 4
>> >                                               ss <- getWord16le -- 2
>> >                                               v <-
>> > getRemainingLazyByteString  -- remaining should be 6 bytes.
>> >                                               return $ MessageClient $
>> > Rversion {size=s,
>> >
>> >                         mtype=mt,
>> >
>> >                         tag=t,
>> >
>> >                         msize=ms,
>> >
>> >                         ssize=ss,
>> >
>> >                         version=v}
>> > Should I file a bug?  I don't believe I should be seeing an error
>> > message
>> > claiming a failure at the 20th byte when I've never asked for one.
>> > Dave
>> >
>> > On Tue, Jun 2, 2009 at 10:51 AM, John Van Enk  wrote:
>> >>
>> >> 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 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') routine and walk though that to figure out how much
>> >> > it should be consuming.  I notice you have a guard on the
>> >> > 'getSpecific' function, hopefully you're sure the case you gave us is
>> >> > the branch being taken.
>> >> >
>> >> > I think the issue isn't with the code provided.  I cleaned up the
>> >> > code
>> >> > (which did change behavior due to the guard and data declarations
>> >> > that
>> >> > weren't in the mailling) and it works fine all the way down to the
>> >> > expected minimum of 13 bytes.
>> >> >
>> >> >
>> >> >> import Data.ByteString.Lazy
>> >> >> import Data.Binary
>> >> >> import Data.Binary.Get
>> >> >>
>> >> >> data RV =
>> >> >> Rversion {     size   :: Word32,
>> >> >>                mtype  :: Word8,
>> >> >>                tag    :: Word16,
>> >> >>                msize  :: Word32,
>> >> >>                ssize  :: Word16,
>> >> >>                version :: 

Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread John Van Enk
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 generally have a lot of
trailing useless data?

1. 
http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/Data-Binary-Get.html#v%3AgetBytes
2. 
http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/Data-Binary-Get.html#v%3Aremaining

On Tue, Jun 2, 2009 at 4:28 PM, David Leimbach  wrote:
>
>
> On Tue, Jun 2, 2009 at 10:24 AM, Thomas DuBuisson
>  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 providing.
>
> I've shown that I am not trying to decode more than I'm providing.  I've
> asked, expliciitly, for 13 bytes, and then "remaining", and the library is
> complaining about the 20th byte.
>
>>
>> First check the length of the bytestring you pass in to the to level
>> decode (or 'get') routine and walk though that to figure out how much
>> it should be consuming.  I notice you have a guard on the
>> 'getSpecific' function, hopefully you're sure the case you gave us is
>> the branch being taken.
>
> The other branch is Rerror, which is a shorter message decode stream.
>  Unfortunately, I can't get Debug.Trace to show anything to prove it's
> taking this fork of the code.  I suppose I could unsafePerformIO :-)
> Perhaps I just need a new version of "binary"??  I'll give it a go and try
> your version.  But I need to decode over a dozen message types, so I will
> need a case or guard or something.
> Dave
>>
>>
>> I think the issue isn't with the code provided.  I cleaned up the code
>> (which did change behavior due to the guard and data declarations that
>> weren't in the mailling) and it works fine all the way down to the
>> expected minimum of 13 bytes.
>>
>>
>> > import Data.ByteString.Lazy
>> > import Data.Binary
>> > import Data.Binary.Get
>> >
>> > data RV =
>> > Rversion {     size   :: Word32,
>> >                mtype  :: Word8,
>> >                tag    :: Word16,
>> >                msize  :: Word32,
>> >                ssize  :: Word16,
>> >                version :: ByteString}
>> >       deriving (Eq, Ord, Show)
>>
>> > instance Binary RV where
>> >  get = do s <- getWord32le
>> >          mtype <- getWord8
>> >          getSpecific s mtype
>> >   where
>> >    getSpecific s mt = do t <- getWord16le
>> >                          ms <- getWord32le
>> >                          ss <- getWord16le
>> >                          v <- getRemainingLazyByteString
>> >                          return $ Rversion {size=s,
>> >                                             mtype=mt,
>> >                                             tag=t,
>> >                                             msize=ms,
>> >                                             ssize=ss,
>> >                                             version=v }
>> >  put _ = undefined
>
>



-- 
/jve
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread David Leimbach
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
 mtype <- getWord8
 getSpecific s mtype
where
  getSpecific s mt
  | mt == mtRversion = do t <- getWord16le
  ms <- getWord32le
  ss <- getWord16le
  v <-
getRemainingLazyByteString
  return $ MessageClient $
Rversion {size=s,

mtype=mt,

tag=t,

msize=ms,

ssize=ss,

version=v}
  | mt == mtRerror = do t <- getWord16le
ss <- getWord16le
e <- getLazyByteString $
fromIntegral ss
return $ MessageClient $ Rerror
{size=s,

mtype=mt,

tag=t,

ssize=ss,

ename=e}



>
>
> 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'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 the response type for
> a
> > Tversion request
> >  = 2 bytes for 16bit message "tag".
> >
> > 0004 = 4 bytes for the 32 bit maximum message payload size I'm
> > negotiating with the 9P server.  This is little endian for 1024
> > 0600 =  2 bytes for 16 bit value for the length of the "string" I'm
> sending.
> >  The strings are *NOT* null terminated in 9p, and this is little endian
> for
> > 6 bytes remaining.
> > 5032303030 = 6 bytes the ASCII or UTF-8 string "9P2000" which is 6 bytes
> > 4 + 1 + 2 + 4 + 2 + 6 = 19 bytes.
> > As far as I can see, my "get" code does NOT ask for a 20th byte, so why
> am I
> > getting that error?
> > get = do s <- getWord32le  -- 4
> >  mtype <- getWord8  -- 1
> >  getSpecific s mtype
> > where
> >   getSpecific s mt
> >   | mt == mtRversion = do t <- getWord16le -- 2
> >   ms <- getWord32le  -- 4
> >   ss <- getWord16le -- 2
> >   v <-
> > getRemainingLazyByteString  -- remaining should be 6 bytes.
> >   return $ MessageClient $
> > Rversion {size=s,
> >
> > mtype=mt,
> >
> > tag=t,
> >
> > msize=ms,
> >
> > ssize=ss,
> >
> > version=v}
> > Should I file a bug?  I don't believe I should be seeing an error message
> > claiming a failure at the 20th byte when I've never asked for one.
> > Dave
> >
> > On Tue, Jun 2, 2009 at 10:51 AM, John Van Enk  wrote:
> >>
> >> 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 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') routine and walk though that to figure out how much
> >> > it should be consuming.  I notice you have a guard on the
> >> > 'getSpecific' function, hopefully you're sure the case you gave us is
> >> > the branch being taken.
> >> >
> >> > I think the issue isn't with the code provided.  I cleaned up the code
> >> > (which did change behavior due to the guard and data declarations that
> >> > weren't in the mailling) and it works fine all the way down to the
> >> > expected minimum of 13 bytes.
> >> >
> >> >
> >> >> import Data.ByteString.Lazy
> >> >> import Data.Binary
> >> >> import Data.Binary.Get
> >> >>
> >> >> data RV =
> >> >> Rversion { size   :: Word32,
> >> >>mtype  :: Word8,
> >> >>tag:: Word16,
> >> >>msize  :: Word32,
> >> >>ssize  :: Word16,
> >> >>version :: ByteString}
> >> >>   deriving (Eq, Ord, Show)
> >> >
> >> >> instance Binary RV where
> >> >>  get = do s <- getWord32le
> >> >>  mtype <- getWord8
> >> >>  getSpecific s mtype
> >> >>   where
> >> >>getSpecific s mt = do t <- getWord16le
> >> >>  ms <- getWord32le
> >> >>  ss <-

Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread David Leimbach
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 providing.


I've shown that I am not trying to decode more than I'm providing.  I've
asked, expliciitly, for 13 bytes, and then "remaining", and the library is
complaining about the 20th byte.



>
> First check the length of the bytestring you pass in to the to level
> decode (or 'get') routine and walk though that to figure out how much
> it should be consuming.  I notice you have a guard on the
> 'getSpecific' function, hopefully you're sure the case you gave us is
> the branch being taken.


The other branch is Rerror, which is a shorter message decode stream.
 Unfortunately, I can't get Debug.Trace to show anything to prove it's
taking this fork of the code.  I suppose I could unsafePerformIO :-)

Perhaps I just need a new version of "binary"??  I'll give it a go and try
your version.  But I need to decode over a dozen message types, so I will
need a case or guard or something.

Dave


>
> I think the issue isn't with the code provided.  I cleaned up the code
> (which did change behavior due to the guard and data declarations that
> weren't in the mailling) and it works fine all the way down to the
> expected minimum of 13 bytes.
>
>
> > import Data.ByteString.Lazy
> > import Data.Binary
> > import Data.Binary.Get
> >
> > data RV =
> > Rversion { size   :: Word32,
> >mtype  :: Word8,
> >tag:: Word16,
> >msize  :: Word32,
> >ssize  :: Word16,
> >version :: ByteString}
> >   deriving (Eq, Ord, Show)
>
> > instance Binary RV where
> >  get = do s <- getWord32le
> >  mtype <- getWord8
> >  getSpecific s mtype
> >   where
> >getSpecific s mt = do t <- getWord16le
> >  ms <- getWord32le
> >  ss <- getWord16le
> >  v <- getRemainingLazyByteString
> >  return $ Rversion {size=s,
> > mtype=mt,
> > tag=t,
> > msize=ms,
> > ssize=ss,
> > version=v }
> >  put _ = undefined
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread John Van Enk
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'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 the response type for a
> Tversion request
>  = 2 bytes for 16bit message "tag".
>
> 0004 = 4 bytes for the 32 bit maximum message payload size I'm
> negotiating with the 9P server.  This is little endian for 1024
> 0600 =  2 bytes for 16 bit value for the length of the "string" I'm sending.
>  The strings are *NOT* null terminated in 9p, and this is little endian for
> 6 bytes remaining.
> 5032303030 = 6 bytes the ASCII or UTF-8 string "9P2000" which is 6 bytes
> 4 + 1 + 2 + 4 + 2 + 6 = 19 bytes.
> As far as I can see, my "get" code does NOT ask for a 20th byte, so why am I
> getting that error?
> get = do s <- getWord32le  -- 4
>              mtype <- getWord8  -- 1
>              getSpecific s mtype
>         where
>           getSpecific s mt
>                       | mt == mtRversion = do t <- getWord16le -- 2
>                                               ms <- getWord32le  -- 4
>                                               ss <- getWord16le -- 2
>                                               v <-
> getRemainingLazyByteString  -- remaining should be 6 bytes.
>                                               return $ MessageClient $
> Rversion {size=s,
>
>                         mtype=mt,
>
>                         tag=t,
>
>                         msize=ms,
>
>                         ssize=ss,
>
>                         version=v}
> Should I file a bug?  I don't believe I should be seeing an error message
> claiming a failure at the 20th byte when I've never asked for one.
> Dave
>
> On Tue, Jun 2, 2009 at 10:51 AM, John Van Enk  wrote:
>>
>> 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 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') routine and walk though that to figure out how much
>> > it should be consuming.  I notice you have a guard on the
>> > 'getSpecific' function, hopefully you're sure the case you gave us is
>> > the branch being taken.
>> >
>> > I think the issue isn't with the code provided.  I cleaned up the code
>> > (which did change behavior due to the guard and data declarations that
>> > weren't in the mailling) and it works fine all the way down to the
>> > expected minimum of 13 bytes.
>> >
>> >
>> >> import Data.ByteString.Lazy
>> >> import Data.Binary
>> >> import Data.Binary.Get
>> >>
>> >> data RV =
>> >> Rversion {     size   :: Word32,
>> >>                mtype  :: Word8,
>> >>                tag    :: Word16,
>> >>                msize  :: Word32,
>> >>                ssize  :: Word16,
>> >>                version :: ByteString}
>> >>       deriving (Eq, Ord, Show)
>> >
>> >> instance Binary RV where
>> >>  get = do s <- getWord32le
>> >>          mtype <- getWord8
>> >>          getSpecific s mtype
>> >>   where
>> >>    getSpecific s mt = do t <- getWord16le
>> >>                          ms <- getWord32le
>> >>                          ss <- getWord16le
>> >>                          v <- getRemainingLazyByteString
>> >>                          return $ Rversion {size=s,
>> >>                                             mtype=mt,
>> >>                                             tag=t,
>> >>                                             msize=ms,
>> >>                                             ssize=ss,
>> >>                                             version=v }
>> >>  put _ = undefined
>> >
>>
>>
>>
>> --
>> /jve
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



-- 
/jve
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread David Leimbach
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 the response type for a
Tversion request

 = 2 bytes for 16bit message "tag".


0004 = 4 bytes for the 32 bit maximum message payload size I'm
negotiating with the 9P server.  This is little endian for 1024

0600 =  2 bytes for 16 bit value for the length of the "string" I'm sending.
 The strings are *NOT* null terminated in 9p, and this is little endian for
6 bytes remaining.

5032303030 = 6 bytes the ASCII or UTF-8 string "9P2000" which is 6 bytes

4 + 1 + 2 + 4 + 2 + 6 = 19 bytes.

As far as I can see, my "get" code does NOT ask for a 20th byte, so why am I
getting that error?

get = do s <- getWord32le  -- 4
 mtype <- getWord8  -- 1
 getSpecific s mtype
where
  getSpecific s mt
  | mt == mtRversion = do t <- getWord16le -- 2
  ms <- getWord32le  -- 4
  ss <- getWord16le -- 2
  v <-
getRemainingLazyByteString  -- remaining should be 6 bytes.
  return $ MessageClient $
Rversion {size=s,

mtype=mt,

tag=t,

msize=ms,

ssize=ss,

version=v}

Should I file a bug?  I don't believe I should be seeing an error message
claiming a failure at the 20th byte when I've never asked for one.

Dave

On Tue, Jun 2, 2009 at 10:51 AM, John Van Enk  wrote:

> 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 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') routine and walk though that to figure out how much
> > it should be consuming.  I notice you have a guard on the
> > 'getSpecific' function, hopefully you're sure the case you gave us is
> > the branch being taken.
> >
> > I think the issue isn't with the code provided.  I cleaned up the code
> > (which did change behavior due to the guard and data declarations that
> > weren't in the mailling) and it works fine all the way down to the
> > expected minimum of 13 bytes.
> >
> >
> >> import Data.ByteString.Lazy
> >> import Data.Binary
> >> import Data.Binary.Get
> >>
> >> data RV =
> >> Rversion { size   :: Word32,
> >>mtype  :: Word8,
> >>tag:: Word16,
> >>msize  :: Word32,
> >>ssize  :: Word16,
> >>version :: ByteString}
> >>   deriving (Eq, Ord, Show)
> >
> >> instance Binary RV where
> >>  get = do s <- getWord32le
> >>  mtype <- getWord8
> >>  getSpecific s mtype
> >>   where
> >>getSpecific s mt = do t <- getWord16le
> >>  ms <- getWord32le
> >>  ss <- getWord16le
> >>  v <- getRemainingLazyByteString
> >>  return $ Rversion {size=s,
> >> mtype=mt,
> >> tag=t,
> >> msize=ms,
> >> ssize=ss,
> >> version=v }
> >>  put _ = undefined
> >
>
>
>
> --
> /jve
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Compiling a windows app - embedding a manifest

2009-06-02 Thread GüŸnther Schmidt

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


Re: [Haskell-cafe] Checking a value against a passed-in constructor?

2009-06-02 Thread Ryan Ingram
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? zeClass
>        end
>
> This does not require a new function for every class defined in Ruby.
> (To be fair, though, the class of a Ruby object tells you precious
> little, compared to a Haskell type constructor).
>
> 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..

So the question is, why do you need to know if x is an Atom or a Bool?
 The Haskell idiom is to pattern match and just do what you want with
the data:

f (Atom s) = ...
f (Bool b) = ...

instead of

f x = if isAtom x then ... atomData x ... else ... boolData x ...

Alternatively, you can define a fold[1] once:

myval :: MyVal -> (Bool -> a) -> (String -> a) -> a
myval (Bool b) bool atom = bool b
myval (Atom s) bool atom = atom s

f x = myval bool atom where
   bool b = ...
   atom s = ...

This is a small amount of boilerplate that you write once for each
type; it's possible to automate it with TH, but usually it's not worth
it, in my opinion.

Coming from Ruby (the same route I took to get to Haskell!), you
should be aware that Haskell does have somewhat more "boilerplate"
than Ruby, but it has its benefits as well.  I am a convert to the
Church of Purity and Type-Safety :)  And you can use type classes for
many metaprogramming tasks.

  -- ryan

[1] "fold" here is the general term for this type of function.  Examples are
foldr: 
http://haskell.org/ghc/docs/latest/html/libraries/base/src/GHC-Base.html#foldr
maybe: 
http://haskell.org/ghc/docs/latest/html/libraries/base/src/Data-Maybe.html#maybe
either: 
http://haskell.org/ghc/docs/latest/html/libraries/base/src/Data-Either.html#either
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread John Van Enk
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 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') routine and walk though that to figure out how much
> it should be consuming.  I notice you have a guard on the
> 'getSpecific' function, hopefully you're sure the case you gave us is
> the branch being taken.
>
> I think the issue isn't with the code provided.  I cleaned up the code
> (which did change behavior due to the guard and data declarations that
> weren't in the mailling) and it works fine all the way down to the
> expected minimum of 13 bytes.
>
>
>> import Data.ByteString.Lazy
>> import Data.Binary
>> import Data.Binary.Get
>>
>> data RV =
>> Rversion {     size   :: Word32,
>>                mtype  :: Word8,
>>                tag    :: Word16,
>>                msize  :: Word32,
>>                ssize  :: Word16,
>>                version :: ByteString}
>>       deriving (Eq, Ord, Show)
>
>> instance Binary RV where
>>  get = do s <- getWord32le
>>          mtype <- getWord8
>>          getSpecific s mtype
>>   where
>>    getSpecific s mt = do t <- getWord16le
>>                          ms <- getWord32le
>>                          ss <- getWord16le
>>                          v <- getRemainingLazyByteString
>>                          return $ Rversion {size=s,
>>                                             mtype=mt,
>>                                             tag=t,
>>                                             msize=ms,
>>                                             ssize=ss,
>>                                             version=v }
>>  put _ = undefined
>



-- 
/jve
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread Thomas DuBuisson
> 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') routine and walk though that to figure out how much
it should be consuming.  I notice you have a guard on the
'getSpecific' function, hopefully you're sure the case you gave us is
the branch being taken.

I think the issue isn't with the code provided.  I cleaned up the code
(which did change behavior due to the guard and data declarations that
weren't in the mailling) and it works fine all the way down to the
expected minimum of 13 bytes.


> import Data.ByteString.Lazy
> import Data.Binary
> import Data.Binary.Get
>
> data RV =
> Rversion { size   :: Word32,
>mtype  :: Word8,
>tag:: Word16,
>msize  :: Word32,
>ssize  :: Word16,
>version :: ByteString}
>   deriving (Eq, Ord, Show)

> instance Binary RV where
>  get = do s <- getWord32le
>  mtype <- getWord8
>  getSpecific s mtype
>   where
>getSpecific s mt = do t <- getWord16le
>  ms <- getWord32le
>  ss <- getWord16le
>  v <- getRemainingLazyByteString
>  return $ Rversion {size=s,
> mtype=mt,
> tag=t,
> msize=ms,
> ssize=ss,
> version=v }
>  put _ = undefined
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread John Van Enk
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 -> return empty -- Data.ByteString.Lazy.empty
 _ -> getRemainingLazyByteString

Hope this helps. :)

/jve

1: 
http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/Data-Binary-Get.html#v%3Aremaining

On Tue, Jun 2, 2009 at 12:20 PM, David Leimbach  wrote:
> 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 following fields in it:
>  Rversion {size :: Word32,
>                 mtype :: Word8,
>                 tag :: Word16,
>                 msize :: Word32,
>                 ssize :: Word16,
>                 version :: ByteString}
> But when I try to use the following implementation of "get" to decode this
> stream, I'm getting the following error:
> "too few bytes. Failed reading at byte position 20"
> Unfortunately, I'm only expecting 19 bytes, and in fact never asked for byte
> 20.  (I am just asking for everything up to ssize, and then
> "getRemainingLazyByteString").
> Is this a bug?    Is it mine or in Data.Binary?  :-)
> Here's my "get" function:
>  get = do s <- getWord32le
>              mtype <- getWord8
>              getSpecific s mtype
>         where
>           getSpecific s mt
>                       | mt == mtRversion = do t <- getWord16le
>                                               ms <- getWord32le
>                                               ss <- getWord16le
>                                               v <-
> getRemainingLazyByteString
>                                               return $ MessageClient $
> Rversion {size=s,
>
>                         mtype=mt,
>
>                         tag=t,
>
>                         msize=ms,
>
>                         ssize=ss,
>
>                         version=v}
>
>
> The good news is I'm talking 9P otherwise, correctly, just having some
> decoding issues.  I hope to have a hackage package eventually for this.
> Dave
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



-- 
/jve
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Success and one last issue with Data.Binary

2009-06-02 Thread David Leimbach
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 following fields in it:

 Rversion {size :: Word32,
mtype :: Word8,
tag :: Word16,
msize :: Word32,
ssize :: Word16,
version :: ByteString}

But when I try to use the following implementation of "get" to decode this
stream, I'm getting the following error:

"too few bytes. Failed reading at byte position 20"

Unfortunately, I'm only expecting 19 bytes, and in fact never asked for byte
20.  (I am just asking for everything up to ssize, and then
"getRemainingLazyByteString").

Is this a bug?Is it mine or in Data.Binary?  :-)

Here's my "get" function:

 get = do s <- getWord32le
 mtype <- getWord8
 getSpecific s mtype
where
  getSpecific s mt
  | mt == mtRversion = do t <- getWord16le
  ms <- getWord32le
  ss <- getWord16le
  v <-
getRemainingLazyByteString
  return $ MessageClient $
Rversion {size=s,

mtype=mt,

tag=t,

msize=ms,

ssize=ss,

version=v}



The good news is I'm talking 9P otherwise, correctly, just having some
decoding issues.  I hope to have a hackage package eventually for this.

Dave
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Possible Haskell Project

2009-06-02 Thread S. Doaitse Swierstra
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 extremely informative and make you loose any hope that something  
good will come out of this soon; there are just too many stakeholders,  
and no so-called "problem-owner"s except you. Simple questions asked,  
for which there often is no answer is:


 - who owns the information?
 - are you allowed to change information which you own?
 - should docters pay for the right to enter information in this  
system, or be paid for the service they provide if they enter  
information?


Instead of trying to change the world you may run a small wiki (I run  
Twiki) server on your home machine where you just store the  
information you collect, and enter your information while you are  
having a consult through your iPhone! When you leave the room you ask  
your docter whether what you have entered is a correct view of this  
situation ;-}I think this will solve the major part of your problem,  
and maybe it opens the eyes of the medical establishment.


 Doaitse Swierstra




On 2 jun 2009, at 11:18, wren ng thornton wrote:


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 problems, and our friends at Galios continue to show how
effective Haskell is at building secure systems.
Any thoughts?  Ideas?


Actually, it's a lot more complicated than that, albeit not for  
"technical" reasons. There's a great deal of legislation about what  
can and cannot be done with medical records: who can have access to  
them, under what circumstances, how they can be transmitted, stored,  
etc. This is more than just boilerplate code--- clinics can be  
audited to prove proper handling and can loose their licenses or  
worse for improper handling of records. Additionally, the requisite  
formats do require a lot of boilerplate code since the protocols  
were defined back in the paper age and medical legislation moves at  
the speed of mountains.


I worked briefly on an open-source database project for managing a  
medical clinic's records (so, not even for dealing with the public  
in any way). The technical feat isn't that difficult, as you say,  
but the human engineering involved can be quite complex--- and the  
human programming will have major effects on the design, in order to  
forbid invalid or unacceptable behavior. It's not a project to  
undertake lightly or without corporate funding.


Medical record management is a market that has very low penetration  
from the F/OSS movement, which in turn places a burden on smaller  
clinics, so I'm all for anyone who's willing to invest in an open  
solution :)


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Possible Haskell Project

2009-06-02 Thread Tom Hawkins
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 standards so I don't know how useful
> they'd be. I think they might be geared towards vendor-to-vendor
> interop.
>
> As for the legacy of people who thought it wasn't complex:
> http://histalk.blog-city.com/guest_article__repeat_after_me_healthcare_data_models_matter.htm
>
> I don't agree with everything the guy wrote, but it's an interesting article.

In an industry like this that generates so much data, I think all
parties are tempted to record and track as must as possible.  But
after all the lab results, x-rays, and MRIs, it's the two or three
paragraphs of a doctor's dictation that matter.  Maybe patients and
doctors would be best served if they had an easy way to store,
retrieve, and query these dictations.

I see this as an abstracting database problem:
- records (dictations) are write-once-read-only data pertaining to a
subject (patient)
- some users (doctors, patients) are allowed to view a subset of
records on a subject
- some users are allowed to create new records on a subject
- some users are allowed to change capabilities of other users

Then, built on top of an abstract distributed data storage problem:
- a network of computers store a collection of write-once-read-only
data chunks (encoded, fragmented records)
- chunks are distributed to minimize access time
- chunks are distributed to maintain data integrity through system failures

Both of these abstract problems can be used for many things outside
the medical field.  So even if an electronic health record project
does not pan out, the code could find its way into other applications.

-Tom
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Compiling a windows app - embedding application icon

2009-06-02 Thread Bulat Ziganshin
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 using windres:
windres.exe icon.rc icon.o

3) link in icon.o when making executable:
ghc --make main.hs icon.o


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Spam apology

2009-06-02 Thread Daniel Cook
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


[Haskell-cafe] HXT XmlPicklers - TH Derivation

2009-06-02 Thread Max Cantor

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 list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Compiling a windows app - embedding application icon

2009-06-02 Thread GüŸnther Schmidt

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


Re: [Haskell-cafe] HaL4: Haskell-Meeting in Germany, 12th June 2009

2009-06-02 Thread Janis Voigtlaender

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.tu-dresden.de/~voigt/
mailto:vo...@tcs.inf.tu-dresden.de

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] HaL4: Haskell-Meeting in Germany, 12th June 2009

2009-06-02 Thread Janis Voigtlaender

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://wwwtcs.inf.tu-dresden.de/~voigt/
mailto:vo...@tcs.inf.tu-dresden.de
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Checking a value against a passed-in constructor?

2009-06-02 Thread Dan
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 came up with this too, but it seemed ugly to create unnecessary
new values just to take them apart again.

>   is_atom (Atom _) = True
>   is_atom _= False

This is nicer.  It still requires listing out the possible
constructors (Bool, Atom ... the real code obviously has more).  I
don't like that, because I've already listed them out once, in the type
declaration itself.  Surely, I shouldn't have to list them out again?

> There are various meta-programming ("Scrap Your Boilerplate",
> "Template Haskell") approaches you can use to automate some of
> these.

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? zeClass
end

This does not require a new function for every class defined in Ruby.
(To be fair, though, the class of a Ruby object tells you precious
little, compared to a Haskell type constructor).

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..

Cheers,
- Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Possible Haskell Project

2009-06-02 Thread wren ng thornton

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 problems, and our friends at Galios continue to show how
effective Haskell is at building secure systems.

Any thoughts?  Ideas?


Actually, it's a lot more complicated than that, albeit not for 
"technical" reasons. There's a great deal of legislation about what can 
and cannot be done with medical records: who can have access to them, 
under what circumstances, how they can be transmitted, stored, etc. This 
is more than just boilerplate code--- clinics can be audited to prove 
proper handling and can loose their licenses or worse for improper 
handling of records. Additionally, the requisite formats do require a 
lot of boilerplate code since the protocols were defined back in the 
paper age and medical legislation moves at the speed of mountains.


I worked briefly on an open-source database project for managing a 
medical clinic's records (so, not even for dealing with the public in 
any way). The technical feat isn't that difficult, as you say, but the 
human engineering involved can be quite complex--- and the human 
programming will have major effects on the design, in order to forbid 
invalid or unacceptable behavior. It's not a project to undertake 
lightly or without corporate funding.


Medical record management is a market that has very low penetration from 
the F/OSS movement, which in turn places a burden on smaller clinics, so 
I'm all for anyone who's willing to invest in an open solution :)


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble with types

2009-06-02 Thread wren ng thornton

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. However, each use site 
this polymorphism may be restricted down (in particular, to the point of 
monomorphism).


In a syntax more like Core, the definition of the identity function is,

id :: forall a. a -> a
id @a (x :: a) = x

Where the @ is syntax for reifying types or for capital-lambda 
application (whichever interpretation you prefer). In this syntax it's 
clear to see that |id| (of type forall a. a -> a) is quite different 
than any particular |id @a| (of type a->a for the particular @a).



So in your example, there's a big difference between these definitions,

(f,g) = (id,id)

(f', g') @a = (id @a, id @a)

The latter one is polymorphic, but it has interesting type sharing going 
on which precludes giving universally quantified types to f' and g' (the 
universality is for the pair (f',g') and so the types of f' and g' must 
covary). Whereas the former has both fields of the tuple being 
polymorphic (independently).


Both interpretations of the original code are legitimate in theory, but 
the former is much easier to work with and reason about. It also allows 
for tupling definitions as a way of defining local name scope blocks, 
without side effects on types.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: new version of uu-parsinglib

2009-06-02 Thread Ross Paterson
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 empty language.  And some of us are
also interested in Alternatives that aren't parsers.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe