Wed Sep 27 20:36:27 EDT 2006 Samuel Bronson <[EMAIL PROTECTED]>
* Haddockify ByteCode.CompileLib module
Thu Sep 28 07:33:09 EDT 2006 Samuel Bronson <[EMAIL PROTECTED]>
* Fix export list for ByteCode.CompileLib
Thu Sep 28 07:44:45 EDT 2006 Samuel Bronson <[EMAIL PROTECTED]>
* Oops, messed up the docstring for ByteString.CompileLib.State
Thu Sep 28 15:49:35 EDT 2006 Samuel Bronson <[EMAIL PROTECTED]>
* Complain about missing type sigs (haddock needs them)
Thu Sep 28 15:52:07 EDT 2006 Samuel Bronson <[EMAIL PROTECTED]>
* Comment on wierd type synonym in CaseLib
Thu Sep 28 15:52:57 EDT 2006 Samuel Bronson <[EMAIL PROTECTED]>
* Add typesigs to CaseOpt module
Thu Sep 28 15:53:37 EDT 2006 Samuel Bronson <[EMAIL PROTECTED]>
* Add typesigs to Prim module
Thu Sep 28 18:14:08 EDT 2006 Samuel Bronson <[EMAIL PROTECTED]>
* Haddockify NT module
Thu Sep 28 18:16:43 EDT 2006 Samuel Bronson <[EMAIL PROTECTED]>
* Haddockify PosCode module
Thu Sep 28 18:17:58 EDT 2006 Samuel Bronson <[EMAIL PROTECTED]>
* Add signature to SysDep module
Thu Sep 28 18:21:01 EDT 2006 Samuel Bronson <[EMAIL PROTECTED]>
* Haddockify Util.Extra (mostly signatures)
Thu Sep 28 18:25:48 EDT 2006 Samuel Bronson <[EMAIL PROTECTED]>
* Haddockify TokenId
Thu Sep 28 18:26:40 EDT 2006 Samuel Bronson <[EMAIL PROTECTED]>
* Oops, missed some stuff in Util.Extra
I had accidentally recorded it along with the TokenId stuff...
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
}
[Fix export list for ByteCode.CompileLib
Samuel Bronson <[EMAIL PROTECTED]>**20060928113309] {
hunk ./src/compiler98/ByteCode/CompileLib.hs 5
- cStrict, cLazy, cTraced, cUntraced,
+ cStrict, cLazy, cTraced, cUntraced, cUnproject,
hunk ./src/compiler98/ByteCode/CompileLib.hs 15
- isEvaled, newLabel, newLabels, branch, mergeDepths, pushFail, popFail, getFail,
- getIntState
+ isEvaled, evaled, newLabel, newLabels, branch, mergeDepths, pushFail, popFail,
+ getFail, getIntState
hunk ./src/compiler98/ByteCode/CompileLib.hs 85
-cStrict, cLazy, cTraced, cUntraced :: CMode -> CMode
+cStrict, cLazy, cTraced, cUntraced, cUnproject :: CMode -> CMode
}
[Oops, messed up the docstring for ByteString.CompileLib.State
Samuel Bronson <[EMAIL PROTECTED]>**20060928114445] {
hunk ./src/compiler98/ByteCode/CompileLib.hs 35
+--
}
[Complain about missing type sigs (haddock needs them)
Samuel Bronson <[EMAIL PROTECTED]>**20060928194935] {
hunk ./Sconstruct 17
+hsenv.Append(HSFLAGS=["-fwarn-missing-signatures"])
}
[Comment on wierd type synonym in CaseLib
Samuel Bronson <[EMAIL PROTECTED]>**20060928195207] {
hunk ./src/compiler98/CaseLib.hs 15
+-- | This enigmatic type has slightly-less enigmatic comments attached to its use in 'Case.caseTopLevel'
}
[Add typesigs to CaseOpt module
Samuel Bronson <[EMAIL PROTECTED]>**20060928195257] {
hunk ./src/compiler98/CaseOpt.hs 10
+import Id
hunk ./src/compiler98/CaseOpt.hs 12
+optFatBar :: PosExp -> PosExp -> State0 d (IntState, b) (PosExp, (IntState, b))
hunk ./src/compiler98/CaseOpt.hs 21
+failExp :: PosExp -> d -> (IntState, b) -> (Bool, (IntState, b))
hunk ./src/compiler98/CaseOpt.hs 33
+failAlt :: PosAlt -> d -> (IntState, b) -> (Bool, (IntState, b))
hunk ./src/compiler98/CaseOpt.hs 37
+anyMissing :: [PosAlt] -> t -> (IntState, b) -> (Bool, (IntState, b))
hunk ./src/compiler98/CaseOpt.hs 50
+singleVars :: Exp Id -> t -> (IntState, b) -> (Maybe [Maybe (Pos, Id)], (IntState, b))
hunk ./src/compiler98/CaseOpt.hs 61
+getPosI :: Exp id -> Maybe (Pos, id)
}
[Add typesigs to Prim module
Samuel Bronson <[EMAIL PROTECTED]>**20060928195337] {
hunk ./src/compiler98/Prim.hs 47
+strPrim :: Prim -> String
hunk ./src/compiler98/Prim.hs 84
+strPrimOp :: String -> PrimOp -> String
}
[Haddockify NT module
Samuel Bronson <[EMAIL PROTECTED]>**20060928221408] {
hunk ./src/compiler98/NT.hs 1
+-- | Warning: there are a bunch of comments on the positional fields
+-- of constructors in this module (perhaps the constructors should be
+-- record constructors so that they can have docstrings on their
+-- fields?)
+
hunk ./src/compiler98/NT.hs 21
--- Perhaps NewType is a type schema? It quantifies variables over
--- an arrow of NTs.
+-- | Perhaps @NewType@ is a type schema? It quantifies variables over
+-- an arrow of 'NT's.
hunk ./src/compiler98/NT.hs 36
-data NT = NTany Id -- can be instantiated with unboxed
+data NT = NTany Id -- ^ can be instantiated with unboxed
hunk ./src/compiler98/NT.hs 42
- | NTcons Id Kind [NT] -- combines constructor + application
- | NTcontext Id Id -- context (class, type variable)
+ | NTcons Id Kind [NT] -- ^ combines constructor + application
+ | NTcontext Id Id -- ^ context (class, type variable)
hunk ./src/compiler98/NT.hs 47
+mkNTvar, mkNTexist :: Id -> NT
hunk ./src/compiler98/NT.hs 51
+mkNTcons :: Id -> [NT] -> NT
hunk ./src/compiler98/NT.hs 55
+kindNT :: NT -> Kind
hunk ./src/compiler98/NT.hs 63
+stripNT :: NT -> Id
hunk ./src/compiler98/NT.hs 70
+strictNT :: NT -> Bool
hunk ./src/compiler98/NT.hs 74
+ntContext2Pair :: NT -> (Id, Id)
hunk ./src/compiler98/NT.hs 77
+contextNT :: NT -> Bool
hunk ./src/compiler98/NT.hs 82
-{- Determine the type constructors that occur in the given type -}
+{- | Determine the type constructors that occur in the given type -}
hunk ./src/compiler98/NT.hs 93
-{-
+{- |
hunk ./src/compiler98/NT.hs 95
-used only in module Export
+used only in module 'Export'
hunk ./src/compiler98/NT.hs 108
-{- Determine type variables that occur in given type. -}
+{- | Determine type variables that occur in given type. -}
hunk ./src/compiler98/NT.hs 119
-{-
+{- |
hunk ./src/compiler98/NT.hs 133
+anyNT :: [Id] -> NT -> NT
hunk ./src/compiler98/NT.hs 141
+polyNT :: [Id] -> NT -> NT
hunk ./src/compiler98/NT.hs 149
+-- | FIXME: Isn't this type a tad more general than appropriate for the name?
+transCtxs :: (a -> b) -> (c -> d) -> [(c, a)] -> [(d, b)]
hunk ./src/compiler98/NT.hs 155
-{- Show function for NT, parameterised by show functions for
-constructors/class names and for type variables.
+{- | Show function for 'NT', parameterised by show functions for
+constructors\/class names and for type variables.
hunk ./src/compiler98/NT.hs 172
+strTVar :: Id -> String
hunk ./src/compiler98/NT.hs 184
+strTVs :: [Id] -> String
}
[Haddockify PosCode module
Samuel Bronson <[EMAIL PROTECTED]>**20060928221643] {
hunk ./src/compiler98/PosCode.hs 25
+posExpApp :: Pos -> [PosExp] -> PosExp
hunk ./src/compiler98/PosCode.hs 29
+posExpLet :: Pos -> [PosBinding] -> PosExp -> PosExp
hunk ./src/compiler98/PosCode.hs 34
- = PosExpDict PosExp -- hack to mark dictionaries
- | PosExpLet Bool Pos [PosBinding] PosExp -- True for recursive lets, false otherwise
+ = PosExpDict PosExp -- ^ Hack to mark dictionaries
+ | PosExpLet Bool Pos [PosBinding] PosExp -- ^ True for recursive lets, false otherwise
hunk ./src/compiler98/PosCode.hs 38
- | PosExpThunk Pos Bool [PosExp] -- True if this is really 'apply'
- | PosExpFatBar Bool PosExp PosExp -- True if fail can escape fatbar
+ | PosExpThunk Pos Bool [PosExp] -- ^ True if this is really \'apply\'
+ | PosExpFatBar Bool PosExp PosExp -- ^ True if fail can escape fatbar
hunk ./src/compiler98/PosCode.hs 41
- | PosExpIf Pos Bool PosExp PosExp PosExp -- True if this is really a guard
+ | PosExpIf Pos Bool PosExp PosExp PosExp -- ^ True if this is really a guard
hunk ./src/compiler98/PosCode.hs 51
- -- Only temporary !!
+ -- Only temporary !! [which?!? -- SamB]
hunk ./src/compiler98/PosCode.hs 58
- = PosAltCon Pos Int [(Pos,Int)] PosExp -- Constructor numbers, new variables, expression
- | PosAltInt Pos Int Bool PosExp -- Is the Int an Integer{True} or a Char{False}
+ = PosAltCon Pos Int [(Pos,Int)] PosExp -- ^ Constructor numbers, new variables, expression
+ | PosAltInt Pos Int Bool PosExp -- ^ Is the Int an Integer{True} or a Char{False}
hunk ./src/compiler98/PosCode.hs 61
+isPosAtom :: PosExp -> Bool
hunk ./src/compiler98/PosCode.hs 103
+mapPosExp_Binding :: PlayPosExp b => (PosExp -> PosExp) -> (a, b) -> (a, b)
}
[Add signature to SysDep module
Samuel Bronson <[EMAIL PROTECTED]>**20060928221758] {
hunk ./src/compiler98/SysDeps.hs 10
+openBinaryFileWrite :: FilePath -> IO Handle
}
[Haddockify Util.Extra (mostly signatures)
Samuel Bronson <[EMAIL PROTECTED]>**20060928222101] {
hunk ./src/compiler98/Util/Extra.hs 72
+dropEither :: Either a a -> a
hunk ./src/compiler98/Util/Extra.hs 76
+mapPair :: (a -> b) -> (c -> d) -> (a, c) -> (b, d)
+mapFst :: (a -> b) -> (a, o) -> (b, o)
+mapSnd :: (a -> b) -> (o, a) -> (o, b)
hunk ./src/compiler98/Util/Extra.hs 83
+findLeft :: [Either e a] -> Either e [a]
hunk ./src/compiler98/Util/Extra.hs 91
+-- | Isn't this just @(\f -> findLeft . map f)@?
+eitherMap :: (a -> Either e b) -> [a] -> Either e [b]
hunk ./src/compiler98/Util/Extra.hs 112
+-- | Take a function and a list and return a list of spans in which
+-- the function returns the same value for each element.
+partitions :: Eq b => (a -> b) -> [a] -> [[a]]
hunk ./src/compiler98/Util/Extra.hs 126
+mix :: String -> [String] -> String
hunk ./src/compiler98/Util/Extra.hs 130
+mixSpace, mixComma, mixLine :: [String] -> String
hunk ./src/compiler98/Util/Extra.hs 135
+mixCommaAnd :: [String] -> String
hunk ./src/compiler98/Util/Extra.hs 155
--- abstract type for storing the position of a syntactic construct in a file,
+-- | abstract type for storing the position of a syntactic construct in a file,
hunk ./src/compiler98/Util/Extra.hs 166
--- used in STGcode to get encoded start position
+-- | used in STGcode to get encoded start position
hunk ./src/compiler98/Util/Extra.hs 174
--- create a virtual position out of a real one
+-- | create a virtual position out of a real one
hunk ./src/compiler98/Util/Extra.hs 182
--- combines positions by determining minimal one that covers both
+-- ^ combines positions by determining minimal one that covers both
hunk ./src/compiler98/Util/Extra.hs 192
--- merge a list of positions
+-- ^ merge a list of positions
hunk ./src/compiler98/Util/Extra.hs 245
--- splitIntegral :: (Integral a) => a -> SplitIntegral
+splitIntegral :: (Integral n) => n -> SplitIntegral
hunk ./src/compiler98/Util/Extra.hs 258
+emptySet :: Set a
hunk ./src/compiler98/Util/Extra.hs 261
+singletonSet :: a -> Set a
hunk ./src/compiler98/Util/Extra.hs 264
+listSet :: Eq a => [a] -> Set a
hunk ./src/compiler98/Util/Extra.hs 267
+unionSet :: Eq a => Set a -> Set a -> Set a
hunk ./src/compiler98/Util/Extra.hs 273
+removeSet :: Eq a => Set a -> Set a -> Set a
hunk ./src/compiler98/Util/Extra.hs 305
--- Given a list of filenames, return filename and its content of first file
+-- | Given a list of filenames, return filename and its content of first file
hunk ./src/compiler98/Util/Extra.hs 325
--- Test integers for their size bounds
+-- * Test integers for their size bounds
}
[Haddockify TokenId
Samuel Bronson <[EMAIL PROTECTED]>**20060928222548] {
hunk ./src/compiler98/TokenId.hs 1
-{- ---------------------------------------------------------------------------
+{- |
hunk ./src/compiler98/TokenId.hs 4
+
+You might as well just read the source if you want to know about
+those, they are *far* to numerous to document here.
hunk ./src/compiler98/TokenId.hs 14
+-- * 'TokenId' and functions
hunk ./src/compiler98/TokenId.hs 16
+visible :: String -> TokenId
hunk ./src/compiler98/TokenId.hs 18
+qualify :: String -> String -> TokenId
hunk ./src/compiler98/TokenId.hs 23
- TupleId Int -- no distinction between the type and the value constructor?
- | Visible PackedString -- unqualified name
+ TupleId Int -- ^ no distinction between the type and the value constructor?
+ | Visible PackedString -- ^ unqualified name
hunk ./src/compiler98/TokenId.hs 26
- -- token for qualified name: module name, variable name
+ -- ^ token for qualified name: module name, variable name
hunk ./src/compiler98/TokenId.hs 28
- -- token with: module name, class token, type token for a dictionary?
+ -- ^ token with: module name, class token, type token for a dictionary?
hunk ./src/compiler98/TokenId.hs 30
- -- token for method in instance: module name, class token, type token, method token
+ -- ^ token for method in instance: module name, class token, type token, method token
hunk ./src/compiler98/TokenId.hs 74
+notPrelude :: TokenId -> Bool
hunk ./src/compiler98/TokenId.hs 82
-{- construct Qualified2 token from given two tokens -}
+{- | construct Qualified2 token from given two tokens -}
hunk ./src/compiler98/TokenId.hs 87
-{- construct Qualified3 token from given three tokens -}
+{- | construct Qualified3 token from given three tokens -}
hunk ./src/compiler98/TokenId.hs 101
-{- if token is not qualified make it qualified with given module name -}
+{- | if token is not qualified make it qualified with given module name -}
hunk ./src/compiler98/TokenId.hs 107
-{- make token into qualified token with given module name -}
+{- | make token into qualified token with given module name -}
hunk ./src/compiler98/TokenId.hs 114
-{- drop all qualification (module names) from token -}
+{- | drop all qualification (module names) from token -}
hunk ./src/compiler98/TokenId.hs 121
-{- get module name from token, correct for Visible? -}
+{- | get module name from token, correct for Visible? -}
hunk ./src/compiler98/TokenId.hs 125
+extractM' :: TokenId -> Maybe PackedString
hunk ./src/compiler98/TokenId.hs 131
-{- split a token -}
+{- | split a token -}
hunk ./src/compiler98/TokenId.hs 143
+unpack :: PackedString -> String
hunk ./src/compiler98/TokenId.hs 146
-{- make an external token -}
+{- | make an external token -}
hunk ./src/compiler98/TokenId.hs 151
-{- get identifier name from token, without qualification -}
+{- | get identifier name from token, without qualification -}
hunk ./src/compiler98/TokenId.hs 160
-{- extend token by adding position to the identifier name -}
+{- | extend token by adding position to the identifier name -}
hunk ./src/compiler98/TokenId.hs 175
-{- append given string to module name of qualified token -}
+{- | append given string to module name of qualified token -}
hunk ./src/compiler98/TokenId.hs 180
+visImport, qualImpPrel, qualImpNHC, qualImpBin, qualImpRat, qualImpIx, qualImpFFI :: String -> TokenId
+qualImpPS, qualImpPrim, qualImpDyn :: String -> TokenId
hunk ./src/compiler98/TokenId.hs 193
+qualImpFFIBC :: String -> String -> TokenId
hunk ./src/compiler98/TokenId.hs 200
+rpsPrelude, rpsInternal, rpsRatio, rpsIx, rpsFFI, rpsPS, rpsBinary, rpsPrimitive, rpsYhcDynamic
+ :: PackedString
hunk ./src/compiler98/TokenId.hs 213
+isUnit :: TokenId -> Bool
hunk ./src/compiler98/TokenId.hs 218
-{- make token for tuple of given size -}
+{- | make token for tuple of given size -}
hunk ./src/compiler98/TokenId.hs 222
-
+-- * Hardcoded names
+tmain :: TokenId
hunk ./src/compiler98/TokenId.hs 226
+tPrelude, tNHCInternal, tYHCDynamic :: TokenId
hunk ./src/compiler98/TokenId.hs 231
+t_underscore, t_Bang, tprefix, tqualified, thiding, tas, tinterface, tforall, tdot :: TokenId
+tunboxed, tprimitive, tMain :: TokenId
hunk ./src/compiler98/TokenId.hs 246
+
+tUnknown :: Show a => a -> TokenId
hunk ./src/compiler98/TokenId.hs 250
+t_gtgteq, t_gtgt, tfail, t_error, t_undef, tfromInteger, tNum, tIntegral, tInt, tIntHash :: TokenId
+t_flip, tminus, tident, tnegate, tTrue, tFalse, tunknown, terror, tIO, tBool, tFloatHash :: TokenId
+tFloat, tChar, t_List :: TokenId
hunk ./src/compiler98/TokenId.hs 264
-
+t_Arrow, tString, t_filter, t_foldr, t_Colon, t_x, t_y, t_apply1 :: TokenId
+t_apply2, t_apply3, t_apply4, tInteger, tDouble, tDoubleHash, tfromRational, t_fromEnum :: TokenId
+t_toEnum, tEq, tOrd, tEnum, tIx, tShow, tRead, t_andand, t_pipepipe, tcompare, tLT, tEQ :: TokenId
+tGT, t_equalequal, t_lessequal, t_lessthan, t_greater, t_greaterequal :: TokenId
hunk ./src/compiler98/TokenId.hs 317
+tseq :: TokenId
hunk ./src/compiler98/TokenId.hs 320
+trange, tindex, tinRange, t_tupleRange, t_tupleIndex, t_enumRange, t_enumIndex, t_enumInRange :: TokenId
hunk ./src/compiler98/TokenId.hs 330
+tfromEnum, ttoEnum, tenumFrom, tenumFromTo, tenumFromThen, tenumFromThenTo :: TokenId
+t_enumFromTo, t_enumFromThenTo :: TokenId
hunk ./src/compiler98/TokenId.hs 341
+tBounded, tminBound, tmaxBound :: TokenId
hunk ./src/compiler98/TokenId.hs 346
+t_append, t_readCon0, t_readConInfix, t_readCon, t_readConArg, t_readField, t_readFinal :: TokenId
hunk ./src/compiler98/TokenId.hs 355
+tshowsPrec, tshowsType, treadsPrec, t_dot, tshowString, tshowChar, tshowParen, treadParen :: TokenId
+tFractional, tRational, tRatio, tRatioCon, tNEED, t_eqInteger, t_eqDouble, t_eqFloat :: TokenId
+t_otherwise :: TokenId
hunk ./src/compiler98/TokenId.hs 376
+t_id :: TokenId
hunk ./src/compiler98/TokenId.hs 381
-{- Malcolm's additions from here on -}
+{- * Malcolm's additions from here on -}
hunk ./src/compiler98/TokenId.hs 383
-{- class + instances of Binary -}
+{- ** class + instances of Binary -}
+tBinary, t_put, t_get, t_getF, t_sizeOf, t_putBits, t_getBits, t_getBitsF, t_ltlt, t_return, t_plus
+ :: TokenId
hunk ./src/compiler98/TokenId.hs 398
-{- (N+K) patterns -}
+{- ** (N+K) patterns -}
+t_nplusk, t_subtract :: TokenId
hunk ./src/compiler98/TokenId.hs 403
-{- FFI -}
+{- ** FFI -}
+t_foreign, t_export, t_ccall, t_stdcall, t_fastccall, t_faststdcall, t_haskell, t_noproto :: TokenId
+t_cplusplus, t_dotnet, t_jvm, t_cast, t_safe, t_unsafe, tAddr, tPtr, tFunPtr, tForeignObj :: TokenId
+tForeignPtr, tStablePtr, tInt8, tInt16, tInt32, tInt64, tWord8, tWord16, tWord32, tWord64 :: TokenId
+tPackedString :: TokenId
hunk ./src/compiler98/TokenId.hs 438
+tAddrBC, tPtrBC, tFunPtrBC, tForeignObjBC, tForeignPtrBC, tStablePtrBC :: TokenId
+tInt8BC, tInt16BC, tInt32BC, tInt64BC, tWord8BC, tWord16BC, tWord32BC, tWord64BC :: TokenId
hunk ./src/compiler98/TokenId.hs 457
+tunsafePerformIO :: TokenId
hunk ./src/compiler98/TokenId.hs 460
-{- more FFI -}
+{- ** more FFI -}
+t_mkIOok :: Int -> TokenId
hunk ./src/compiler98/TokenId.hs 464
-{- YHC.Dynamic -}
+{- ** YHC.Dynamic -}
+ttypeRep, tTyCon, tTyGeneric :: TokenId
hunk ./src/compiler98/TokenId.hs 470
+-- * Not hardcoded names
}
[Oops, missed some stuff in Util.Extra
Samuel Bronson <[EMAIL PROTECTED]>**20060928222640
I had accidentally recorded it along with the TokenId stuff...
] {
hunk ./src/compiler98/Util/Extra.hs 20
+fst3 :: (a, b, c) -> a
hunk ./src/compiler98/Util/Extra.hs 22
+snd3 :: (a, b, c) -> b
hunk ./src/compiler98/Util/Extra.hs 24
+thd3 :: (a, b, c) -> c
hunk ./src/compiler98/Util/Extra.hs 35
+foldls :: (a -> b -> a) -> a -> [b] -> a
hunk ./src/compiler98/Util/Extra.hs 48
+strace :: String -> a -> a
hunk ./src/compiler98/Util/Extra.hs 53
+warning :: String -> a -> a
hunk ./src/compiler98/Util/Extra.hs 57
+fstOf :: a -> b -> a
hunk ./src/compiler98/Util/Extra.hs 60
+safeTail :: [a] -> [a]
hunk ./src/compiler98/Util/Extra.hs 64
+snub :: Eq a => [a] -> [a]
hunk ./src/compiler98/Util/Extra.hs 68
+pair :: a -> b -> (a, b)
hunk ./src/compiler98/Util/Extra.hs 70
+triple :: a -> b -> c -> (a, b, c)
hunk ./src/compiler98/Util/Extra.hs 73
+isLeft :: Either a b -> Bool
hunk ./src/compiler98/Util/Extra.hs 77
+isRight :: Either a b -> Bool
hunk ./src/compiler98/Util/Extra.hs 81
+dropLeft :: Either a b -> a
hunk ./src/compiler98/Util/Extra.hs 84
+dropRight :: Either a b -> b
}
Context:
[Doc edits in Error module
Samuel Bronson <[EMAIL PROTECTED]>**20060927202801]
[Haddockify DotNet.IL module
Samuel Bronson <[EMAIL PROTECTED]>**20060927202706]
[Haddockify FixSyntax module
Samuel Bronson <[EMAIL PROTECTED]>**20060927195005]
[Haddockify Case module
Samuel Bronson <[EMAIL PROTECTED]>**20060927194709]
[Change haddock commandline in Sconstruct to match Makefile.bat
Samuel Bronson <[EMAIL PROTECTED]>**20060927192354]
[Haddockify Bind module.
Samuel Bronson <[EMAIL PROTECTED]>**20060927191828]
[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:
f14e2930d439b1dfc419f7ce895062b3cea250e3
_______________________________________________
Yhc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/yhc