> And also, there is one problem left. When i read a binary file, data is
> truncated at the charactor EOF.
Which character is this: ^D or ^Z? Which operating system - Windows,
perhaps? And you are reading from a file, not from stdin?
-k
___
Haskel
Donald Bruce Stewart wrote:
> Bryan O'Sullivan, Don Stewart and John Goerzen are pleased, and frankly,
> very excited to announce that were developing a new book for O'Reilly, on
> practical Haskell programming. The working title is Real-World Haskell.
I have absolutely no doubt that I'm gonna lov
leaveye.guo:
> Thanks for your suggestion, and sorry for the subject.
>
> I have read the introduction of Data.ByteString, it is helpful.
>
> And also, there is one problem left. When i read a binary file, data
> is truncated at the charactor EOF.
>
> Which function could do this work correctly
Thanks for your suggestion, and sorry for the subject.
I have read the introduction of Data.ByteString, it is helpful.
And also, there is one problem left. When i read a binary file, data is
truncated at the charactor EOF.
Which function could do this work correctly ?
--
leaveye.guo:
> Hi MailList Haskell-Cafe:
>
> Till now, which module / package / lib can i use to access binary
> file ? And is this easy to use in GHC ?
Data.Binary? Or perhaps just Data.ByteString, available on hackage,
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bina
Hi MailList Haskell-Cafe:
Till now, which module / package / lib can i use to access binary file ?
And is this easy to use in GHC ?
Regards
--
L.Guo
2007-05-24
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haske
I'll condense my remaining replies to this thread into a single message,
to save people a little noise.
Henning Thielemann:
I guess there will also be some lines about how to write
efficient code by using ByteString et. al.?
You bet!
What about a public darcs repository where people can co
Dougal Stanton wrote:
That is fantastic news to hear. I realise this may be jumping the gun
a bit but could you say anything about predicted timelines?
Not just yet, but it will be a much faster process with three seasoned
verbmonkeys at work than if we had just one.
Are you
starting from
Joshua,
Obviously this example is contrived, and you'd never want to use the
list comprehension syntax for the IO monad. But you might want to for,
say, the probability monad. Isn't that enough reason enough to
decouple the sugar from the typing? (Though I agree with Claus that
cryptic error mes
Are you seeking an intellectually challenging position in which you'll
be developing cutting edge software using functional programming
technologies? Do you aspire to work with a team that shares your
level of commitment and enthusiasm to develop tomorrow's
high-assurance technology today? Do you
On 5/23/07, Adrian Hey <[EMAIL PROTECTED]> wrote:
I think I still prefer..
var :: IORef Int
var <- newIORef 3
So do I. For one very good reason: this syntax could be defined as a
"constructor" syntax and guaranteed to run before main.
The other syntaxes proposed don't strike me as sufficientl
if you want to go down that route:
Prelude> let monadic m = m `asTypeOf` return undefined
Prelude> :t monadic undefined
monadic undefined :: (Monad m) => m a
Prelude> :t monadic $ undefined >> return ()
monadic $ undefined >> return () :: (Monad m) => m ()
Prelude> :t monadic
Chad Scherrer wrote:
On 5/23/07, Philippa Cowderoy <[EMAIL PROTECTED]> wrote:
On Wed, 23 May 2007, Chad Scherrer wrote:
> Is (^2) really considered currying? As I understand it, this is
> syntactic sugar for a "section", and might confuse the issue a bit,
> since it's distinct from ((^) 2).
Su
While we're on the topic of coupling/cohesion of types and syntactic
sugar (and because sometimes problems are made easier by generalizing
them), I have a question.
What is the rationale for disallowing the following code?
main = print "Type 'True' on three lines or I will quit." >> foo
foo = [
On 5/24/07, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:
Why do you need to convert Socket to Handle?
Initially, we chose to use socketToHandle for simplicity reasons--why
duplicate functionality if we can reuse it? After Simon Marlow's
comment that my reason to assume it inappropriate does n
* Dan Weston <[EMAIL PROTECTED]> [070523 12:41]:
> What power animal have you chosen for the cover of your O'Reilly book? Alas,
> most of the good ones are gone already!
I'd like to suggest the Mantis shrimp because they have excellent
vision, they're long lived and they pack a punch.
I haven'
I am uncertain about all the issues here, but
Why do you need to convert Socket to Handle?
I have no clue if this code I pasted below works but it does compile:
> import Network.Socket
> import Data.ByteString.Base as Base
>
> -- 'recvBSFrom' gets a strict ByteString from a socket.
> -- cre
Am Mittwoch, 23. Mai 2007 17:55 schrieb Steffen Mazanek:
> Hello,
>
> I have two questions regarding a Cocke, Younger, Kasami parser.
>
> Consider this program:
>
> type NT = Char -- Nonterminal
> type T = Char -- Terminal
> -- a Chomsky production has either two nonterminals or one terminal on it
Once again thank you apfelmus :-)
The key point of the dynamic programming algorithm is indeed to memoize
the results gs i j for all pairs of i and j. In other words, the insight
that yields a fast algorithm is that for solving the subproblems gs i j
(of which there are n^2), solution to smaller
Spencer,
How about:
do x ==> (x :: Monad m => m a)
That one does not do it, because now you demand x to be polymorphic
in all monad types m and all monad-element types a, which I guess
restricts x to
undefined
and
return undefined
and combinations thereof, glued together by mona
Hello Cafe!
I'd greatly appreciate any ideas/comments on the design of the
interface to the Network.HTTP library with a LazyByteString (LBS)
backend.
As has been discussed previously on this list [1] lazy evaluation can
complicate resource management, which is especially critical if
resources ar
On 5/23/07, Tom Harper <[EMAIL PROTECTED]> wrote:
I really hope they choose the flying squirrel.
They should just use that picture of Philip Wadler as Lambda-Man.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman
That's pretty baa-aa-aad.
Mike
brad clawsie wrote:
On Wed, May 23, 2007 at 12:40:58PM -0700, Dan Weston wrote:
What power animal have you chosen for the cover of your O'Reilly book? Alas,
most of the good ones are gone already!
"lamb"-da?
___
Has
On Wed, May 23, 2007 at 12:40:58PM -0700, Dan Weston wrote:
> What power animal have you chosen for the cover of your O'Reilly book? Alas,
> most of the good ones are gone already!
"lamb"-da?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http
I really hope they choose the flying squirrel.
On 5/23/07, Dan Weston <[EMAIL PROTECTED]> wrote:
What power animal have you chosen for the cover of your O'Reilly book?
Alas, most of the good ones are gone already!
Donald Bruce Stewart wrote:
> Bryan O'Sullivan, Don Stewart and John Goerzen are
What power animal have you chosen for the cover of your O'Reilly book?
Alas, most of the good ones are gone already!
Donald Bruce Stewart wrote:
Bryan O'Sullivan, Don Stewart and John Goerzen are pleased, and frankly,
very excited to announce that were developing a new book for O'Reilly, on
pra
On Wed, 23 May 2007 19:54:27 +0100
"Neil Mitchell" <[EMAIL PROTECTED]> wrote:
> Hi
>
> > > foo = do (1 :: Int)
> >
> > While intuitively this should be disallowed, it seems a pity that
> > desugaring couldn't be totally separated from typechecking. Hmm.
>
> You can always desugar as:
>
> do x ==
foo = do (1 :: Int)
While intuitively this should be disallowed, it seems a pity that
desugaring couldn't be totally separated from typechecking. Hmm.
or perhaps not. while a type-free desugaring, followed by
type-checking, seems more modular, i'd rather see any type
errors in terms of the sug
The plan is to cover the major techniques used to write serious,
real-world Haskell code, so that programmers can just get to work in the
language.
Amen to that! Too many people seem to think Hasekll is some sort of
"pretend language" that is only useful for defining quicksort and other
triv
On Wed, 23 May 2007, Ian Lynagh wrote:
> On Wed, May 23, 2007 at 06:27:32PM +0100, Neil Mitchell wrote:
> >
> > foo = do (1 :: Int)
>
> While intuitively this should be disallowed, it seems a pity that
> desugaring couldn't be totally separated from typechecking. Hmm.
>
Disallow it by beating
2007/5/23, Ian Lynagh <[EMAIL PROTECTED]>:
On Wed, May 23, 2007 at 06:27:32PM +0100, Neil Mitchell wrote:
>
> foo = do (1 :: Int)
While intuitively this should be disallowed, it seems a pity that
desugaring couldn't be totally separated from typechecking. Hmm.
You *could* desugar it to
foo =
Hi
> foo = do (1 :: Int)
While intuitively this should be disallowed, it seems a pity that
desugaring couldn't be totally separated from typechecking. Hmm.
You can always desugar as:
do x ==> return () >> x
Although then you are relying on the Monad laws more than you possibly
should. You c
On Wed, May 23, 2007 at 06:27:32PM +0100, Neil Mitchell wrote:
>
> foo = do (1 :: Int)
While intuitively this should be disallowed, it seems a pity that
desugaring couldn't be totally separated from typechecking. Hmm.
Ian, on the fence.
___
Haskell-C
On 23/05/07, David House <[EMAIL PROTECTED]> wrote:
Why should it compile? Expressions in a do-block have to have the type
m a for some monad m, don't they?
Further developments on #haskell:
dmhouse: where in the report does it say that do blocks constrain
types inherently?
SamB_XP: I was
Neil,
As discussed on #haskell, the following code:
module Foo where
foo = do (1 :: Int)
Compiles fine on Yhc, but doesn't on Hugs and GHC.
So the question is, who is right? Where do the bugs need filing? Does
this issue need clarifying for Haskell' ?
Wel
On 23/05/07, Neil Mitchell <[EMAIL PROTECTED]> wrote:
As discussed on #haskell, the following code:
module Foo where
foo = do (1 :: Int)
Compiles fine on Yhc, but doesn't on Hugs and GHC.
Why should it compile? Expressions in a do-block have to have the type
Steffen Mazanek wrote:
> I have two questions regarding a Cocke, Younger, Kasami parser.
>
> type NT = Char -- Nonterminal
> type T = Char -- Terminal
> -- a Chomsky production has either two nonterminals or one terminal on its
> right-hand side
> type ChomskyProd = (NT, Either T (NT, NT))
> -- a
Hi,
As discussed on #haskell, the following code:
module Foo where
foo = do (1 :: Int)
Compiles fine on Yhc, but doesn't on Hugs and GHC.
GHC:
Couldn't match expected type `t t1' against inferred type `Int'
In the expression: (1 :: Int)
In the express
Disclaimer: I've not read the standard.
Sections are de-sugared depending on which argument you supply:
(x^) ==> (^) x
(^x) ==> flip (^) x
I think this is why they are considered special cases.
Prelude> map (^2) [1..10]
[1,4,9,16,25,36,49,64,81,100]
Prelude> map (flip (^) 2) [1..10]
[1,4,9,16,
On 5/23/07, Philippa Cowderoy <[EMAIL PROTECTED]> wrote:
On Wed, 23 May 2007, Chad Scherrer wrote:
> Is (^2) really considered currying? As I understand it, this is
> syntactic sugar for a "section", and might confuse the issue a bit,
> since it's distinct from ((^) 2).
Sure, but it's (flip (^)
PR Stanley wrote:
What is the rationale behind currying?
Given
map :: (a->b) -> [a]->[b]
take :: Int -> [a] -> [a]
I can write "map f . take 10" or "take 10 >>> map f".
Given
tmap :: (a->b, [a]) -> [b]
ttake :: (Int, [a]) -> [a]
I have to write "\x -> tmap(f, ttake(10, x))".
I
On Wed, 23 May 2007, Chad Scherrer wrote:
> Is (^2) really considered currying? As I understand it, this is
> syntactic sugar for a "section", and might confuse the issue a bit,
> since it's distinct from ((^) 2).
Sure, but it's (flip (^)) 2.
--
[EMAIL PROTECTED]
Sometimes you gotta fight fire
Is (^2) really considered currying? As I understand it, this is
syntactic sugar for a "section", and might confuse the issue a bit,
since it's distinct from ((^) 2). In this case we would have something
like
Prelude> let pow2 = ((^) 2)
Prelude> map pow2 [1..10]
[2,4,8,16,32,64,128,256,512,1024]
Hello,
I have two questions regarding a Cocke, Younger, Kasami parser.
Consider this program:
type NT = Char -- Nonterminal
type T = Char -- Terminal
-- a Chomsky production has either two nonterminals or one terminal on its
right-hand side
type ChomskyProd = (NT, Either T (NT, NT))
-- a gramm
Henning,
i need the bi-partitions of a multiset. That is, all the ways you can split
a multiset, M, into two multisets, M1 and M2, such that M = M1
`multiset-union` M2.
Best wishes,
--greg
On 5/23/07, Henning Thielemann <[EMAIL PROTECTED]> wrote:
On Tue, 22 May 2007, Greg Meredith wrote:
>
Ketil Malde wrote:
> On Tue, 2007-05-22 at 10:19 +0200, apfelmus wrote:
>
>> http://www.asktog.com/TOI/toi06KeyboardVMouse1.html
>>
>> It adresses the question whether selecting commands in menus with the
>> mouse or accessing them via keyboard shortcuts is faster. The answer is:
>>
>> "* Test su
On Wed, 2007-05-23 at 17:01 +1000, Donald Bruce Stewart wrote:
> Bryan O'Sullivan, Don Stewart and John Goerzen are pleased, and frankly,
> very excited to announce that were developing a new book for O'Reilly, on
> practical Haskell programming. The working title is Real-World Haskell.
>
> The pl
On Tue, 22 May 2007, Greg Meredith wrote:
> mSplitC :: [a] -> [([a], [a])] -- C for comprehension
>
> mSplitC [] = [([],[])]
> mSplitC [x] = [([x],[])]
> mSplitC (x:xs) = concat [ [(x:l,r),(l,x:r)] | (l,r) <- mSplitC xs ]
>
> which Matthias Radestock suggested to me.
>
> Note that if you only sup
On Wed, 23 May 2007, Dougal Stanton wrote:
> On 23/05/07, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote:
> >
> > Bryan O'Sullivan, Don Stewart and John Goerzen are pleased, and frankly,
> > very excited to announce that were developing a new book for O'Reilly, on
> > practical Haskell programmin
On 5/23/07, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote:
Bryan O'Sullivan, Don Stewart and John Goerzen are pleased, and frankly,
very excited to announce that were developing a new book for O'Reilly, on
practical Haskell programming. The working title is Real-World Haskell.
That is simply
On 23/05/07, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote:
Bryan O'Sullivan, Don Stewart and John Goerzen are pleased, and frankly,
very excited to announce that were developing a new book for O'Reilly, on
practical Haskell programming. The working title is Real-World Haskell.
That is fantas
On Wed, 2007-05-23 at 10:45 +0100, Alistair Bayley wrote:
> Hello cafe,
>
> D'ya fancy an optimisation exercise?
>
> In Takusen we currently marshal UTF8-encoded CStrings by first turning the
> CString into [word8], and then running this through a [Word8] -> String
> UTF8 decoder. We thought it w
Hello cafe,
D'ya fancy an optimisation exercise?
In Takusen we currently marshal UTF8-encoded CStrings by first turning the
CString into [word8], and then running this through a [Word8] -> String
UTF8 decoder. We thought it would be more space-efficient (and hopefully
faster) to marshal directly
On Wed, 23 May 2007 10:07:29 +0200
Gour <[EMAIL PROTECTED]> wrote:
> Congratualtions for your effort?
Oops...it should be !
> Sincerely,
> Gour
signature.asc
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www
On Wed, 23 May 2007 17:01:28 +1000
[EMAIL PROTECTED] (Donald Bruce Stewart) wrote:
Hi!
Congratualtions for your effort?
> Bryan O'Sullivan, Don Stewart and John Goerzen are pleased, and
> frankly, very excited to announce that were developing a new book for
> O'Reilly, on practical Haskell prog
On Wednesday 23 May 2007 19:01, Donald Bruce Stewart wrote:
> Bryan O'Sullivan, Don Stewart and John Goerzen are pleased, and frankly,
> very excited to announce that were developing a new book for O'Reilly, on
> practical Haskell programming. The working title is Real-World Haskell.
That's good n
Bryan O'Sullivan, Don Stewart and John Goerzen are pleased, and frankly,
very excited to announce that were developing a new book for O'Reilly, on
practical Haskell programming. The working title is Real-World Haskell.
The plan is to cover the major techniques used to write serious,
real-world Ha
57 matches
Mail list logo