Skip to content
Snippets Groups Projects
  1. Oct 02, 2000
  2. Sep 29, 2000
  3. Sep 28, 2000
    • Simon Peyton Jones's avatar
      [project @ 2000-09-28 16:49:36 by simonpj] · 5f8800e2
      Simon Peyton Jones authored
      Another wibble
      5f8800e2
    • Julian Seward's avatar
      [project @ 2000-09-28 16:17:07 by sewardj] · 7b349762
      Julian Seward authored
      wibbles
      7b349762
    • Julian Seward's avatar
      [project @ 2000-09-28 15:50:04 by sewardj] · 87e26385
      Julian Seward authored
      Fill in details about how CM works.
      87e26385
    • Simon Peyton Jones's avatar
      [project @ 2000-09-28 15:16:20 by simonpj] · 05af0089
      Simon Peyton Jones authored
      Simon's log file; I don't want to lose this!
      05af0089
    • Simon Peyton Jones's avatar
      [project @ 2000-09-28 15:15:48 by simonpj] · fa67ca4d
      Simon Peyton Jones authored
      Wibbles
      fa67ca4d
    • Simon Peyton Jones's avatar
      [project @ 2000-09-28 13:04:14 by simonpj] · 861e836e
      Simon Peyton Jones authored
      ------------------------------------
      	   Mainly PredTypes (28 Sept 00)
      	------------------------------------
      
      Three things in this commit:
      
      	1.  Main thing: tidy up PredTypes
      	2.  Move all Keys into PrelNames
      	3.  Check for unboxed tuples in function args
      
      1. Tidy up PredTypes
      ~~~~~~~~~~~~~~~~~~~~
      The main thing in this commit is to modify the representation of Types
      so that they are a (much) better for the qualified-type world.  This
      should simplify Jeff's life as he proceeds with implicit parameters
      and functional dependencies.  In particular, PredType, introduced by
      Jeff, is now blessed and dignified with a place in TypeRep.lhs:
      
      	data PredType  = Class  Class [Type]
      		       | IParam Name  Type
      
      Consider these examples:
      	f :: (Eq a) => a -> Int
      	g :: (?x :: Int -> Int) => a -> Int
      	h :: (r\l) => {r} => {l::Int | r}
      
      Here the "Eq a" and "?x :: Int -> Int" and "r\l" are all called
      *predicates*, and are represented by a PredType.  (We don't support
      TREX records yet, but the setup is designed to expand to allow them.)
      
      In addition, Type gains an extra constructor:
      
      	data Type = .... | PredTy PredType
      
      so that PredType is injected directly into Type.  So the type
      	p => t
      is represented by
      	PredType p `FunTy` t
      
      I have deleted the hackish IPNote stuff; predicates are dealt with entirely
      through PredTys, not through NoteTy at all.
      
      
      2.  Move Keys into PrelNames
      ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
      This is just a housekeeping operation. I've moved all the pre-assigned Uniques
      (aka Keys) from Unique.lhs into PrelNames.lhs.  I've also moved knowKeyRdrNames
      from PrelInfo down into PrelNames.  This localises in PrelNames lots of stuff
      about predefined names.  Previously one had to alter three files to add one,
      now only one.
      
      3.  Unboxed tuples
      ~~~~~~~~~~~~~~~~~~
      Add a static check for unboxed tuple arguments.  E.g.
      	data T = T (# Int, Int #)
      is illegal
      861e836e
    • Julian Seward's avatar
      [project @ 2000-09-28 12:19:46 by sewardj] · 0be02ed6
      Julian Seward authored
      Define relationship between what CM implements and the HEP interface.
      Start on saying how CM behaves.
      0be02ed6
  4. Sep 27, 2000
  5. Sep 26, 2000
  6. Sep 25, 2000
  7. Sep 22, 2000
    • Simon Peyton Jones's avatar
      [project @ 2000-09-22 16:00:08 by simonpj] · 01d54e87
      Simon Peyton Jones authored
      Forgot to remove HsBasic and add HsLit
      01d54e87
    • Simon Peyton Jones's avatar
      [project @ 2000-09-22 15:56:12 by simonpj] · 1bba522f
      Simon Peyton Jones authored
      --------------------------------------------------
      	Tidying up HsLit, and making it possible to define
      		your own numeric library
      
      		Simon PJ 22 Sept 00
      	--------------------------------------------------
      
      ** NOTE: I did these changes on the aeroplane.  They should compile,
      	 and the Prelude still compiles OK, but it's entirely 
      	 possible that I've broken something
      
      The original reason for this many-file but rather shallow
      commit is that it's impossible in Haskell to write your own
      numeric library.  Why?  Because when you say '1' you get 
      (Prelude.fromInteger 1), regardless of what you hide from the
      Prelude, or import from other libraries you have written.  So the
      idea is to extend the -fno-implicit-prelude flag so that 
      in addition to no importing the Prelude, you can rebind 
      	fromInteger	-- Applied to literal constants
      	fromRational	-- Ditto
      	negate		-- Invoked by the syntax (-x)
      	the (-) used when desugaring n+k patterns
      
      After toying with other designs, I eventually settled on a simple,
      crude one: rather than adding a new flag, I just extended the
      semantics of -fno-implicit-prelude so that uses of fromInteger,
      fromRational and negate are all bound to "whatever is in scope" 
      rather than "the fixed Prelude functions".  So if you say
      
      	{-# OPTIONS -fno-implicit-prelude #-}
      	module M where
       	import MyPrelude( fromInteger )
      
      	x = 3
      
      the literal 3 will use whatever (unqualified) "fromInteger" is in scope,
      in this case the one gotten from MyPrelude.
      
      
      On the way, though, I studied how HsLit worked, and did a substantial tidy
      up, deleting quite a lot of code along the way.  In particular.
      
      * HsBasic.lhs is renamed HsLit.lhs.  It defines the HsLit type.
      
      * There are now two HsLit types, both defined in HsLit.
      	HsLit for non-overloaded literals (like 'x')
      	HsOverLit for overloaded literals (like 1 and 2.3)
      
      * HsOverLit completely replaces Inst.OverloadedLit, which disappears.
        An HsExpr can now be an HsOverLit as well as an HsLit.
      
      * HsOverLit carries the Name of the fromInteger/fromRational operation,
        so that the renamer can help with looking up the unqualified name 
        when -fno-implicit-prelude is on.  Ditto the HsExpr for negation.
        It's all very tidy now.
      
      * RdrHsSyn contains the stuff that handles -fno-implicit-prelude
        (see esp RdrHsSyn.prelQual).  RdrHsSyn also contains all the "smart constructors"
        used by the parser when building HsSyn.  See for example RdrHsSyn.mkNegApp
        (previously the renamer (!) did the business of turning (- 3#) into -3#).
      
      * I tidied up the handling of "special ids" in the parser.  There's much
        less duplication now.
      
      * Move Sven's Horner stuff to the desugarer, where it belongs.  
        There's now a nice function DsUtils.mkIntegerLit which brings together
        related code from no fewer than three separate places into one single
        place.  Nice!
      
      * A nice tidy-up in MatchLit.partitionEqnsByLit became possible.
      
      * Desugaring of HsLits is now much tidier (DsExpr.dsLit)
      
      * Some stuff to do with RdrNames is moved from ParseUtil.lhs to RdrHsSyn.lhs,
        which is where it really belongs.
      
      * I also removed 
      	many unnecessary imports from modules 
      	quite a bit of dead code
        in divers places
      1bba522f
    • Simon Peyton Jones's avatar
      [project @ 2000-09-22 15:47:14 by simonpj] · a8e1967f
      Simon Peyton Jones authored
      msg1
      a8e1967f
  8. Sep 14, 2000
    • Simon Marlow's avatar
      [project @ 2000-09-14 14:24:02 by simonmar] · 46b762e6
      Simon Marlow authored
      rename blockAsyncExceptions and unblockAsyncExceptions to block and
      unblock repectively, to match all the literature.  DEPRECATE the old
      names.
      46b762e6
    • Simon Peyton Jones's avatar
      [project @ 2000-09-14 13:46:39 by simonpj] · cae34044
      Simon Peyton Jones authored
      ---------------------------------------
      	Simon's tuning changes: early Sept 2000
      	---------------------------------------
      
      Library changes
      ~~~~~~~~~~~~~~~
      * Eta expand PrelShow.showLitChar.  It's impossible to compile this well,
        and it makes a big difference to some programs (e.g. gen_regexps)
      
      * Make PrelList.concat into a good producer (in the foldr/build sense)
      
      
      Flag changes
      ~~~~~~~~~~~~
      * Add -ddump-hi-diffs to print out changes in interface files.  Useful
        when watching what the compiler is doing
      
      * Add -funfolding-update-in-place to enable the experimental optimisation
        that makes the inliner a bit keener to inline if it's in the RHS of
        a thunk that might be updated in place.  Sometimes this is a bad idea
        (one example is in spectral/sphere; see notes in nofib/Simon-nofib-notes)
      
      
      Tuning things
      ~~~~~~~~~~~~~
      * Fix a bug in SetLevels.lvlMFE.  (change ctxt_lvl to dest_level)
        I don't think this has any performance effect, but it saves making
        a redundant let-binding that is later eliminated.
      
      * Desugar.dsProgram and DsForeign
        Glom together all the bindings into a single Rec.  Previously the
        bindings generated by 'foreign' declarations were not glommed together, but
        this led to an infelicity (i.e. poorer code than necessary) in the modules
        that actually declare Float and Double (explained a bit more in Desugar.dsProgram)
      
      * OccurAnal.shortMeOut and IdInfo.shortableIdInfo
        Don't do the occurrence analyser's shorting out stuff for things which
        have rules.  Comments near IdInfo.shortableIdInfo.
        This is deeply boring, and mainly to do with making rules work well.
        Maybe rules should have phases attached too....
      
      * CprAnalyse.addIdCprInfo
        Be a bit more willing to add CPR information to thunks;
        in particular, if the strictness analyser has just discovered that this
        is a strict let, then the let-to-case transform will happen, and CPR is fine.
        This made a big difference to PrelBase.modInt, which had something like
      	modInt = \ x -> let r = ... -> I# v in
      			...body strict in r...
        r's RHS isn't a value yet; but modInt returns r in various branches, so
        if r doesn't have the CPR property then neither does modInt
      
      * MkId.mkDataConWrapId
        Arrange that vanilla constructors, like (:) and I#, get unfoldings that are
        just a simple variable $w:, $wI#.  This ensures they'll be inlined even into
        rules etc, which makes matching a bit more reliable.  The downside is that in
        situations like (map (:) xs), we'll end up with (map (\y ys. $w: y ys) xs.
        Which is tiresome but it doesn't happen much.
      
      * SaAbsInt.findStrictness
        Deal with the case where a thing with no arguments is bottom.  This is Good.
        E.g.   module M where { foo = error "help" }
        Suppose we have in another module
      	case M.foo of ...
        Then we'd like to do the case-of-error transform, without inlining foo.
      
      
      Tidying up things
      ~~~~~~~~~~~~~~~~~
      * Reorganised Simplify.completeBinding (again).
      
      * Removed the is_bot field in CoreUnfolding (is_cheap is true if is_bot is!)
        This is just a tidy up
      
      * HsDecls and others
        Remove the NewCon constructor from ConDecl.  It just added code, and nothing else.
        And it led to a bug in MkIface, which though that a newtype decl was always changing!
      
      * IdInfo and many others
        Remove all vestiges of UpdateInfo (hasn't been used for years)
      cae34044
    • Simon Peyton Jones's avatar
      [project @ 2000-09-14 12:12:23 by simonpj] · 189333a4
      Simon Peyton Jones authored
      Improve the kind-inference test
      189333a4
    • Simon Marlow's avatar
      [project @ 2000-09-14 09:58:00 by simonmar] · fd1e4701
      Simon Marlow authored
      don't forget to bail out when "compilation IS NOT required"
      fd1e4701
Loading