[Haskell-cafe] eyes again please .... on my POSIX aio code
Hello, I have modified my aioError and aioReturn to hopefully be more in line with the actual aio_error and aio_return signatures, respectively. In the first implementation I had suffered a serious brain f**t ... oh well . The implementations below are still somewhat preliminary. Not seemingly rocket science I am still not getting a correct count from aioReturn .. should be 20 but I get 0! I have a C program which behaves properly giving 20 for aio_return! grr! aioReturn :: AIOCB -> IO (AIOCB, ByteCount) aioReturn aiocb = do allocaBytes (#const sizeof(struct aiocb)) $ \ p_aiocb -> do poke p_aiocb aiocb -- DO A PEEK HERE! -- count <- throwErrnoIfMinus1 "aioReturn" (c_aio_return p_aiocb) count <- (c_aio_return p_aiocb) putStrLn ("count -> " ++ (show count)) aiocb <- peek p_aiocb putStrLn "aioReturn" aiocb1 <- peek p_aiocb dumpAIOCB aiocb1 return (aiocb, fromIntegral count) foreign import ccall safe "aio.h aio_return" c_aio_return :: Ptr AIOCB -> IO CInt aioError :: AIOCB -> IO (Errno) aioError aiocb = do allocaBytes (#const sizeof(struct aiocb)) $ \ p_aiocb -> do poke p_aiocb aiocb --throwErrnoIfMinus1 "aioError" (c_aio_error p_aiocb) errno <- (c_aio_error p_aiocb) putStrLn ("errno -> " ++ (show errno)) putStrLn "aioError" aiocb1 <- peek p_aiocb dumpAIOCB aiocb1 return (Errno errno) foreign import ccall safe "aio.h aio_error" c_aio_error :: Ptr AIOCB -> IO CInt I added an internal helper function dumpAIOCB to print out the aiocb at points for sanity checking!! dumpAIOCB :: AIOCB -> IO () dumpAIOCB (AIOCB aioFd aioLioOpcode aioReqPrio aioOffset aioBuf aioBytes aioSigevent) = do putStrLn "aiocb dump" putStrLn ("fd => " ++ (show aioFd)) putStrLn ("opcode => " ++ (show aioLioOpcode)) putStrLn ("prio => " ++ (show aioReqPrio)) putStrLn ("offset => " ++ (show aioOffset)) -- aioBuf putStrLn ("nbytes => " ++ (show aioBytes) ++ "\n") -- aioSigevent Kind regards, Vasili ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] nested parsing?
Here's something I occasionally want to do with parsec: msg = do header body <- manyTill anyToken footer vals <- sub_parse parse_body (preprocess body) ... By coincidence I notice that perhaps the "manyTill stack overflow" thread could use something like this too. So I wrote: sub_parse :: Parsec.GenParser subtok st a -> [subtok] -> Parsec.GenParser tok st a sub_parse parser toks = do st <- Parsec.getState pos <- Parsec.getPosition case Parsec.runParser (Parsec.setPosition pos >> parser) st "" toks of Left err -> fail (show err) Right val -> return val -- oh yes, and I'd set the state to the final sub parse state too In this particular case, I found another solution that didn't need sub-parsing, so I haven't actually tested this much. In particular parsec doesn't let me throw a "raw" exception so I have to use "fail" and the error msgs look ugly. In addition, if 'preprocess' adds or removes tokens from 'body', I have to do something awkward like pass tokens around as (pos, tok). But come to think of it, I've done this pattern before, where I invoke a sub-monad and (mostly) splice it in with the current one, in one case to allow the submonad to be monomorphic on the monad type while calling monad remains polymorphic, in another case so I can run the submonad from dynamically loaded code which must be monomorphic but splice its results into the polymorphic calling monad... this is similar to the first one I guess. It seems somewhat similar to what catchError is doing. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] parsec manyTill stack overflow
I'm using makeTokenParser and buildExpressionParser for the inner_parser. Thanks for your thoughts, I'll use a two-stage parser that looks for /end_section> and stores tokens in heap and then getInput/setInput to feed the inner_parser. --- On Fri, 7/4/08, Jonathan Cast <[EMAIL PROTECTED]> wrote: > From: Jonathan Cast <[EMAIL PROTECTED]> > Subject: Re: [Haskell-cafe] parsec manyTill stack overflow > To: [EMAIL PROTECTED] > Cc: "Derek Elkins" <[EMAIL PROTECTED]>, haskell-cafe@haskell.org > Date: Friday, July 4, 2008, 3:29 PM > On Fri, 2008-07-04 at 15:15 -0700, Badea Daniel wrote: > > The file I'm trying to parse contains mixed > sections like: > > > > ... > > > > > > > ... script including arithmetic expressions ... > > > > /end_section> > > > > ... > > > > so I defined two parsers: one for the 'outer' > language and > > the other one for the 'inner' language. I > used (manyTill > > inner_parser end_section_parser) > > Does inner_parser (or a parser it calls) recognize > `/end_section'? If > not, I don't think you actually need manyTill. If so, > that's more > difficult. Two thoughts: > > * This design looks vaguely XML-ish; is it possible to use > a two-stage > parser, recognizing but not parsing the arithmetic > expressions and then > looping back over the parse tree later? > > * If the part of inner_parser that would recognize > /end_section > (presumably as a division operator followed by an > identifier?) is well > isolated, you could locally exclude it there; e.g., instead > of > > divison_operator = operator "/" > > say > > division_operatory = try $ do > satisfy (=='/') > notFollowedBy (string "end_section") > whitespace > > (Or reverse the order or notFollowedBy and whitespace). > > jcc ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] parsec manyTill stack overflow
On Fri, 2008-07-04 at 15:15 -0700, Badea Daniel wrote: > The file I'm trying to parse contains mixed sections like: > > ... > > > ... script including arithmetic expressions ... > > /end_section> > > ... > > so I defined two parsers: one for the 'outer' language and > the other one for the 'inner' language. I used (manyTill > inner_parser end_section_parser) Does inner_parser (or a parser it calls) recognize `/end_section'? If not, I don't think you actually need manyTill. If so, that's more difficult. Two thoughts: * This design looks vaguely XML-ish; is it possible to use a two-stage parser, recognizing but not parsing the arithmetic expressions and then looping back over the parse tree later? * If the part of inner_parser that would recognize /end_section (presumably as a division operator followed by an identifier?) is well isolated, you could locally exclude it there; e.g., instead of divison_operator = operator "/" say division_operatory = try $ do satisfy (=='/') notFollowedBy (string "end_section") whitespace (Or reverse the order or notFollowedBy and whitespace). jcc ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] parsec manyTill stack overflow
The file I'm trying to parse contains mixed sections like: ... ... so I defined two parsers: one for the 'outer' language and the other one for the 'inner' language. I used (manyTill inner_parser end_section_parser) but I got a stack overflow because there's just too much text between section begin and end. With getInput I can switch from the outer parser to the inner parser but this one tries to parse until eof and when it hits the '/end_section>' it fails. --- On Fri, 7/4/08, Derek Elkins <[EMAIL PROTECTED]> wrote: > From: Derek Elkins <[EMAIL PROTECTED]> > Subject: Re: [Haskell-cafe] parsec manyTill stack overflow > To: "Badea Daniel" <[EMAIL PROTECTED]> > Cc: haskell-cafe@haskell.org > Date: Friday, July 4, 2008, 2:22 PM > On Fri, 2008-07-04 at 13:31 -0700, Badea Daniel wrote: > > I'm trying to parse a large file looking for > instructions on each line and for a section end marker but > Parsec's manyTill function causes stack overflow, as > you can see in the following example (I'm using ghci > 6.8.3): > > > > > parse (many anyChar) "" > ['a'|x<-[1..1024*64]] > > > > It almost immediately starts printing > "aaa" and runs to completion. > > > > > parse (manyTill anyChar eof) "" > ['a'|x<-[1..1024*1024]] > > *** Exception: stack overflow > > > > I guess this happens because manyTill recursively > accumulates output > > from the first parser and returns only when it hits > the 'end' parser. > > Is it possible to write a version of > 'manyTill' that works like 'many' > > returning output from 'anyChar' as soon as it > advances through the > > list of tokens? > > No, manyTill doesn't know whether it is going to return > anything at all > until its second argument succeeds. I can make manyTill > not stack > overflow, but it will never immediately start returning > results. For > the particular case above you can use getInput and setInput > to get a > result that does what you want. > > parseRest = do > rest <- getInput > setInput [] > return rest > > That should probably update the position as well though > it's not so > crucial in the likely use-cases of such a function. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] parsec manyTill stack overflow
On Fri, 2008-07-04 at 13:31 -0700, Badea Daniel wrote: > I'm trying to parse a large file looking for instructions on each line and > for a section end marker but Parsec's manyTill function causes stack > overflow, as you can see in the following example (I'm using ghci 6.8.3): > > > parse (many anyChar) "" ['a'|x<-[1..1024*64]] > > It almost immediately starts printing "aaa" and runs to > completion. > > > parse (manyTill anyChar eof) "" ['a'|x<-[1..1024*1024]] > *** Exception: stack overflow > > I guess this happens because manyTill recursively accumulates output > from the first parser and returns only when it hits the 'end' parser. > Is it possible to write a version of 'manyTill' that works like 'many' > returning output from 'anyChar' as soon as it advances through the > list of tokens? No, manyTill doesn't know whether it is going to return anything at all until its second argument succeeds. I can make manyTill not stack overflow, but it will never immediately start returning results. For the particular case above you can use getInput and setInput to get a result that does what you want. parseRest = do rest <- getInput setInput [] return rest That should probably update the position as well though it's not so crucial in the likely use-cases of such a function. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] parsec manyTill stack overflow
On Fri, Jul 4, 2008 at 5:31 PM, Badea Daniel <[EMAIL PROTECTED]> wrote: >> parse (manyTill anyChar eof) "" ['a'|x<-[1..1024*1024]] > *** Exception: stack overflow The usual solution applies: move the data from the stack to the heap. Try using manyTill' act end = go [] where go acc = choice [end >> return (reverse acc) ,act >>= \x -> go (x:acc)] -- Felipe. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] parsec manyTill stack overflow
I'm trying to parse a large file looking for instructions on each line and for a section end marker but Parsec's manyTill function causes stack overflow, as you can see in the following example (I'm using ghci 6.8.3): > parse (many anyChar) "" ['a'|x<-[1..1024*64]] It almost immediately starts printing "aaa" and runs to completion. > parse (manyTill anyChar eof) "" ['a'|x<-[1..1024*1024]] *** Exception: stack overflow I guess this happens because manyTill recursively accumulates output from the first parser and returns only when it hits the 'end' parser. Is it possible to write a version of 'manyTill' that works like 'many' returning output from 'anyChar' as soon as it advances through the list of tokens? Thanks, Daniel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Santana on my evil ways
My son's nickname is Rama, so let me adopt it. I am a functional programmer, even when I use languages such as C. Scheme facilitated my development into a functional programmer, however, I appreciate the benefits of pure function programming at times. Yet when I use Haskell, I hear reminders of my Scheme past cast in the music of Santana. The words I hear are set to "Eval Ways": You've got to change your evil ways... Rama Before I stop respecting you. You've got to change... Rama And every word that I say, it's true. You use strange syntax and typing And offset rules You don't mutate locations You use strange do's This can't go on... Lord knows you got to change. John ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Haskell on ARM (was Re: ANN: Topkata)
Don Stewart wrote: Could we start documenting this on the wiki ? It will be interesting to keep track of what we have tried, what attempts failed and why. -- Don I've added some new sections to the top of the wiki page, above the original attempts. It's now quite long, since it contains details of the problems I encountered trying to build an unregisterised 6.9.20080614 as a first experiment. It ultimately failed because hc-file bootstrapping to a new platform has been broken since 6.8. Only platforms with an existing GHC prior to 6.8 have 6.8 or later now, because of this. A bug[1] has been up since mid-2007 detailing the problem. There's a self-proclaimed "quick hack" diff[2], posted with the following comment: > The diff I uploaded contains some comments inline. It's for ghc-6.8.2 > but also applies to the latest stable snapshot (ghc-6.8.2.20080401). > > As written earlier, it's possible to create a HC file bundle (with > some additional created files) and to build a stage1 compiler with > this. I'm a little bit uncertain how to proceed -- either go ahead > using libcompat (which is a little bit ugly), or try to rebuild all > the libraries immediately with that stage1 compiler (but without using > utils/ghc-pkg, since it's not yet buildable), then build the remaining > tools. The bug is milestoned for 6.10.1, and the owner, Ian Lynagh (Igloo), said on #haskell that 6.10.1 merely meant "soon". So, assuming some GHC dev doesn't swoop down and fix this, what options are left to the project in the short term? An unregisterised build of an old 6.6 should work, that would get us a working, though aging, GHC. Unfortunately a lot of the porting work to move from that first unregisterised build to a registerised one (even without native code-gen) wouldn't be transferable to a later 6.9 or 6.10, since 6.9 has moved from using the Evil Mangler to libffi. As to running GHC on a real ARM device, several steps beyond the first unregisterised build would have to be taken, regardless of GHC version: 1. Registerise it. Pre-6.9, this means porting parts of the Evil Mangler, for which there is a guide. Post-6.9, this is much easier. 2. Native code-gen. Registerised or not, a GHC without native code generation relies on a working gcc. That means a GHC for ARM without NCG would only allow compilation of apps in the development environment, though the binaries should work on the device. 3. Finally, even GHC with native code-gen seems to rely on ld and maybe a few other binutils, but this is much, much lighter than installing all of gcc. So, moving forward I intend to run an unregisterised 6.6 build, just to prove that it can be done. Where we go from there is up in the air. I'd be inclined at that point to wait for 6.10 if #1346 really gets fixed. Fully porting an old version seems like extra work that will hopefully be obsoleted. Comments here or on the wiki page are most welcome, I'll be documenting the quirks and changes for the second attempt with 6.6 there too. And if someone in the GHC know wants to work #1346, they would be my hero. Braden Shepherdson shepheb [1] http://hackage.haskell.org/trac/ghc/ticket/1346 [2] http://hackage.haskell.org/trac/ghc/attachment/ticket/1346/ghc.diff ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] The state of database libraries
2008/7/4 Chris Eidhof <[EMAIL PROTECTED]>: > > I'm figuring out how to do databases in Haskell (on OS X). So far, I've tried > the following approaches: > > 1. hdbc. I'd like to connect to MySQL, so I need the ODBC backend. I couldn't > get this to work under OS X, while I installed myodbc, which seems to be > broken. > > 2. hsql. The packages on hackage don't compile, so I grabbed the darcs > version. Bummer, dude. The only database library that directly supports MySQL is HSQL. If you want to use another library, you'll have to get the ODBC MySQL backend working. Alistair ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] The state of database libraries
Hey everyone, I'm figuring out how to do databases in Haskell (on OS X). So far, I've tried the following approaches: 1. hdbc. I'd like to connect to MySQL, so I need the ODBC backend. I couldn't get this to work under OS X, while I installed myodbc, which seems to be broken. 2. hsql. The packages on hackage don't compile, so I grabbed the darcs version. hqsl itself installed perfectly, but when I try to compile hsql-mysql, it does not recognize that hsql is already installed and tries to recompile. Compiling fails, so I generated a .tar.gz of hsql using cabal sdist, put it in the .cabal/packages directory in the right place, and finally, it does compile. Now hsql-mysql starts compiling, but it finally fails with: MySQL.hsc:270:0: error: ‘MYSQL_NO_DATA’ undeclared (first use in this function) MySQL.hsc:270:0: error: (Each undeclared identifier is reported only once MySQL.hsc:270:0: error: for each function it appears in.) So what is the state of hsql? And haskelldb? Are they actively maintained? Thanks, -chris___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Question about abstraction
combineWith :: b -> (b -> a -> b) -> a -> a -> a -> a -> b n `combineWith` f = \tl tr bl br -> n `f` tl `f` tr `f` bl `f` br instance Foldable T where foldMap f = foldT mempty $ \_ x -> f x `combineWith` mappend -- But 'traverse' won't typecheck: instance Traversable T where traverse f = foldT (pure L) $ \p x -> (N p <$> f x) `combineWith` (<*>) -- Is it possible to make 'combineWith' more general so that the -- previous typechecks (maybe using arbitrary-rank polymorphism but I -- don't see how)? Looks tempting, doesn't it?-) But while the code is the same, the types needed for the two uses are rather different (and the inferred type not the most general one): combineWith ::b ->(b -> a -> b) -> (a -> a-> a-> a-> b) combineWith :: f (a->a->a->a->b) -> (forall a b . f (a->b) -> f a -> f b) -> (f a->f a->f a->f a->f b) We can shorten them a bit: type Four a b = a -> a -> a -> a -> b combineWith :: b ->(b -> a -> b) -> Four a b combineWith :: f (Four a b) -> (forall a b . f (a->b) -> f a -> f b) -> Four (f a) (f b) and we can add a dummy constructor to make them more similar: newtype Id a = Id{unId::a} combineWith :: f b -> ( f b -> f a -> f b) -> Four (f a) (f b) -- f ~ Id combineWith :: f (Four a b) -> (forall a b . f (a->b) -> f a -> f b) -> Four (f a) (f b) which leaves us with the crux of the matter: the function parameters and their uses are completely different: four independent applications of mappend vs four accumulating applications of (<*>). We still can make the simple case look like the complex case, by moving the mappend to the first parameter, but whether that is helpful is another question: combineWith :: f (Four a b) -> (forall a b . f (a->b) -> f a -> f b) -> Four (f a) (f b) n `combineWith` f = \tl tr bl br -> n `f` tl `f` tr `f` bl `f` br four f a b c d e = f (f (f (f a b) c) d) e instance Foldable T where foldMap f = unId . foldT (Id mempty) (\_ x -> Id (four mappend $ f x) `combineWith` (\(Id a) (Id b)->Id (a b))) instance Traversable T where traverse f = foldT (pure L) $ \p x -> (N p <$> f x) `combineWith` (<*>) Slightly more interesting is that foldMap should be an application of traverse (see Traversable documentation, and its source, for foldMapDefault). Hth, Claus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Question concerning datatype "Either"
2008/7/4 phy51km4n <[EMAIL PROTECTED]>: > > There is a exercise using datatype "Either" I'm a bit confused about... > > The following datatypes are given: > > data Either a b = Left a >| Right b > > data Tuple a b c d = One a > | Two a b > | Three a b c > | Four a b c d > > Now the exercise: > > "Based on our definition of Tuple, write a function which takes a Tuple and > returns either the value > (if it's a one-tuple), a Haskell-pair (i.e., ('a',5)) if it's a two-tuple, a > Haskell-triple > if it's a three-tuple or a Haskell-quadruple if it's a four-tuple. You will > need to > use the Either type to represent this." > > Why does that not work? : > > fromTuple (One a) = a > fromTuple (Two a b) = (a, b) > fromTuple (Three a b c) = (a, b, c) > fromTuple (Four a b c d) = (a, b, c, d) The first line tells: fromTuple :: Tuple a b c d -> a The second line tells: fromTuple :: Tuple a b c d -> (a, b) The third line tells: fromTuple :: Tuple a b c d -> (a, b, c) The fourth line tells: fromTuple :: Tuple a b c d -> (a, b, c, d) There is no way you can unify the return types of these four lines (Well, the compiler must have told you something similar). That was the obvious part. > Why is this correct? : > > fromTuple (One a ) = Left (Left a) > fromTuple (Two a b )= Left (Right (a,b)) > fromTuple (Three a b c ) = Right (Left (a,b,c)) > fromTuple (Four a b c d) = Right (Right (a,b,c,d)) > > Why does this combination of Rights and Lefts work and how does it work?? OK, first, let's simplify things a bit: data Stuple a b = Sone a | Stwo (a, b) fromStuple :: Stuple a b -> Either a (a, b) fromStuple (Sone a) = Left a fromStuple (Stwo (a, b)) = Right (a, b) According to the definition of Either, I can perfectly retrun different types for left and right. (That was the whole point of the Either type.) In your more complicated case, you can see you are using four combination of Left and Rights. The type of your function is (tell me if your compiler says otherwise): Tuple a b c d -> Either (Either a (a, b)) (Either (a, b, c) (a, b, c, d)) Ouch. Either is parametrized by two types: the one used in Left, and the one used in Right. If your are using Either types as left an right, it is possible to parametrize each of them by two types totalazing four types. Let me rewrite the return type above so you can read its tree structure more easily: Either (Either a (a, b)) (Either (a, b, c) (a, b, c, d)) Here, this should be obvious: while an Either type can hold two types, this nested one can hold four types. Hope this helps. Loup ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Alternatives to convoluted record syntax
Hi, busNum n | (isBusId n) = $(modify 'query) ($(set 'queryBusNumber) (Just n)) | otherwise = id The solution I am using is creating for each record type @Rec@, and each of its fields @fieldName :: T@ an updater updateFieldName :: (T -> T) -> Rec -> Rec This way you can write busNum n | (isBusId n) = updateQuery $ updateQueryBusNumber $ const (Just n) | otherwise = id The task of creating updaters can be automated using TH, this is what the attached library does: all you need is to say $(genUpdaters ''Opts) $(genUpdaters ''Query) Cheers, Misha RecordUpdate.tar.gz Description: GNU Zip compressed data ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] Question concerning datatype "Either"
> From: [EMAIL PROTECTED] > [mailto:[EMAIL PROTECTED] On Behalf Of phy51km4n > > Why does that not work? : > > fromTuple (One a) = a > fromTuple (Two a b) = (a, b) > fromTuple (Three a b c) = (a, b, c) > fromTuple (Four a b c d) = (a, b, c, d) Have you tried it? What are the types of the various cases in fromTuple (you can rename them to get ghci to accept them as separate functions): fromTuple1 :: Tuple a b c d -> a fromTuple1 (One a) = a fromTuple2 :: Tuple a b c d -> ??? fromTuple2 (Two a b) = (a, b) > Why is this correct? : > > fromTuple (One a ) = Left (Left a) > fromTuple (Two a b )= Left (Right (a,b)) > fromTuple (Three a b c ) = Right (Left (a,b,c)) > fromTuple (Four a b c d) = Right (Right (a,b,c,d)) Again, what is the type of just this line? fromTuple (One a ) = Left (Left a) and this line? fromTuple (Two a b )= Left (Right (a,b)) And if you combine them? fromTuple :: Tuple a b c d -> ??? fromTuple (One a ) = Left (Left a) fromTuple (Two a b )= Left (Right (a,b)) (You should see that Either's type parameters are progressively filled-in as you add more cases.) Alistair * Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. * ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Question concerning datatype "Either"
There is a exercise using datatype "Either" I'm a bit confused about... The following datatypes are given: data Either a b = Left a | Right b data Tuple a b c d = One a | Two a b | Three a b c | Four a b c d Now the exercise: "Based on our definition of Tuple, write a function which takes a Tuple and returns either the value (if it’s a one-tuple), a Haskell-pair (i.e., (’a’,5)) if it’s a two-tuple, a Haskell-triple if it’s a three-tuple or a Haskell-quadruple if it’s a four-tuple. You will need to use the Either type to represent this." Why does that not work? : fromTuple (One a) = a fromTuple (Two a b) = (a, b) fromTuple (Three a b c) = (a, b, c) fromTuple (Four a b c d) = (a, b, c, d) Why is this correct? : fromTuple (One a ) = Left (Left a) fromTuple (Two a b )= Left (Right (a,b)) fromTuple (Three a b c ) = Right (Left (a,b,c)) fromTuple (Four a b c d) = Right (Right (a,b,c,d)) Why does this combination of Rights and Lefts work and how does it work?? -- View this message in context: http://www.nabble.com/Question-concerning-datatype-%22Either%22-tp18264739p18264739.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Type families versus functional dependencies question
On Fri, Jul 4, 2008 at 5:03 AM, Manuel M T Chakravarty <[EMAIL PROTECTED]> wrote: > The problem is that blah's type is ambiguous, as f does only occur as an > argument to the type family. If you'd define > > class Blah f a where >blah :: a -> f -> T f f a > > (and change the rest of the program accordingly) then all will be fine. > See this thread for a more in-depth discussion of the problem: > > http://www.haskell.org/pipermail/haskell-cafe/2008-April/041385.html > Yes, I was afraid that this was the case. However, the question remains on whether my functional dependencies encoding is correct. A correct encoding would help me understand this typing problem a bit more. Especially, now that Claus showed that adding an equality constraint makes this program work! Cheers, Alexey ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Type families versus functional dependenciesquestion
On Thu, Jul 3, 2008 at 10:14 PM, Claus Reinke <[EMAIL PROTECTED]> wrote: > actually, GHC gives me "could not deduce Blah f a from Blah f1 a" >>> first. It seems that desugaring type function notation into an additional >>> constraint helps, so there's something odd going on: >>> >> >> Silly me, I didn't paste the whole type error. Yes, GHC gives both. I >> should >> add that I tested this under GHC 6.8.2. But this is known not to work >> with a >> (one/two months old) GHC head. >> > > yes, I tested with 6.9.20080514. And just in case my phrasing > was unclear: desugaring the type function application makes the > error go away, so you have a workaround. Thanks for highlighting this. Indeed I missed it, and it makes my example work. Cheers, Alexey > > > It is just confusing that this example shows that the "desugaring" > is not a desugaring, in the current implementation.. > > Claus > > > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: ANN: Gtk2Hs 0.9.13 released
Peter Gavin wrote: Gtk2Hs version 0.9.13 is now available. [1] New features: * bindings for Gnome VFS and GStreamer Is this bindings for the new GIO/GVFS stuff? Is Gtk2Hs cabal-ised? -- Ashley ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Integer = infinite precision integer? How?
On Thu, 3 Jul 2008, leledumbo wrote: Does anyone have an explanation how Haskell implement this? Or a pointer to a article describing this? Just a nitpick: Integers can have an arbitrary but only a finite number of digits. In contrast to that reals have infinitely many digits after the decimal point. There are Cantor's proofs that the set of natural numbers and the set of rational numbers have the same cardinality, whereas the set of reals has larger cardinality. Students often fail to understand that, if they are not aware that integers can only have finitely many digits. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe