Re: Wanted: warning option for usages of unary minus
Okay, first steps: 1. A Trac ticket (#1318, http://hackage.haskell.org/trac/ghc/ticket/1318) (is "feature request" a good category, versus "task"?) 2. A test-case to make sure I don't break anything with existing '-' syntax. I'm guessing it should go in testsuite/tests/ghc-regress/parser/should_run/, although maybe since it checks Haskell-98 compatibility it should go in the testsuite/tests/h98 directory? (tested ghc and hugs, which both pass) Isaac (test-case attached in case anyone wants to look at or review it; I'll send a darcs patch adding the testcase once I know where to put it) -- !!! Haskell-98 prefix negate operator -- Make sure the parsing is actually the correct -- one by running this after it's compiled. negatedExpression = - (3 + 4) negatedTightlyBinding = -3^4 negatedNonSection = (- 3) negatedNonSectionWithHighPrecedenceOp = let { f = (+); infix 9 `f` } in ( -3 `f` 4 ) negatedNonSectionWithLowPrecedenceOp = let { f = (+); infix 1 `f` } in ( -3 `f` 4 ) negatedRightHandSide = -- This is actually not legal syntax: 3 * - 4 -- However, lower-precedence binary ops work. -- (see H98 syntax for exp, or imagine it's because it -- would parse differently as 3 * 0 - 4) let { f = (+); infix 1 `f` } in ( 3 `f` - 4 ) subtractionNotNegation = 3 -4 negativePattern = case -3 of { (- 3) -> case -4 of { - 4 -> True } } -- not legal H98 syntax: case -4 of { _x @ -4 -> -- (parentheses needed)case -5 of { ~ -5 -> subtractionNotNegationPattern = -- defines infix '-' (shadowing Prelude definition) let { 3 -4 = True } in (3 - 4) precedenceOfNegationCantBeChanged = let { (-) = undefined; infix 9 - } in (- 3 * 4) negationCantBeQualified = (Prelude.-3) 4 main = do print negatedExpression print negatedTightlyBinding print negatedNonSection print negatedNonSectionWithHighPrecedenceOp print negatedNonSectionWithLowPrecedenceOp print negatedRightHandSide print subtractionNotNegation print negativePattern print subtractionNotNegationPattern print precedenceOfNegationCantBeChanged print negationCantBeQualified ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
Re: Error compiling GHC/Num.lhs
On 4/29/07, Ian Lynagh <[EMAIL PROTECTED]> wrote: Hi Bas, On Sun, Apr 29, 2007 at 11:54:35AM +, Bas van Dijk wrote: > > I'm trying to build GHC from darcs. Unfortunately compilation fails > with the following error: > > ... > cpphs: #error Please define LEFTMOST_BIT to be 2^(SIZEOF_HSWORD*8-1) > in GHC/Num.lhs at line 27 col 1 > make[1]: *** [doc.library.base] Error 1 > make[1]: Leaving directory `/home/bas/development/haskell/ghc/libraries' > make: *** [stage1] Error 2 > ... > > The following is the part where the error occurs in > libraries/base/GHC/Num.lhs : > ... > #include "MachDeps.h" > #if SIZEOF_HSWORD == 4 This is a cpphs bug - IIRC it wasn't recursively expanding SIZEOF_HSWORD. Either install cpphs from darcs (I don't think there is a release with the fix yet) or uninstall it so that cpp is used instead. Thanks Ian After uninstalling cpphs the error no longer occurs, thanks! However the build now crashes when running Haddock on Cabal: ... ifBuildable/ifBuildable Cabal setup/Setup haddock Preprocessing library Cabal-1.1.7... Running Haddock for Cabal-1.1.7... Warning: cannot use package base-2.1: ghc-pkg failed dist/build/tmp/Distribution/PreProcess.hs:"Distribution/PreProcess.hs": 115:1: parse error in doc string: [TokSpecial '/',TokString "build",TokSpecial '"'] make[1]: *** [doc.library.Cabal] Error 1 make[1]: Leaving directory `/home/bas/development/haskell/ghc/libraries' make: *** [stage1] Error 2 The respected code from libraries/Cabal/Distribution/PreProcess.hs (line 115 and onwards a bit): data PreProcessor = PreProcessor { -- Is the output of the pre-processor platform independent? eg happy output -- is portable haskell but c2hs's output is platform dependent. -- This matters since only platform independent generated code can be -- inlcuded into a source tarball. platformIndependent :: Bool, -- TODO: deal with pre-processors that have implementaion dependent output -- eg alex and happy have --ghc flags. However we can't really inlcude -- ghc-specific code into supposedly portable source tarballs. runPreProcessor :: (FilePath, FilePath) -- Location of the source file relative to a base dir -> (FilePath, FilePath) -- Output file name, relative to an output base dir -> Int -- verbosity -> IO ()-- Should exit if the preprocessor fails } Do I maybe need a newer Haddock for this? Currently I have version 0.8. Installing darcs version right now... Thanks, Bas van Dijk ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
Re: More speed please!
I'm replying to a rather old thread here, about unboxing in functions. Duncan had a continuation monad which passed around some data type that would be nice to unbox. You discussed strictness annotations in function types as a potential solution. I have a different tack on the problem which seems potentially useful. I've experimented with doing local defunctionalization on the module. This is a long mail as I will try to explain in some detail what it is that I have done. Please be patient. Normal defunctionalization is about replacing the primitive function type "a -> b" with an algebraic data type which I'll call "Fun a b". Not all functions will be eliminated as we will see but the program will be first order after the transformation. The core of the transformation is that every lambda in the program gives rise to a new constructor in the Fun data type and whenever we apply a function we instead call a newly created "apply function" with the following type "Fun a b -> a -> b". This is basically what JHC does. Defunctionalization is normally a whole program transformation (which is why JHC is a whole program compiler). But sometimes it can be done on a per module basis. This is where *local* defunctionalization comes in. The key to local defunctionalization is that we often can divide the data type Fun into several disjoint data types. We can do this whenever there are several different function spaces that never get mixed up. And sometimes we're even so lucky that a function space is totally contained in one module. Then we can do local defunctionalization of that particular function space only and completely within that module without changing it's interface. This case often comes up when using the continuation monad and Duncan's code is not an exception. So, I've manually done local defunctionalization on Duncan's code. It gives rise to two types which I've called Fun1 and Fun2. They look like follows (including the Put monad): \begin{code} newtype Put a = Put { runPut :: Fun2 a } data Fun1 a where Bind :: (a -> Put b) -> Fun1 b -> Fun1 a Then :: Put b -> Fun1 b -> Fun1 a Run :: Fun1 () FlushOld :: !(Fun1 ()) -> !Int -> !(ForeignPtr Word8) -> !Int -> !Int -> Fun1 () data Fun2 a where Return :: a -> Fun2 a Bind2 :: Put a -> (a -> Put b) -> Fun2 b Then2 :: Put a -> Put b -> Fun2 b Flush :: Fun2 () Write :: !Int -> (Ptr Word8 -> IO ()) -> Fun2 () \end{code} Intuitively every constructor corresponds to a closure. I've chosen the name for the constructor based on which function the closure appears in. The respective apply functions for these data types acts as interpreters and executes the corresponding code for each constructor/closure. Their type look as follow: \begin{code} apply1 :: Fun1 a -> a -> Buffer -> [B.ByteString] apply2 :: Fun2 a -> Fun1 a -> Buffer -> [B.ByteString] \end{code} Now, the cool thing is that once GHC starts optimizing away on these apply functions they will be unboxed and no Buffer will ever be created or passed around. Here is the core type for apply1: \begin{core} $wapply1_r21p :: forall a_aQu. PutMonad.Fun1 a_aQu -> a_aQu -> GHC.Prim.Addr# -> GHC.ForeignPtr.ForeignPtrContents -> GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# -> [Data.ByteString.Base.ByteString] \end{core} This is exactly what Duncan wanted, right? I declare victory :-) However, things are not all roses. There are some functions that will not be unboxed as we hope for with this approach, for instance the function flushOld (see Duncan's code). To achieve the best possible optimization I think one would have to perform strictness analysis and the worker-wrapper transformation twice, once before doing local defunctionalization and then again on the apply functions generated by the defunctionalization process. This should give the code that Duncan wants I believe. I think it should be relatively straightforward to implement local defunctionalization in GHC but it should not be turned on by default as the number of modules where it is beneficial is rather few. The complete defunctionalized version of Duncan's module is attached. I'm sure there are a lot of things that are somewhat unclear in this message. Feel free to ask and I'll do my best to clarify. Cheers, Josef {-# OPTIONS -fglasgow-exts -fbang-patterns -cpp #-} module PutMonad ( -- * The Put type Put , run -- :: Put () -> L.ByteString -- * Flushing the implicit parse state , flush -- :: Put () -- * Primitives , write -- :: Int -> (Ptr Word8 -> IO ()) -> Put () , word8 -- :: Word8 -> Put () ) where import Foreign import qualified Data.ByteString.Base as B ( ByteString(PS), LazyByteString(LPS), inlinePerformIO, mallocByteString, nullForeignPtr) import qualified Data.ByteString.
RE: recent Windows installer for ghc head?
Following the "snapshot distribution" link on GHC's download page yields this http://www.haskell.org/ghc/dist/current/dist/ghc-6.7.20070404-i386-unknown-mingw32.tar.bz2 That seems to be a tar bundle for Windows; it's not an msi but if you unpack it you should be able to run it just fine. Simon From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Conal Elliott Sent: 27 April 2007 20:03 To: glasgow-haskell-users@haskell.org Subject: recent Windows installer for ghc head? I'd like to try out the new & improved combination of type classes and GADTs, which I understand is only in head. Is there a recent working windows installer for head? Thanks, - Conal ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
Re: ghc configure
Mainly this is due to modularity: many of the library packages can be built entirely separately from GHC, so their configure scripts are designed to be standalone. library packages are haskell packages, and much of the configuration data should be common (plus a few package-specific checks). would it be possible to have a "configuration package" with nothing but the common checks? then every package, and ghc itself, could depend on that package being there, and every package configure could modularly use the information from that package. such a package might also encode the information in haskell, for use in cabal? perhaps creating such common info should be a cabal feature, factoring common checks from the package configure files to cabal, which would need access to some shared configuration file to store and retrieve the info? that way, once you've got cabal built on a platform, there'd be no need to repeat the common suspects of tests in individual configure files? just thinking out loud,-) claus ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
Re: ghc configure
Hi Simon, > Mainly this is due to modularity: many of the library packages can be built > entirely separately from GHC, so their configure scripts are designed to be > standalone. > Yes, I guess it would be a fair bit of work to have it check that you are building the whole of GHC as opposed to separate modules. I just thought that it could check to see if it was a global build -- and share configure checks where appropriate; or, in separate module builds the configure runs as normally. > I know that configure takes a long time on Windows, but I'm surprised if it's > a > bottleneck for other platforms. How long does the build take? Have you taken > steps to speed up the build as described in the Building Guide? Configuring and building on my Mac can take several hours. Mind you, it's a slow machine (G4 1.33 with 1 gig of RAM). I can safely say it's very fast on my linux machine - the configure whips through, and even a full build only takes a little more than an hour or so. Thanks for pointing out tips to speed up the build. I must confess my ignorance of not checking that! Kind regards, Chris. ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
Re: ghc configure
C.M.Brown wrote: I've noticed that when you run ./configure on a ghc build lot's of repetition occurs. A lot of the time the same checks are being performed for each configure file in the ghc hierarchy. Could it be possible if some of these checks could be done once at a high level and then subsequent configures could refer to these checks to speed up configuration time? It's just configuring ghc on a mac G4 is a very time consuming process in it's own right! Mainly this is due to modularity: many of the library packages can be built entirely separately from GHC, so their configure scripts are designed to be standalone. I know that configure takes a long time on Windows, but I'm surprised if it's a bottleneck for other platforms. How long does the build take? Have you taken steps to speed up the build as described in the Building Guide? Cheers, Simon ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users