Wed Sep 27 20:36:27 EDT 2006  Samuel Bronson <[EMAIL PROTECTED]>
  * Haddockify ByteCode.CompileLib module
New patches:

[Haddockify ByteCode.CompileLib module
Samuel Bronson <[EMAIL PROTECTED]>**20060928003627] {
hunk ./src/compiler98/ByteCode/CompileLib.hs 1
-module ByteCode.CompileLib where
+module ByteCode.CompileLib 
+    (
+     -- *State and types 
+     CTable, State(..), initCompileState, STCompiler, InsCode, Compiler, CMode(..), 
+     cStrict, cLazy, cTraced, cUntraced,
+     Where(..),
+     shiftWhere,
+
+     -- *Monadic plumbing
+     -- $monadic_plumbing
+     (=>>=), (=>>), mapC, mapC_, simply, lift, block,
+
+     -- *State manipulation functions
+     shiftStack, getFlags, getDepth, setDepth, bindArgs, bind, whereIs, addConst,
+     isEvaled, newLabel, newLabels, branch, mergeDepths, pushFail, popFail, getFail,
+     getIntState     
+    ) where
hunk ./src/compiler98/ByteCode/CompileLib.hs 34
--- the internal compiler state
+-- | The internal compiler state
+-- @
hunk ./src/compiler98/ByteCode/CompileLib.hs 41
+-- @
hunk ./src/compiler98/ByteCode/CompileLib.hs 43
+-- @
hunk ./src/compiler98/ByteCode/CompileLib.hs 48
+-- @
hunk ./src/compiler98/ByteCode/CompileLib.hs 82
-{- compiler mode information -}
+{- | compiler mode information -}
hunk ./src/compiler98/ByteCode/CompileLib.hs 93
-{- where we can find a variable -}
+{- | where we can find a variable -}
hunk ./src/compiler98/ByteCode/CompileLib.hs 98
-{- shift a where by an offset, if it's on the stack -}
+{- | shift a where by an offset, if it's on the stack -}
hunk ./src/compiler98/ByteCode/CompileLib.hs 103
---------------------------------------------------------------
--- monadic plumbing
+
+-- $monadic_plumbing
hunk ./src/compiler98/ByteCode/CompileLib.hs 113
--- p =>> q
+-- > p =>> q
hunk ./src/compiler98/ByteCode/CompileLib.hs 118
--- p =>>= \ x -> q
+-- > p =>>= \ x -> q
hunk ./src/compiler98/ByteCode/CompileLib.hs 125
---   newLabel =>>= \ j ->
---   ins (JUMP j)
+--
+-- > newLabel =>>= \ j ->
+-- > ins (JUMP j)
hunk ./src/compiler98/ByteCode/CompileLib.hs 131
---------------------------------------------------------------
hunk ./src/compiler98/ByteCode/CompileLib.hs 163
-{- shift the stack by the given amount, also offsets the stack stored variables in
+{- | shift the stack by the given amount, also offsets the stack stored variables in
hunk ./src/compiler98/ByteCode/CompileLib.hs 172
-{- get the flags -}
+{- | get the flags -}
hunk ./src/compiler98/ByteCode/CompileLib.hs 176
-{- get the current depth -}
+{- | get the current depth -}
hunk ./src/compiler98/ByteCode/CompileLib.hs 180
-{- set the current depth -}
+{- | set the current depth -}
hunk ./src/compiler98/ByteCode/CompileLib.hs 184
-{- bind the argument list -}
+{- | bind the argument list -}
hunk ./src/compiler98/ByteCode/CompileLib.hs 191
-{- bind an identifier to a stack location -}
+{- | bind an identifier to a stack location -}
hunk ./src/compiler98/ByteCode/CompileLib.hs 195
-{- find out where an identifier is stored -}
+{- | find out where an identifier is stored -}
hunk ./src/compiler98/ByteCode/CompileLib.hs 199
-{- add a const to the consttable, if it's not there already -}
+{- | add a const to the consttable, if it's not there already -}
hunk ./src/compiler98/ByteCode/CompileLib.hs 209
-{- find out whether a variable has been evaluated already -}
+{- | find out whether a variable has been evaluated already -}
hunk ./src/compiler98/ByteCode/CompileLib.hs 213
-{- mark that a variable has been evaluated -}
+{- | mark that a variable has been evaluated -}
hunk ./src/compiler98/ByteCode/CompileLib.hs 217
-{- allocate a new compiler label and return it -}
+{- | allocate a new compiler label and return it -}
hunk ./src/compiler98/ByteCode/CompileLib.hs 222
-{- allocate some new labels -}
+{- | allocate some new labels -}
hunk ./src/compiler98/ByteCode/CompileLib.hs 227
--- take a compiler and compile it in its own environment,
+-- | take a compiler and compile it in its own environment,
hunk ./src/compiler98/ByteCode/CompileLib.hs 242
--- merge together a list of depths taken from branching, checks they are all the same
+-- | merge together a list of depths taken from branching, checks they are all the same
hunk ./src/compiler98/ByteCode/CompileLib.hs 249
--- push a fail on the fail stack
+-- | push a fail on the fail stack
hunk ./src/compiler98/ByteCode/CompileLib.hs 255
--- pop a fail from the fail stack
+-- | pop a fail from the fail stack
hunk ./src/compiler98/ByteCode/CompileLib.hs 260
--- get the failure on the fail of the stack
+-- | get the failure on the fail of the stack
hunk ./src/compiler98/ByteCode/CompileLib.hs 264
--- get the internal state
+-- | get the internal state
}

Context:

[Fix bug 42
Andrew Wilkinson <[EMAIL PROTECTED]>**20060927105351] 
[Clean documentation. Remove Windows-isms from Samuel Bronson's patch.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060927095103] 
[scons doc -- now with working!
Samuel Bronson <[EMAIL PROTECTED]>**20060927014733] 
[Support for building most of the haddock docs with scons
Samuel Bronson <[EMAIL PROTECTED]>**20060927014204] 
[Make vsnprintf available from platform.h, make the last windows fix a bit cleaner
Neil Mitchell**20060926112812] 
[Define vsnprintf on Windows, where only the _ variant exists
Neil Mitchell**20060926111154] 
[Fix the indentation in protectEsc, otherwise its a bad pattern match error (spotted by Catch)
Neil Mitchell**20060926105755] 
[Added YHC_BASE_PATH guessing for windows ...
Tom Shackell <[EMAIL PROTECTED]>**20060925153440] 
[yhi now guesses YHC_BASE_PATH where possible
Tom Shackell <[EMAIL PROTECTED]>**20060925153150] 
[Look in a special location for libgmp, specially for Greg.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060925141402] 
[Minor corrections to release build. Add optimisations to Windows build.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060925134027] 
[If YHC_BASE_PATH is not set, default to looking for yhc on the PATH, and then hop around from there
Neil Mitchell**20060925130913] 
[Change debug=1 flag to type=debug. Add type=release.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060925114000] 
[Give better type information - CoreItem is now CoreFunc and CoreData, CoreLet now has a more accurate type (breaks binary compatability, again...)
Neil Mitchell**20060920132218] 
[Change the Show instance for Core, now export Show for each of the constructors, not just Core
Neil Mitchell**20060920130130] 
[Add coreFunc to the Core API
Neil Mitchell**20060919175519] 
[Another dependency for Ix.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060919171058] 
[Add dependency for Data.Ix.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060919165550] 
[Add a Play instance for Core, and initial Play infrastructure
Neil Mitchell**20060919164102] 
[Change the CoreFunc format, to lift the name and arguments up explicitly - much more sensible! (breaks compatability with all external Core tools - but they are all mine)
Neil Mitchell**20060919161741] 
[Delete the Read/Show instances for Core, people should use the binary stuff instead
Neil Mitchell**20060919153827] 
[Make Core.Core purely generate Core from PosLambda, and the showing/saving to Compile
Neil Mitchell**20060919153344] 
[Add a binary read/write for Core
Neil Mitchell**20060919143956] 
[Move Core.Pretty to Yhc.Core.Show
Neil Mitchell**20060919142031] 
[Move dropModule from Pretty to Yhc.Core.Type
Neil Mitchell**20060919141644] 
[Move to Yhc.Core, just move the data structure for now
Neil Mitchell**20060919141044] 
[Remove Core.Reduce, wasn't a very good idea, and wasn't used, and wouldn't build
Neil Mitchell**20060919140321] 
[Add dependency for Ix on Data.Ratio.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060919082731] 
[Copy bootstrap files to the compilation directory rather than installation.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060918190915] 
[Minor tweak
Tom Shackell <[EMAIL PROTECTED]>**20060918183056] 
[Added YHC.Dynamic support :-)
Tom Shackell <[EMAIL PROTECTED]>**20060918182436] 
[Added mod_load as part of the Runtime.API (how did I forget that one?)
Tom Shackell <[EMAIL PROTECTED]>**20060918102314] 
[If checking of type sizes failed delete the cache.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060915110303] 
[Don't check for svn if we don't need it.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060914152928] 
[Allow the user to skip pulling a copy of ctypes by passing skipctypes=1 on the command line. They must provide their own copy if this is going to work.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060914152640] 
[Allow commandline options to be stored in a file (options.txt)
Andrew Wilkinson <[EMAIL PROTECTED]>**20060914151911] 
[None isn't a valid value, use 0 instead.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060914145032] 
[Change failed configure results to None to disable caching.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060914142841] 
[Add proper pragma support into Yhc, delete it from Scons
Neil Mitchell**20060914135504] 
[Split into processArgs and processMoreArgs, to allow OPTIONS pragma to add more parse information
Neil Mitchell**20060914130423] 
[Remove some redundant code
Neil Mitchell**20060914130035] 
[Added anna,fluid & prolog to tests
Tom Shackell <[EMAIL PROTECTED]>**20060914132309] 
[Add a special core option for Neil. Type scons core=1 to activate.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060914112103] 
[Allow the user to override the detected architecture.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060914110551] 
[Recalculate dependencies if file modification time has changed.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060914105015] 
[Only rebuild files if the .hi files they depend on change. Fixes bug #20.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060914104411] 
[Added '-h 40M' flags to paraffins so it works on x64
Tom Shackell <[EMAIL PROTECTED]>**20060913180359] 
[Improved the pic and removed the gamteb test
Tom Shackell <[EMAIL PROTECTED]>**20060913175829] 
[Use absolute YHC_BASE_PATH
Andrew Wilkinson <[EMAIL PROTECTED]>**20060913164718] 
[os.getcwd() doesn't end in a slash.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060913162706] 
[Fixed the x2n1 bug 
Tom Shackell <[EMAIL PROTECTED]>**20060913155320
 
 The problem was actually a serious issue with regard to the NEEDHEAP analysis. 
 I'd forgotten that the amount of heap used by an APPLY instruction is not fixed 
 until runtime - and thus every APPLY needs to be followed by a NEED_HEAP 
 (providing no memory was allocated). The solution was simply to do that, have the
 memory analysis phase introduce NEED_HEAP instructions after APPLY. The most common
 case of
 
    APPLY ...
    EVAL
 
 still requires no NEED_HEAP (which is correctly determined and removed automatically).
 
 Tom
 
] 
[Use absolute path for YHC_BASE_PATH
Andrew Wilkinson <[EMAIL PROTECTED]>**20060913155844] 
[Fix up the test script, assuming that YHC_BASE_PATH is always absolute
Neil Mitchell**20060913154258] 
[If the extension is .lhs, then always give the -unlit flag
Neil Mitchell**20060913150026] 
[Move the Flags and FileFlags structures into FrontData, where they (hopefully) belong
Neil Mitchell**20060913143135] 
[Move the Flags data into the FileFlags information, so each file can have different flags
Neil Mitchell**20060913135506] 
[Incorporated nofib tests into the testsuite, modified yhi and tester to do so.
Tom Shackell <[EMAIL PROTECTED]>**20060913120540] 
[Fix the Core output so its all with the right name, for Catch
Neil Mitchell**20060911211822] 
[Add Eq instances for Core, entirely unneeded for Yhc, but makes Catch a bit easier ;)
Neil Mitchell**20060911175447] 
[Make tuples desugar to the same thing everywhere (rather than just the use, not the definition!)
Neil Mitchell**20060911172801] 
[Remove empty WheelSieve2 directory, since that test is now in the testsuite
Neil Mitchell**20060911144752] 
[Move wheelsieve into the tests, in a manner guaranteed to invoke GC
Neil Mitchell**20060911144617] 
[Take less prime numbers, but still enough to ensure GC happens
Neil Mitchell**20060911144159] 
[Delete nqueens, is in the test directory as Queens
Neil Mitchell**20060911143951] 
[Delete unneeded makefiles in the test directory
Neil Mitchell**20060911143840] 
[Remove test/Lit.lhs, has now been moved to parsing/literate
Neil Mitchell**20060911143407] 
[Wheelsieve fix (oops)
Tom Shackell <[EMAIL PROTECTED]>**20060911140815] 
[Wheelsieve fix
Tom Shackell <[EMAIL PROTECTED]>**20060911140656] 
[Make the initial file depend on both its .hi and .hbc file
Neil Mitchell**20060911140036] 
[Check if the initial file is dirty or not, make recompilations really quick
Neil Mitchell**20060911133438] 
[Add CoreDouble and CoreFloat, to encode floating point numbers in the Core
Neil Mitchell**20060911125853] 
[Make lam2core cope with primitives and foreign function calls (which are treated as though they were primitive)
Neil Mitchell**20060911124513] 
[Dump the -corep information to a file with the extension .ycr
Neil Mitchell**20060911111539] 
[Don't link to libdl on FreeBSD
Andrew Wilkinson <[EMAIL PROTECTED]>**20060907151046] 
[Fix an incompatability introduced by ctypes, by making ctypes depend on python
Neil Mitchell**20060907145727] 
[Detect when the C compiler doesn't work. And don't require one if we're only building yhc.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060817142541] 
[Pass entire environment to GHC. Avoids 'HOME: getEnv: does not exist (no environment variable)' message from GHC.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060815155119] 
[Back out change which made Char signed as it's not on Linux PPC.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060815151658] 
[Don't make assumptions about char.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060815124721] 
[Remove libffi that was in the source code directory
Neil Mitchell**20060815134849] 
[Mark packed string as expected to fail
Neil Mitchell**20060815134351] 
[Add expected failure concept to tester, so that buildbot reports success
Neil Mitchell**20060815134320] 
[Make the tests be executed in the same order regardless of the order the file system finds them in
Neil Mitchell**20060815130142] 
[Remove build warnings from yhi.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060815110046] 
[Force types to be signed. Should fix bug on ppc linux where char is unsigned by default.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060814105637] 
[Don't check /usr/local on Windows
Andrew Wilkinson <[EMAIL PROTECTED]>**20060814100019] 
[Add libffi build rule for MacOS X on x86
Andrew Wilkinson <[EMAIL PROTECTED]>**20060814083001] 
[Link against libraries on non Darwin operating systems on PPC
Andrew Wilkinson <[EMAIL PROTECTED]>**20060810111259] 
[Fix copy and paste error.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060810084957] 
[Add support for linux on ppc.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060809105016] 
[Actually make my last two patches work.
Andrew Wilkinson <[EMAIL PROTECTED]>**20060809093638] 
[Check /usr/local for headers and library files
Andrew Wilkinson <[EMAIL PROTECTED]>**20060808133931] 
[Fall back to Python if uname -o fails
Andrew Wilkinson <[EMAIL PROTECTED]>**20060808133902] 
[TAG 03_AUG_2006
Neil Mitchell**20060803135817] 
Patch bundle hash:
861badf1f20dc4075286a836e31d4b0abc6b9c0c
_______________________________________________
Yhc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/yhc

Reply via email to