X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=docs%2Fusers_guide%2Fglasgow_exts.xml;h=7e88a4f480133935d212503deb2c85329827b0ba;hb=e33f8e0de301e7138d2fc9287acbf2e890e727ed;hp=f6879febecf3a1c4e660caf00235c09af0871bc1;hpb=b7078f351d72f77b0a2b5d1fdf6e050ea0bfef61;p=ghc-hetmet.git diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index f6879fe..7e88a4f 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -351,6 +351,15 @@ Indeed, the bindings can even be recursive. Name + + + :: @@ -399,6 +408,52 @@ Indeed, the bindings can even be recursive. MIDLINE HORIZONTAL ELLIPSIS + + + + -< + + 0x2919 + LEFTWARDS ARROW-TAIL + + + + + + >- + + 0x291A + RIGHTWARDS ARROW-TAIL + + + + + + -<< + + 0x291B + LEFTWARDS DOUBLE ARROW-TAIL + + + + + + >>- + + 0x291C + RIGHTWARDS DOUBLE ARROW-TAIL + + + + + + * + + 0x2605 + BLACK STAR + + + @@ -871,8 +926,6 @@ the do-notation. The flag provides the necessary synta Here is a simple (albeit contrived) example: {-# LANGUAGE DoRec #-} -import Control.Monad.Fix - justOnes = do { rec { xs <- Just (1:xs) } ; return (map negate xs) } @@ -883,9 +936,9 @@ The background and motivation for recusrive do-notation is described in A recursive do for Haskell, by Levent Erkok, John Launchbury, Haskell Workshop 2002, pages: 29-37. Pittsburgh, Pennsylvania. -This paper is essential reading for anyone making non-trivial use of mdo-notation, -and we do not repeat it here. However, note that GHC uses a different syntax than the one -in the paper. +The theory behind monadic value recursion is explained further in Erkok's thesis +Value Recursion in Monadic Computations. +However, note that GHC uses a different syntax than the one described in these documents. @@ -913,30 +966,54 @@ while rec is monadic. (In Haskell let is really letrec, of course.) -The Control.Monad.Fix library introduces the MonadFix class. Its definition is: - +The static and dynamic semantics of rec can be described as follows: + + +First, +similar to let-bindings, the rec is broken into +minimal recursive groups, a process known as segmentation. +For example: -class Monad m => MonadFix m where - mfix :: (a -> m a) -> m a +rec { a <- getChar ===> a <- getChar + ; b <- f a c rec { b <- f a c + ; c <- f b a ; c <- f b a } + ; putChar c } putChar c - -The function mfix -dictates how the required recursion operation should be performed. For example, -justOnes desugars as follows: +The details of segmentation are described in Section 3.2 of +A recursive do for Haskell. +Segmentation improves polymorphism, reduces the size of the recursive "knot", and, as the paper +describes, also has a semantic effect (unless the monad satisfies the right-shrinking law). + + +Then each resulting rec is desugared, using a call to Control.Monad.Fix.mfix. +For example, the rec group in the preceding example is desugared like this: -justOnes = do { xs <- mfix (\xs' -> do { xs <- Just (1:xs'); return xs }) - ; return (map negate xs) } +rec { b <- f a c ===> (b,c) <- mfix (\~(b,c) -> do { b <- f a c + ; c <- f b a } ; c <- f b a + ; return (b,c) }) In general, the statment rec ss is desugared to the statement - vs <- mfix (\~vs -> do { ss; return vs }) +vs <- mfix (\~vs -> do { ss; return vs }) where vs is a tuple of the variables bound by ss. -Moreover, the original rec typechecks exactly -when the above desugared version would do so. (For example, this means that + +The original rec typechecks exactly +when the above desugared version would do so. For example, this means that the variables vs are all monomorphic in the statements -following the rec, because they are bound by a lambda.) +following the rec, because they are bound by a lambda. + + +The mfix function is defined in the MonadFix +class, in Control.Monad.Fix, thus: + +class Monad m => MonadFix m where + mfix :: (a -> m a) -> m a + + + + Here are some other important points in using the recursive-do notation: @@ -958,18 +1035,13 @@ for Haskell's internal state monad (strict and lazy, respectively). -Unlike ordinary do-notation, but like let and where bindings, -name shadowing is not allowed; that is, all the names bound in a single mdo must +Like let and where bindings, +name shadowing is not allowed within a rec; +that is, all the names bound in a single rec must be distinct (Section 3.3 of the paper). - -Similar to let-bindings, GHC implements the segmentation technique described in Section 3.2 of -A recursive do for Haskell, -to break up a single rec statement into a sequence of statements with -rec groups of minimal size. This -improves polymorphism, reduces the size of the recursive "knot", and, as the paper -describes, also has a semantic effect (unless the monad satisfies the right-shrinking law). +It supports rebindable syntax (see ). @@ -977,9 +1049,9 @@ describes, also has a semantic effect (unless the monad satisfies the right-shri Mdo-notation (deprecated) - GHC used to support the flag , + GHC used to support the flag , which enabled the keyword mdo, precisely as described in -A recursive do for Haskell, +A recursive do for Haskell, but this is now deprecated. Instead of mdo { Q; e }, write do { rec Q; e }. @@ -3933,6 +4005,51 @@ of the instance declaration, thus: (You need to do this.) +Warning: overlapping instances must be used with care. They +can give rise to incoherence (ie different instance choices are made +in different parts of the program) even without . Consider: + +{-# LANGUAGE OverlappingInstances #-} +module Help where + + class MyShow a where + myshow :: a -> String + + instance MyShow a => MyShow [a] where + myshow xs = concatMap myshow xs + + showHelp :: MyShow a => [a] -> String + showHelp xs = myshow xs + +{-# LANGUAGE FlexibleInstances, OverlappingInstances #-} +module Main where + import Help + + data T = MkT + + instance MyShow T where + myshow x = "Used generic instance" + + instance MyShow [T] where + myshow xs = "Used more specific instance" + + main = do { print (myshow [MkT]); print (showHelp [MkT]) } + +In function showHelp GHC sees no overlapping +instances, and so uses the MyShow [a] instance +without complaint. In the call to myshow in main, +GHC resolves the MyShow [T] constraint using the overlapping +instance declaration in module Main. As a result, +the program prints + + "Used more specific instance" + "Used generic instance" + +(An alternative possible behaviour, not currently implemented, +would be to reject module Help +on the grounds that a later instance declaration might overlap the local one.) + + The willingness to be overlapped or incoherent is a property of the instance declaration itself, controlled by the presence or otherwise of the @@ -5667,6 +5784,9 @@ for rank-2 types. Impredicative polymorphism +NOTE: the impredicative-polymorphism feature is deprecated in GHC 6.12, and +will be removed or replaced in GHC 6.14. + GHC supports impredicative polymorphism, enabled with . This means @@ -7521,6 +7641,14 @@ itself, so an INLINE pragma is always ignored. portable). + + CONLIKE modifier + CONLIKE + An INLINE or NOINLINE pragma may have a CONLIKE modifier, + which affects matching in RULEs (only). See . + + + Phase control @@ -8156,18 +8284,24 @@ not be substituted, and the rule would not fire. - + + + + + + + +How rules interact with INLINE/NOINLINE and CONLIKE pragmas Ordinary inlining happens at the same time as rule rewriting, which may lead to unexpected results. Consider this (artificial) example f x = x -{-# RULES "f" f True = False #-} - g y = f y - h z = g True + +{-# RULES "f" f True = False #-} Since f's right-hand side is small, it is inlined into g, to give @@ -8181,14 +8315,37 @@ would have been a better chance that f's RULE might fire. The way to get predictable behaviour is to use a NOINLINE -pragma on f, to ensure +pragma, or an INLINE[phase] pragma, on f, to ensure that it is not inlined until its RULEs have had a chance to fire. - - - + +GHC is very cautious about duplicating work. For example, consider + +f k z xs = let xs = build g + in ...(foldr k z xs)...sum xs... +{-# RULES "foldr/build" forall k z g. foldr k z (build g) = g k z #-} + +Since xs is used twice, GHC does not fire the foldr/build rule. Rightly +so, because it might take a lot of work to compute xs, which would be +duplicated if the rule fired. + + +Sometimes, however, this approach is over-cautious, and we do want the +rule to fire, even though doing so would duplicate redex. There is no way that GHC can work out +when this is a good idea, so we provide the CONLIKE pragma to declare it, thus: + +{-# INLINE[1] CONLIKE f #-} +f x = blah + +CONLIKE is a modifier to an INLINE or NOINLINE pragam. It specifies that an application +of f to one argument (in general, the number of arguments to the left of the '=' sign) +should be considered cheap enough to duplicate, if such a duplication would make rule +fire. (The name "CONLIKE" is short for "constructor-like", because constructors certainly +have such a property.) +The CONLIKE pragam is a modifier to INLINE/NOINLINE because it really only makes sense to match +f on the LHS of a rule if you are sure that f is +not going to be inlined before the rule has a chance to fire. - @@ -8460,15 +8617,22 @@ comparison. Use to see what transformation rules GHC is using. - + Use to see what rules are being fired. If you add you get a more detailed listing. + + + Use to see in great detail what rules are being fired. +If you add you get a still more detailed listing. + + + The definition of (say) build in GHC/Base.lhs looks like this: