summaryrefslogtreecommitdiff
path: root/ghc/lib/std/PrelHandle.lhs
Commit message (Collapse)AuthorAgeFilesLines
* [project @ 2001-05-18 16:54:04 by simonmar]simonmar2001-05-181-1292/+0
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | I/O library rewrite ------------------- This commit replaces the old C/Haskell I/O implementation with a new Haskell-only one using the new FFI & hsc2hs. main points: - lots of code deleted: we're about 3000 lines of C lighter, but the amount of Haskell code is about the same. - performance is ok: some operations are faster, others are slower. There's still some tuning to do, though. - the new library is designed to handle read/write streams much better: a read/write stream gets a special kind of handle internally called a "DuplexHandle", which actually contains two separate handles, one for writing and one for reading. The upshot is that you can do simultaneous reading and writing to/from a socket or FIFO without any locking problems. The effect is similar to calling socketToHandle twice, except that finalization works properly (creating two separate Handles could lead to the socket being closed too early when one of the Handles is GC'd). - hConnectTo and withHandleFor are gone (no one responded to my mail on GHC users, but we can always bring 'em back if necessary). - I made a half-hearted attempt at keeping the system-specific code in one place: see PrelPosix.hsc. - I've rearranged the I/O tests and added lots more. ghc/tests/lib/IO now contains Haskell 98-only IO tests, ghc/test/lib/{IOExts, Directory, Time} now contain tests for the relevant libraries. I haven't quite finished in here yet, the IO tests work but the others don't yet. - I haven't done anything about Unicode yet, but now we can start to discuss what needs doing here. The new library is using MutableByteArrays for its buffers because that turned out to be a *lot* easier (and quicker) than malloc'd buffers - I hope this won't cause trouble for unicode translations though. WARNING: Windows users refrain from updating until we've had a chance to fix any issues that arise. Testing: the basic H98 stuff has been pretty thoroughly tested, but the new duplex handle stuff is still a little green.
* [project @ 2001-02-22 13:17:57 by simonpj]simonpj2001-02-221-3/+3
| | | | | | | | | | | | | | fromInt Remove fromInt from class Num, though it is retained as an overloaded operation (with unchanged type) in PrelNum. There are quite a few consequential changes in the Prelude. I hope I got them all correct! Also fix a bug that meant Integer (and its instances) wasn't getting slurped in by the renamer, even though it was needed for defaulting.
* [project @ 2001-01-11 17:25:56 by simonmar]simonmar2001-01-111-40/+36
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Re-organisation of ghc/lib/std and hslibs/lang ---------------------------------------------- In brief: move deprecated features out of ghc/lib/std and into hslibs/lang, move new FFI libraries into ghc/lib/std and start using them. - foreign import may now return an unboxed type (this was advertised to work before, but in fact didn't). Subsequent cleanups in PrelInt/PrelWord. - Ptr is now defined in ghc/lib/std/PrelPtr.lhs. Ptr is no longer a newtype of Addr, it is defined directly in terms of Addr#. - PrelAddr has disappeared from ghc/lib/std, all uses of Addr in ghc/lib/std have been replaced with Ptr. The definitions of Addr has been moved to hslibs/lang/Addr.lhs, as has lots of other Addr-related stuff. - ForeignObj has been removed from ghc/lib/std, and replaced with ForeignPtr. The definition of ForeignObj has been moved to hslibs/lang/ForeignObj.lhs. - Most of the new FFI has been moved into ghc/lib/std in the form of modules PrelMarshalAlloc, PrelCString, PrelCError, PrelMarshalError, PrelMarshalArray, PrelMarshalUtils, PrelCTypes, PrelCTypesISO, and PrelStorable. The corresponding modules in hslibs/lang simply re-export the contents of these modules. - PrelPosixTypes defines a few POSIX types (CMode == mode_t, etc.) - PrelCError changed to access errno using foreign label and peek (the POSIX book I have says that errno is guaranteed to be an extern int, so this should be OK until I get around to making errno thread-safe). - Hacked the macros that generate the code for CTypes and CTypesISO to generate much less code (ghc/lib/std/cbits/CTypes.h). - RtsAPI is now a bit more honest when it comes to building heap objects (it uses the correct constructors). - the Bits class and related stuff has been moved to ghc/lib/std (it was simpler this way). - Directory and System have been converted to use the new FFI.
* [project @ 2001-01-11 07:04:16 by qrczak]qrczak2001-01-111-16/+15
| | | | Change the representation of IOException: add optional filename.
* [project @ 2001-01-10 16:28:15 by qrczak]qrczak2001-01-101-12/+15
| | | | | | | | | | | | | | | | Remove CError.throwCError. Export the new function errnoToIOError. Add a missing colon in a string inside IOException formed from the error-specific part and optional filename. The IOException representation has not changed yet, but IMHO the filename should be kept separate. Correctly handle user errors in IO.ioeGet* functions like other IO errors. Let fail :: String -> IO a throw a user error instead of invoking error (Haskell98 is ambiguous about that and IMHO it should be this way; this is also what nhc does).
* [project @ 2000-11-07 10:42:55 by simonmar]simonmar2000-11-071-35/+6
| | | | | merge before-ghci -> before-ghci-branch-merged into the ghc (non-compiler) parts of the tree.
* [project @ 2000-09-14 14:24:02 by simonmar]simonmar2000-09-141-4/+4
| | | | | | rename blockAsyncExceptions and unblockAsyncExceptions to block and unblock repectively, to match all the literature. DEPRECATE the old names.
* [project @ 2000-08-29 16:37:35 by simonpj]simonpj2000-08-291-7/+1
| | | | Remove redundant imports and dead code
* [project @ 2000-07-25 15:20:10 by simonmar]simonmar2000-07-251-2/+1
| | | | | | | | | | | | | | | | | Fix bug reported by Hannah Schroeter: reading a file lazily using hGetContents and then closing it using hClose can cause the program to fall over with a deadlock. The reason is that when closing the file in lazyRead{Block,Line,Char}, we set the foreign object in the handle to nullFile__, which causes the finalizer to run (at some point in the future). The finalizer takes the MVar in the handle, frees the contents, but never puts the MVar back. hClose then tries to take the MVar, and deadlocks. The solution is not to set the foreign object to nullFile__ in the first place; I'm not sure why it was done this way, and in fact it leads to a memory leak. hClose itself has a similar problem, leading to a leak of the fileObject.
* [project @ 2000-07-07 11:03:57 by simonmar]simonmar2000-07-071-35/+56
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | Rearrange exception stuff, as per my message on glasgow-haskell-users recently. The main change is the IOError type is now a synonym for Exception. IO.ioError can therefore be used for throwing exceptions. IO.catch still catches only IO exceptions, for backwards compatibility. The interface exported by Exception has changed somewhat: try :: IO a -> IO (Either Exception a) tryJust :: (Exception -> Maybe b) -> a -> IO (Either b a) catch :: IO a -> (Exception -> IO a) -> IO a catchJust :: (Exception -> Maybe b) -> IO a -> (b -> IO a) -> IO a ioErrors :: Exception -> Maybe IOError arithExceptions :: Exception -> Maybe ArithException errorCalls :: Exception -> Maybe String dynExceptions :: Exception -> Maybe Dynamic assertions :: Exception -> Maybe String asyncExceptions :: Exception -> Maybe AsyncException raiseInThread is now called throwTo. Where possible, the old functions have been left around, but marked deprecated.
* [project @ 2000-05-18 12:42:20 by simonmar]simonmar2000-05-181-2/+34
| | | | | | | New version of hGetLine that is roughly 4 times faster than the original, and is tail-recursive to boot. I'm not entirely happy with the code, but it needs to get some testing.
* [project @ 2000-05-01 14:53:47 by panne]panne2000-05-011-4/+5
| | | | | Adding a bunch of `unsafe's to foreign imports. TODO: Could somebody verify that declaring shutdownHaskellAndExit as unsafe is OK?
* [project @ 2000-04-14 15:28:24 by rrt]rrt2000-04-141-1/+1
| | | | Removed -fcompiling-prelude flag (now removed from compiler)
* [project @ 2000-04-14 12:49:39 by simonmar]simonmar2000-04-141-4/+9
| | | | Free the spare buffers immediately we hClose a file handle.
* [project @ 2000-04-12 17:33:16 by simonmar]simonmar2000-04-121-106/+85
| | | | | | | | | | | | | | | | | | | | | | | | This commit fixes the trace/stderr problem, and also fixes some other problems with the I/O library. - handles now contain a list of free buffers, which are guaranteed to be the same size as the primary handle buffer. - hPutStr now doesn't evaluate any part of the input string with the handle locked. Instead, it acquires a buffer from the handle copies characters into it, then commits the buffer. This is better for concurrency too, because the handle is only locked while we're actually reading/writing, not while evaluating. - there were an even number of off-by-one errors in the I/O system which compensated for each other. This has been fixed. - made the I/O subsystem a little more exception-safe. It still isn't totally exception-safe, but I can't face doing that without a complete rewrite of this thing in Haskell. - add hPutBufFull and hGetBufFull. The compiler probably needs to be updated to use these too.
* [project @ 2000-04-11 20:44:17 by panne]panne2000-04-111-11/+7
| | | | | | | | | | | | | | | | | | Cleaning up the foreign object naming mess: * Renamed the primop from makeForeignObj# to mkForeignObj#, this is more consistent with the old Foreign.mkForeignObj. * PrelForeign now exports makeForeignObj with the new signature. * freeFile.c now uses StgAddr instead of StgForeignObj, this removes the need for some fixIOs. * Lots of import tweaking to prepare The Big Foreign Renamer, which will move most of Foreign to ForeignObj, and FFI to Foreign. Note: I've tried to track the changes in the interpreter sources, but didn't test them.
* [project @ 2000-04-10 16:02:58 by simonpj]simonpj2000-04-101-1/+1
| | | | | | | | | | Make it so that -fcompiling-prelude applies only for Prelude modules (i.e. ones called Prelxxx). I've done this with an {-# OPTIONS #-} line in each such module (they all has -fno-implicit-prelude anyway) but a less repetitive approach in the Makefile would be welcome.
* [project @ 2000-04-10 12:12:27 by simonpj]simonpj2000-04-101-1/+1
| | | | | | | | | | | | | | | | | | | | Make it so that (A) All modules imported by Prelude are PrelXXX modules, not library modules (notably Ix, Monad were culprits). This lines up with the Hugs story, and is more intuitive. (B) All things needed implicitly by syntax (e.g. do-notation needs Monad) come from PrelXXX modules, even if they aren't visible when you say 'import Prelude'. These changes simplify the story, and fix the 'looking for [boot] interface for Ix' problem. This change is not quite complete. I'm committing it so Simon can finish it off.
* [project @ 2000-03-31 03:09:35 by hwloidl]hwloidl2000-03-311-20/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Numerous changes in the RTS to get GUM-4.06 working (currently works with parfib-ish programs). Most changes are isolated in the rts/parallel dir. rts/parallel/: The most important changes are a rewrite of the (un-)packing code (Pack.c) and changes in LAGA, GALA table operations (Global.c) expecially in rebuilding the tables during GC. rts/: Minor changes in Schedule.c, GC.c (interface to par specific root marking and evacuation), and lots of additions to Sanity.c (surprise ;-) Main.c change for startup: I use a new function rts_evalNothing to start non-main-PEs in a PAR || SMP setup (RtsAPI.c) includes/: Updated GranSim macros in PrimOps.h. lib/std: Few changes in PrelHandle.c etc replacing ForeignObj by Addr in a PAR setup (we still don't support ForeignObjs or WeakPtrs in GUM). Typically use #define FILE_OBJECT Addr when dealing with files. hslibs/lang/: Same as above (in Foreign(Obj).lhs, Weak.lhs, IOExts.lhs etc). -- HWL
* [project @ 2000-03-23 17:45:17 by simonpj]simonpj2000-03-231-1/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This utterly gigantic commit is what I've been up to in background mode in the last couple of months. Originally the main goal was to get rid of Con (staturated constant applications) in the CoreExpr type, but one thing led to another, and I kept postponing actually committing. Sorry. Simon, 23 March 2000 I've tested it pretty thoroughly, but doubtless things will break. Here are the highlights * Con is gone; the CoreExpr type is simpler * NoRepLits have gone * Better usage info in interface files => less recompilation * Result type signatures work * CCall primop is tidied up * Constant folding now done by Rules * Lots of hackery in the simplifier * Improvements in CPR and strictness analysis Many bug fixes including * Sergey's DoCon compiles OK; no loop in the strictness analyser * Volker Wysk's programs don't crash the CPR analyser I have not done much on measuring compilation times and binary sizes; they could have got worse. I think performance has got significantly better, though, in most cases. Removing the Con form of Core expressions ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The big thing is that For every constructor C there are now *two* Ids: C is the constructor's *wrapper*. It evaluates and unboxes arguments before calling $wC. It has a perfectly ordinary top-level defn in the module defining the data type. $wC is the constructor's *worker*. It is like a primop that simply allocates and builds the constructor value. Its arguments are the actual representation arguments of the constructor. Its type may be different to C, because: - useless dict args are dropped - strict args may be flattened For every primop P there is *one* Id, its (curried) Id Neither contructor worker Id nor the primop Id have a defminition anywhere. Instead they are saturated during the core-to-STG pass, and the code generator generates code for them directly. The STG language still has saturated primops and constructor applications. * The Const type disappears, along with Const.lhs. The literal part of Const.lhs reappears as Literal.lhs. Much tidying up in here, to bring all the range checking into this one module. * I got rid of NoRep literals entirely. They just seem to be too much trouble. * Because Con's don't exist any more, the funny C { args } syntax disappears from inteface files. Parsing ~~~~~~~ * Result type signatures now work f :: Int -> Int = \x -> x -- The Int->Int is the type of f g x y :: Int = x+y -- The Int is the type of the result of (g x y) Recompilation checking and make ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * The .hi file for a modules is not touched if it doesn't change. (It used to be touched regardless, forcing a chain of recompilations.) The penalty for this is that we record exported things just as if they were mentioned in the body of the module. And the penalty for that is that we may recompile a module when the only things that have changed are the things it is passing on without using. But it seems like a good trade. * -recomp is on by default Foreign declarations ~~~~~~~~~~~~~~~~~~~~ * If you say foreign export zoo :: Int -> IO Int then you get a C produre called 'zoo', not 'zzoo' as before. I've also added a check that complains if you export (or import) a C procedure whose name isn't legal C. Code generation and labels ~~~~~~~~~~~~~~~~~~~~~~~~~~ * Now that constructor workers and wrappers have distinct names, there's no need to have a Foo_static_closure and a Foo_closure for constructor Foo. I nuked the entire StaticClosure story. This has effects in some of the RTS headers (i.e. s/static_closure/closure/g) Rules, constant folding ~~~~~~~~~~~~~~~~~~~~~~~ * Constant folding becomes just another rewrite rule, attached to the Id for the PrimOp. To achieve this, there's a new form of Rule, a BuiltinRule (see CoreSyn.lhs). The prelude rules are in prelude/PrelRules.lhs, while simplCore/ConFold.lhs has gone. * Appending of constant strings now works, using fold/build fusion, plus the rewrite rule unpack "foo" c (unpack "baz" c n) = unpack "foobaz" c n Implemented in PrelRules.lhs * The CCall primop is tidied up quite a bit. There is now a data type CCall, defined in PrimOp, that packages up the info needed for a particular CCall. There is a new Id for each new ccall, with an big "occurrence name" {__ccall "foo" gc Int# -> Int#} In interface files, this is parsed as a single Id, which is what it is, really. Miscellaneous ~~~~~~~~~~~~~ * There were numerous places where the host compiler's minInt/maxInt was being used as the target machine's minInt/maxInt. I nuked all of these; everything is localised to inIntRange and inWordRange, in Literal.lhs * Desugaring record updates was broken: it didn't generate correct matches when used withe records with fancy unboxing etc. It now uses matchWrapper. * Significant tidying up in codeGen/SMRep.lhs * Add __word, __word64, __int64 terminals to signal the obvious types in interface files. Add the ability to print word values in hex into C code. * PrimOp.lhs is no longer part of a loop. Remove PrimOp.hi-boot* Types ~~~~~ * isProductTyCon no longer returns False for recursive products, nor for unboxed products; you have to test for these separately. There's no reason not to do CPR for recursive product types, for example. Ditto splitProductType_maybe. Simplification ~~~~~~~~~~~~~~~ * New -fno-case-of-case flag for the simplifier. We use this in the first run of the simplifier, where it helps to stop messing up expressions that the (subsequent) full laziness pass would otherwise find float out. It's much more effective than previous half-baked hacks in inlining. Actually, it turned out that there were three places in Simplify.lhs that needed to know use this flag. * Make the float-in pass push duplicatable bindings into the branches of a case expression, in the hope that we never have to allocate them. (see FloatIn.sepBindsByDropPoint) * Arrange that top-level bottoming Ids get a NOINLINE pragma This reduced gratuitous inlining of error messages. But arrange that such things still get w/w'd. * Arrange that a strict argument position is regarded as an 'interesting' context, so that if we see foldr k z (g x) then we'll be inclined to inline g; this can expose a build. * There was a missing case in CoreUtils.exprEtaExpandArity that meant we were missing some obvious cases for eta expansion Also improve the code when handling applications. * Make record selectors (identifiable by their IdFlavour) into "cheap" operations. [The change is a 2-liner in CoreUtils.exprIsCheap] This means that record selection may be inlined into function bodies, which greatly improves the arities of overloaded functions. * Make a cleaner job of inlining "lone variables". There was some distributed cunning, but I've centralised it all now in SimplUtils.analyseCont, which analyses the context of a call to decide whether it is "interesting". * Don't specialise very small functions in Specialise.specDefn It's better to inline it. Rather like the worker/wrapper case. * Be just a little more aggressive when floating out of let rhss. See comments with Simplify.wantToExpose A small change with an occasional big effect. * Make the inline-size computation think that case x of I# x -> ... is *free*. CPR analysis ~~~~~~~~~~~~ * Fix what was essentially a bug in CPR analysis. Consider letrec f x = let g y = let ... in f e1 in if ... then (a,b) else g x g has the CPR property if f does; so when generating the final annotated RHS for f, we must use an envt in which f is bound to its final abstract value. This wasn't happening. Instead, f was given the CPR tag but g wasn't; but of course the w/w pass gives rotten results in that case!! (Because f's CPR-ness relied on g's.) On they way I tidied up the code in CprAnalyse. It's quite a bit shorter. The fact that some data constructors return a constructed product shows up in their CPR info (MkId.mkDataConId) not in CprAnalyse.lhs Strictness analysis and worker/wrapper ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * BIG THING: pass in the demand to StrictAnal.saExpr. This affects situations like f (let x = e1 in (x,x)) where f turns out to have strictness u(SS), say. In this case we can mark x as demanded, and use a case expression for it. The situation before is that we didn't "know" that there is the u(SS) demand on the argument, so we simply computed that the body of the let expression is lazy in x, and marked x as lazily-demanded. Then even after f was w/w'd we got let x = e1 in case (x,x) of (a,b) -> $wf a b and hence let x = e1 in $wf a b I found a much more complicated situation in spectral/sphere/Main.shade, which improved quite a bit with this change. * Moved the StrictnessInfo type from IdInfo to Demand. It's the logical place for it, and helps avoid module loops * Do worker/wrapper for coerces even if the arity is zero. Thus: stdout = coerce Handle (..blurg..) ==> wibble = (...blurg...) stdout = coerce Handle wibble This is good because I found places where we were saying case coerce t stdout of { MVar a -> ... case coerce t stdout of { MVar b -> ... and the redundant case wasn't getting eliminated because of the coerce.
* [project @ 2000-03-14 12:16:00 by simonmar]simonmar2000-03-141-23/+0
| | | | | | | | | | | | | | | Simplfy the mutable array story: - rename MutableArray to STArray (and similarly for all operations on MutableArray, eg newArray is now newSTArray). - remove the extra level of indirection between STArrays and MutableArrays. - remove the MutableArray interface from hslibs/lang/MutableArray. This module will go away soon - Andy, don't bother porting it to Hugs.
* [project @ 2000-03-10 15:20:18 by simonmar]simonmar2000-03-101-27/+78
| | | | | | Fix h{Fill,Put}Buf(BA)?. They now work in the presence of partial/blocking reads and writes, and hPutBuf now doesn't hold on to the handle while it's blocking.
* [project @ 2000-01-30 10:08:27 by simonmar]simonmar2000-01-301-1/+8
| | | | comment fixup
* [project @ 2000-01-18 12:44:37 by simonmar]simonmar2000-01-181-17/+37
| | | | | | Don't hold the lock on the Handle while we block waiting for data on a read. This is a partial solution to the general problem of holding a lock on the Handle while in mayBlock.
* [project @ 2000-01-13 14:33:57 by hwloidl]hwloidl2000-01-131-0/+2
| | | | | Merged GUM-4-04 branch into the main trunk. In particular merged GUM and SMP code. Most of the GranSim code in GUM-4-04 still has to be carried over.
* [project @ 1999-12-20 10:34:27 by simonpj]simonpj1999-12-201-3/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This commit implements a substantial re-organisation of the Prelude It also fixes a couple of small renamer bugs that were reported recently (notably, Sven pointed out that we weren't reporting unused imports properly) My original goal was to get rid of all "orphan" modules (i.e. ones with instance decls that don't belong either to a tycon or a class defined in the same module). This should reduce the number of interface files that have to be read when compiling small Haskell modules. But like most expeditions into the Prelude Swamp, it spiraled out of control. The result is quite satisfactory, though. GONE AWAY: PrelCCall, PrelNumExtra NEW: PrelReal, PrelFloat, PrelByteArr, PrelNum.hi-boot (The extra PrelNum.hi-boot is because of a tiresome thin-air Id, addr2Integer, which used to be in PrelBase.) Quite a lot of types have moved from one module to another, which entails some changes to part of the compiler (PrelInfo, PrelMods) etc, and there are a few places in the RTS includes and even in the driver that know about these home modules (alas). So the rough structure is as follows, in (linearised) dependency order [this list now appears in PrelBase.lhs] PrelGHC Has no implementation. It defines built-in things, and by importing it you bring them into scope. The source file is PrelGHC.hi-boot, which is just copied to make PrelGHC.hi Classes: CCallable, CReturnable PrelBase Classes: Eq, Ord, Functor, Monad Types: list, (), Int, Bool, Ordering, Char, String PrelTup Types: tuples, plus instances for PrelBase classes PrelShow Class: Show, plus instances for PrelBase/PrelTup types PrelEnum Class: Enum, plus instances for PrelBase/PrelTup types PrelMaybe Type: Maybe, plus instances for PrelBase classes PrelNum Class: Num, plus instances for Int Type: Integer, plus instances for all classes so far (Eq, Ord, Num, Show) Integer is needed here because it is mentioned in the signature of 'fromInteger' in class Num PrelReal Classes: Real, Integral, Fractional, RealFrac plus instances for Int, Integer Types: Ratio, Rational plus intances for classes so far Rational is needed here because it is mentioned in the signature of 'toRational' in class Real Ix Classes: Ix, plus instances for Int, Bool, Char, Integer, Ordering, tuples PrelArr Types: Array, MutableArray, MutableVar Does *not* contain any ByteArray stuff (see PrelByteArr) Arrays are used by a function in PrelFloat PrelFloat Classes: Floating, RealFloat Types: Float, Double, plus instances of all classes so far This module contains everything to do with floating point. It is a big module (900 lines) With a bit of luck, many modules can be compiled without ever reading PrelFloat.hi PrelByteArr Types: ByteArray, MutableByteArray We want this one to be after PrelFloat, because it defines arrays of unboxed floats. Other Prelude modules are much easier with fewer complex dependencies.
* [project @ 1999-11-29 14:52:24 by keithw]keithw1999-11-291-1/+1
| | | | error.h -> stgerror.h
* [project @ 1999-11-22 15:55:49 by simonmar]simonmar1999-11-221-2/+5
| | | | | | Reduce the number of orphan-instance modules. There are a few left, but these can't be removed without significant reorganisation due to recursive dependencies.
* [project @ 1999-10-22 08:47:39 by sof]sof1999-10-221-2/+2
| | | | made writeErrString__ f.i. unsafe
* [project @ 1999-10-05 09:02:30 by simonmar]simonmar1999-10-051-1/+1
| | | | | | Flatten out the tuple of bounds in the Array, MutableArray and ByteArray datatypes. This improves performance of heavy array manipulations quite significantly.
* [project @ 1999-09-19 19:12:39 by sof]sof1999-09-191-173/+178
| | | | | Drop the use of _ccall_, _casm_ and lit-lits in std/, "foreign import" is the future.
* [project @ 1999-09-17 09:38:33 by sof]sof1999-09-171-3/+3
| | | | Non-blocking I/O isn't supported on 'pure' Win32 platforms.
* [project @ 1999-09-16 13:14:38 by simonmar]simonmar1999-09-161-23/+5
| | | | | | | | | | | | | | | | | | | | Cleanup of non-blocking I/O - file descriptors are now always set to non-blocking mode. - we don't do an inputReady operation on descriptors before attempting to read from them any more. - the non-blocking flag on Handles has gone. - the {set,clear}[Conn]NonBlockingFlag() functions have gone. - the socket operations have been made to work properly with threads: accept is now non-blocking (it does a threadWaitRead instead of blocking), and the file descriptors returned by accept are set to non-blocking mode. Win32 will need some adjustments, no doubt.
* [project @ 1999-08-26 13:34:36 by simonmar]simonmar1999-08-261-11/+0
| | | | threadDelay etc. should be defined in PrelConc.
* [project @ 1999-08-25 16:39:14 by simonmar]simonmar1999-08-251-17/+9
| | | | enable non-blocking I/O.
* [project @ 1999-08-23 12:53:23 by keithw]keithw1999-08-231-1/+1
| | | | | | Revert commit of 1999/06/12 16:17:28. We use -traditional for CPP, and so x##y and #x don't work and we must use x/**/y (ugh) and "x" (urk!!) instead. Ah well.
* [project @ 1999-07-08 08:10:52 by simonmar]simonmar1999-07-081-12/+13
| | | | Back out rev 1.30 - it broke a lot of things.
* [project @ 1999-07-06 16:45:31 by simonpj]simonpj1999-07-061-4/+0
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | All Simon's recent tuning changes. Rough summary follows: * Fix Kevin Atkinson's cant-find-instance bug. Turns out that Rename.slurpSourceRefs needs to repeatedly call getImportedInstDecls, and then go back to slurping source-refs. Comments with Rename.slurpSourceRefs. * Add a case to Simplify.mkDupableAlt for the quite-common case where there's a very simple alternative, in which case there's no point in creating a join-point binding. * Fix CoreUtils.exprOkForSpeculation so that it returns True of (==# a# b#). This lack meant that case ==# a# b# of { True -> x; False -> x } was not simplifying * Make float-out dump bindings at the top of a function argument, as at the top of a let(rec) rhs. See notes with FloatOut.floatRhs * Make the ArgOf case of mkDupableAlt generate a OneShot lambda. This gave a noticeable boost to spectral/boyer2 * Reduce the number of coerces, using worker/wrapper stuff. The main idea is in WwLib.mkWWcoerce. The gloss is that we must do the w/w split even for small non-recursive things. See notes with WorkWrap.tryWw. * This further complicated getWorkerId, so I finally bit the bullet and make the workerInfo field of the IdInfo work properly, including under substitutions. Death to getWorkerId. Kevin Glynn will be happy. * Make all lambdas over realWorldStatePrimTy into one-shot lambdas. This is a GROSS HACK. * Also make the occurrence analyser aware of one-shot lambdas. * Make various Prelude things into INLINE, so that foldr doesn't get inlined in their body, so that the caller gets the benefit of fusion. Notably in PrelArr.lhs.
* [project @ 1999-07-05 19:26:42 by sof]sof1999-07-051-13/+12
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | Temporary workaround for problem which caused the following program main = putStrLn ("aa" ++ IOExts.trace "bb" "cc") to deadlock - when the (untouched) stderr is evaluated (which IOExts.trace forces), it will touch stdout (see code for details of why), but it has already been locked by putStrLn. Boom - game over. This temporary 'fix' is, to put it kindly, in the fancy-footwork category as it doesn't solve the problem, but merely turns it on its head. Instead of stderr depending on stdout, stdout now depends on stderr, so the following program will deadlock main = hPutStrLn stderr ("aa" ++ myTrace "bb" "cc") myTrace msg v = unsafePerformIO $ do putStrLn msg return v The 'theory' is that this is far less likely to occur in practice than the other way around. The next step / real solution would be to give up the lock on an output Handle while filling up its output buffer. However, that requires ripping out / re-org'ing a fair bit of buffer management code, which I'll delay doing.
* [project @ 1999-06-25 14:10:03 by simonmar]simonmar1999-06-251-232/+139
| | | | Fix some race holes in the handle locking code, and clean it up a little.
* [project @ 1999-06-12 16:17:23 by keithw]keithw1999-06-121-1/+1
| | | | K&R -> ANSI token pasting (ie, x##y for x/**/y)
* [project @ 1999-06-01 16:15:42 by simonmar]simonmar1999-06-011-4/+4
| | | | Remove illegal use of layout.
* [project @ 1999-05-18 14:59:04 by simonpj]simonpj1999-05-181-1/+4
| | | | ../compiler/msg_prel
* [project @ 1999-05-10 16:52:10 by sof]sof1999-05-101-1/+1
| | | | PrelHandle.withHandle: don't catch IO exceptions.
* [project @ 1999-04-27 17:41:17 by sof]sof1999-04-271-4/+57
| | | | | | | | | | | | * Added toplevel exception handler: topHandler :: Bool -- bomb on exception caught -> Exception -> IO () for PrelMain.mainIO and Concurrent.forkIO to use * moved forkIO out of PrelConc and into Concurrent.
* [project @ 1999-02-25 10:18:28 by sof]sof1999-02-251-1/+1
| | | | | | | | | | hClose: don't raise an exception when passed a handle that's already closed, i.e., h <- openFile "a" ReadMode >> hClose h >> hClose h will now succeed (provided 'a' exists and is readable, of course.) Repeated hClose's are just redundant.
* [project @ 1999-02-19 10:48:27 by simonm]simonm1999-02-191-5/+6
| | | | Hack around a couple of explicit uses of the Integer rep.
* [project @ 1999-02-17 15:57:20 by simonm]simonm1999-02-171-2/+2
| | | | | | | | | | | | | | | | | | Fast Integers. The rep. of Integers is now data Integer = S# Int# | J# Int# ByteArray# - several new primops added for overflow-detecting arithmetic - negateInteger# removed; it can be done directly - integer_0, integer_1 etc. removed. - the compiler now uses S# where it previously used int2Integer. - the compiler generates small integers for -2^32 .. 2^32-1, instead of -2^29 .. -2^29-1. - PrelST.State datatype moved to LazyST (its only use). - some library code (in Time.lhs) still needs cleaning up, it depends on the Integer rep.
* [project @ 1999-02-11 14:35:23 by simonm]simonm1999-02-111-7/+7
| | | | More weak pointer changes.
* [project @ 1999-01-28 11:32:11 by simonpj]simonpj1999-01-281-2/+0
| | | | Wibble