Hi,

You might already be aware of this, but .type seems to be a gas- specific directive. At least, it's not supported by the OS X version of as, so HEAD can't successfully compile things on that platform for the moment. Feel free to ignore me if you're already planning to fix this. :)

Thanks,
Aaron

On Jun 27, 2007, at 9:54 AM, Clemens Fruhwirth wrote:

Wed Jun 27 18:51:50 CEST 2007 Clemens Fruhwirth <[EMAIL PROTECTED]>
  * Set .type @object for all global symbols in NCG

When linking against a dynamic library, the linker will emit a warning if no type information is present within the library. We generate the
  most trivial type for all externally visible labels, namely @object.

New patches:

[Set .type @object for all global symbols in NCG
Clemens Fruhwirth <[EMAIL PROTECTED]>**20070627165150

When linking against a dynamic library, the linker will emit a warning
 if no type information is present within the library. We generate the
 most trivial type for all externally visible labels, namely @object.
] {
hunk ./compiler/nativeGen/PprMach.hs 695
+pprTypeAndSizeDecl :: CLabel -> Doc
+pprTypeAndSizeDecl lbl
+  | not (externallyVisibleCLabel lbl) = empty
+  | otherwise = ptext SLIT(".type ") <>
+               pprCLabel_asm lbl <> ptext SLIT(", @object")
+
hunk ./compiler/nativeGen/PprMach.hs 702
-pprLabel lbl = pprGloblDecl lbl $$ (pprCLabel_asm lbl <> char ':')
+pprLabel lbl = pprGloblDecl lbl $$ pprTypeAndSizeDecl lbl $$ (pprCLabel_asm lbl <> char ':')
}

Context:

[FIX BUILD (on Windows): follow changes to make threaded RTS compile with -fasm
[EMAIL PROTECTED]
[Fix names of coercions in newtype instances
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070627094200
 - Thanks to Roman for spotting the problem.
]
[Cleaning up Hpc.c; adding support for reflection into Hpc.
[EMAIL PROTECTED]
[Fixing Makefile hpc to use compat
[EMAIL PROTECTED]
[Adding Tix to compat library, so that hpc in utils can use it
[EMAIL PROTECTED]
[fixing creation of directory for html output; fixing html markup for 0% bars.
[EMAIL PROTECTED]
[Fixing -fhpc flag to allow -fno-hpc
[EMAIL PROTECTED]
[Fixed deriving of associated data types
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070627054834
- We forgot to pull the data declarations nested in class instances out of the instances when collecting all the predicates that we need derive.
   Thanks to Roman for spotting this.
]
[add missing case for compiling 64-bit operations on x86
Simon Marlow <[EMAIL PROTECTED]>**20070626211153]
[Make the threaded RTS compilable using -fasm
Simon Marlow <[EMAIL PROTECTED]>**20070626211058
 We needed to turn some inline C functions and C macros into either
 real C functions or C-- macros.
]
[x86_64: fix a few bugs in the >8 floating point args case
Simon Marlow <[EMAIL PROTECTED]>**20070626103055]
[make inplace scripts less sensitive to /bin/sh quoting by avoiding \
Simon Marlow <[EMAIL PROTECTED]>**20070623200006]
[excluding Trace.Hpc.* when using the compat library
[EMAIL PROTECTED]
[Making -fhpc work with a stage1 build, via the compat 'package'.
[EMAIL PROTECTED]
[Adding hpc lib as part of the compat 'package'
[EMAIL PROTECTED]
[Cleanup Hpc sub-system, remove hpc-tracer implementation.
[EMAIL PROTECTED]
[Add a compileToCore function to the GHC API
Tim Chevalier <[EMAIL PROTECTED]>**20070625220608

 Added a compileToCore function to the GHC API that takes a
   session, module, and filename, and returns a list of Core
   bindings if successful. This is just a first try and could
   probably be improved (for example, there's probably a way to
   get the filename from the module so that it doesn't have to
   be passed in, I just don't see it offhand.)

]
[Define SUBDIRS in Makefile (needed for clean; fixes trac #1440)
Ian Lynagh <[EMAIL PROTECTED]>**20070625174952]
[Tweak the configuration and installation slightly
Ian Lynagh <[EMAIL PROTECTED]>**20070625174011
Make it so that the documentation ends up where Cabal expects it to be
 on Windows (prep-bin-dist-mingw used to move it).
]
[withExtendedLinkerState: don't revert the whole state
Simon Marlow <[EMAIL PROTECTED]>**20070625151455
 Fixes test failures print017 and print024
]
[Print infix type constructors in an infix way
[EMAIL PROTECTED]

 Fixes Trac #1425.  The printer for types doesn't know about fixities.
 (It could be educated to know, but it doesn't at the moment.)  So it
treats all infix tycons as of precedence less than application and function
 arrrow.

I took a slight shortcut and reused function-arrow prededence, so I think
 you may get
        T -> T :% T
 meaning
        T -> (T :% T)

 If that becomes a problem we can fix it.

]
[Clamp -O flag to beween 0 and 2
[EMAIL PROTECTED]

 Fixes Trac #1272

]
[Adding hpc tools, as a single program.
[EMAIL PROTECTED]
[Update version numbering policy in the users guide
Ian Lynagh <[EMAIL PROTECTED]>**20070623224440]
[Fix an error message
Ian Lynagh <[EMAIL PROTECTED]>**20070623190653
 `y' in the error message
     `x' is not a (visible) method of class `y'
 had gone missing.
]
[turning off -fhpc in stage1 built ghc
[EMAIL PROTECTED]
[removing -fhpc-tracer from ghc, is subsumed by the GHC debugger
[EMAIL PROTECTED]
[Stage2 now used the package hpc to get the hpc datastructures
[EMAIL PROTECTED]
 Stage1 no longer supports hpc (-fhpc is ignored)

]
[Fix typo in Makefile
Ian Lynagh <[EMAIL PROTECTED]>**20070622222133]
[Adding hpc package to ghc core libraries
[EMAIL PROTECTED]
[Change how the libraries Makefile adds --configure-option= flags; fixes #1431
Ian Lynagh <[EMAIL PROTECTED]>**20070622160951
 We now assume that each configure option is quoted with '', and thus
 replace " '" with " --configure-option='".
]
[update with new libraries
Simon Marlow <[EMAIL PROTECTED]>**20070622131211]
[FIX BUILD on Windows: horrible hack to work around make(?) bug
Simon Marlow <[EMAIL PROTECTED]>*-20070621144519]
[FIX BUILD (on Windows): Cabal must invoke compiler/stage1/ghc-inplace
Simon Marlow <[EMAIL PROTECTED]>**20070622111634
 not compiler/ghc-inplace, which is a symlink.

]
[remove unnecessary cruft
Simon Marlow <[EMAIL PROTECTED]>**20070622075602]
[FIX BUILD: all builds need --template, not just Windows
Simon Marlow <[EMAIL PROTECTED]>**20070622075444]
[ignore all but the last --template option
Simon Marlow <[EMAIL PROTECTED]>**20070622075417]
[Unbreak the stage-2 compiler (record-type changes)
[EMAIL PROTECTED]
[-fglasgow-exts implies -X=GADTs
[EMAIL PROTECTED]
[FIX read040: patterns with type sig on LHS of do-binding
[EMAIL PROTECTED]

 f () = do { x :: Bool <- return True; ... }

 For some reason the production for 'pat' required 'infixexp' on the
 LHS of a do-notation binding.  This patch makes it an 'exp', which
 thereby allows an expression with a type sig.

 Happily, there are no new shift-reduce errors, so I don't think this
 will break anything else.



]
[Another wibble to the head-exploded error message (suggested by David Roundy)
[EMAIL PROTECTED]
[Use the correct flag for controlling scoped type variables in an instance decl
[EMAIL PROTECTED]
[Improve 'my head exploded' error message
[EMAIL PROTECTED]
[FIX BUILD: add missing prime!
[EMAIL PROTECTED]
[FIX BUILD on Windows: horrible hack to work around make(?) bug
Simon Marlow <[EMAIL PROTECTED]>**20070621144519]
[yet more fixes: Cygwin broke this time
Simon Marlow <[EMAIL PROTECTED]>**20070621140653]
[fix bugs with hsc2hs-inplace
Lemmih <[EMAIL PROTECTED]>**20070621132825]
[mk/build.mk is optional
Lemmih <[EMAIL PROTECTED]>**20070621130727]
[further fixes to the inplace scripts
Lemmih <[EMAIL PROTECTED]>**20070621130657]
[use a binary for hsc2hs-inplace too
Simon Marlow <[EMAIL PROTECTED]>**20070621121426]
[Fix problems with new inplace stuff on Cygwin
Simon Marlow <[EMAIL PROTECTED]>**20070621114147]
[FIX BUILD: can't build the makefiles during make boot
Simon Marlow <[EMAIL PROTECTED]>**20070621095154]
[clean up lib/{GNUmakefile,Makefile.local}
Simon Marlow <[EMAIL PROTECTED]>**20070620132809]
[default_target should be "all", not "build"
Simon Marlow <[EMAIL PROTECTED]>**20070620132001]
[add comment
Simon Marlow <[EMAIL PROTECTED]>**20070620131949]
[Fix a problem with package.mk being included too early
Simon Marlow <[EMAIL PROTECTED]>**20070620122224]
[Use setup makefile + make by default to build libraries
Simon Marlow <[EMAIL PROTECTED]>**20070620122009

 The advantages of this are
(a) it's a step closer to getting -j working again (make -j works in
       an individual library, but not in libraries/ yet).
   (b) it's easier to hack on libraries: make dist/build/Foo.o
   (c) it's a step closer to getting HC bootstrapping again

 The build system creates <lib>/GNUmakefile as part of 'make boot'.
 This was chosen so as not to interfere with existing Makefiles, but
 it's a bit of a hack.  (previously I used CabalMakefile, but that
 means adding -f CabalMakefile each time you run make, and that's a
 pain).
]
[Use a real binary instead of scripts for ghc-inplace
Simon Marlow <[EMAIL PROTECTED]>**20070621101324
 Fixes various problems with getting the scripts right on Windows.
Binaries are universally executable by /bin/sh, cmd.exe and rawSystem,
 so this allows us to remove some platform-specific hacks.
]
[Add several new record features
Lemmih <[EMAIL PROTECTED]>**20070621091552

 1. Record disambiguation (-fdisambiguate-record-fields)

 In record construction and pattern matching (although not
 in record updates) it is clear which field name is intended
 even if there are several in scope.  This extension uses
 the constructor to disambiguate.  Thus
        C { x=3 }
 uses the 'x' field from constructor C (assuming there is one)
 even if there are many x's in scope.


 2. Record punning (-frecord-puns)

 In a record construction or pattern match or update you can
 omit the "=" part, thus
        C { x, y }
 This is just syntactic sugar for
        C { x=x, y=y }


 3.  Dot-dot notation for records (-frecord-dot-dot)

 In record construction or pattern match (but not update)
 you can use ".." to mean "all the remaining fields".  So

        C { x=v, .. }

 means to fill in the remaining fields to give

        C { x=v, y=y }

 (assuming C has fields x and y).  This might reasonably
 considered very dodgy stuff.  For pattern-matching it brings
 into scope a bunch of things that are not explictly mentioned;
 and in record construction it just picks whatver 'y' is in
 scope for the 'y' field.   Still, Lennart Augustsson really
 wants it, and it's a feature that is extremely easy to explain.


 Implementation
 ~~~~~~~~~~~~~~
 I thought of using the "parent" field in the GlobalRdrEnv, but
 that's really used for import/export and just isn't right for this.
 For example, for import/export a field is a subordinate of the *type
 constructor* whereas here we need to know what fields belong to a
 particular *data* constructor.

 The main thing is that we need to map a data constructor to its
 fields, and we need to do so in the renamer.   For imported modules
 it's easy: just look in the imported TypeEnv.  For the module being
 compiled, we make a new field tcg_field_env in the TcGblEnv.
 The important functions are
        RnEnv.lookupRecordBndr
        RnEnv.lookupConstructorFields

 There is still a significant infelicity in the way the renamer
 works on patterns, which I'll tackle next.


 I also did quite a bit of refactoring in the representation of
 record fields (mainly in HsPat).***END OF DESCRIPTION***

Place the long patch description above the ***END OF DESCRIPTION*** marker.
 The first line of this file will be the patch name.


 This patch contains the following changes:

 M ./compiler/deSugar/Check.lhs -3 +5
 M ./compiler/deSugar/Coverage.lhs -6 +7
 M ./compiler/deSugar/DsExpr.lhs -6 +13
 M ./compiler/deSugar/DsMeta.hs -8 +8
 M ./compiler/deSugar/DsUtils.lhs -1 +1
 M ./compiler/deSugar/MatchCon.lhs -2 +2
 M ./compiler/hsSyn/Convert.lhs -3 +3
 M ./compiler/hsSyn/HsDecls.lhs -9 +25
 M ./compiler/hsSyn/HsExpr.lhs -13 +3
 M ./compiler/hsSyn/HsPat.lhs -25 +63
 M ./compiler/hsSyn/HsUtils.lhs -3 +3
 M ./compiler/main/DynFlags.hs +6
 M ./compiler/parser/Parser.y.pp -13 +17
 M ./compiler/parser/RdrHsSyn.lhs -16 +18
 M ./compiler/rename/RnBinds.lhs -2 +2
 M ./compiler/rename/RnEnv.lhs -22 +82
 M ./compiler/rename/RnExpr.lhs -34 +12
 M ./compiler/rename/RnHsSyn.lhs -3 +2
 M ./compiler/rename/RnSource.lhs -50 +78
 M ./compiler/rename/RnTypes.lhs -50 +84
 M ./compiler/typecheck/TcExpr.lhs -18 +18
 M ./compiler/typecheck/TcHsSyn.lhs -20 +21
 M ./compiler/typecheck/TcPat.lhs -8 +6
 M ./compiler/typecheck/TcRnMonad.lhs -6 +15
 M ./compiler/typecheck/TcRnTypes.lhs -2 +11
 M ./compiler/typecheck/TcTyClsDecls.lhs -3 +4
 M ./docs/users_guide/flags.xml +7
 M ./docs/users_guide/glasgow_exts.xml +42
]
[Remove the unused HsExpr constructor DictPat
Lemmih <[EMAIL PROTECTED]>**20070618124605]
[Fix a bug in MatchCon, and clarify what dataConInstOrigArgTys does
Lemmih <[EMAIL PROTECTED]>**20070607213837

There was an outright bug in MatchCon.matchOneCon, in the construction of arg_tys. Easily fixed. It never showed up becuase the arg_tys are only used in WildPats, and they in turn seldom have their types looked
 (except by hsPatType).  So I can't make a test case for htis.

 While I was investigating, I added a bit of clarifation and
 invariant-checking to dataConInstOrigArgTys and dataConInstArgTys

]
[Do not perform a worker/wrapper split for a NOINLINE function
Lemmih <[EMAIL PROTECTED]>**20070607213523

 This came up in an email exchange with Duncan Coutts in May 2007.
 If a function is marked NOINLINE there is really no point in
 doing a worker/wrapper split, because the wrapper will never
 be inlined.


]
[Fix Trac #1402: typo in specialiser
Lemmih <[EMAIL PROTECTED]>**20070607185534

 This patch fixes a plain bug in the specialiser (rhs_bndrs instead
 of rhs_ids) which made GHC crash in obscure cases.

It exposed a case in which we might not do all possible specialisation; see Note [Specialisation shape]. It's not an important case, but I've
 added a warning in DEBUG mode.

 Trac #1402.  Test is spec003.hs

]
[Wibble: make -fno-implicit-prelude work
[EMAIL PROTECTED]
[Remove an incorrect claim that [t| ... |] isn't implemented yet
Ian Lynagh <[EMAIL PROTECTED]>**20070621003103]
[Make building haddock docs opt-in rather than opt-out
Ian Lynagh <[EMAIL PROTECTED]>**20070620235909]
[Don't assume that the main repo is called "ghc" in darcs-all
Ian Lynagh <[EMAIL PROTECTED]>**20070620234007
 Fixes working in branches where that isn't true.
]
[Trivial fix to clear Trac #1386
[EMAIL PROTECTED]
[Wibbles in flaggery, concerning backward compatibility with -f flags
[EMAIL PROTECTED]
[Implement -X=GADTs and -X=RelaxedPolyRec
[EMAIL PROTECTED]

Two new -X flags, one for GADTs and one for relaxed polymorphic recursion

 This also fixes a rather confusing error message that the Darcs folk
 tripped over.

]
[Use -X for language extensions
[EMAIL PROTECTED]

We've often talked about having a separate flag for language extensions,
 and now we have one. You can say

        -XImplicitParams
        -X=ImplicitParams
        -Ximplicit-params

 as you like.  These replace the "-f" flags with similar names (though
 the -f prefix will serve as a synonym for -X for a while).

There's an optional "=", and the flag is normalised by removing hyphens
 and lower-casing, so all the above variants mean the same thing.

 The nomenclature is intended to match the LANGUAGE pramgas, which are
 defined by Cabal.  So you can also say

        {-# LANGUAGE ImplicitParams #-}

But Cabal doesn't have as many language options as GHC does, so the -X
 things are a superset of the LANGUAGE things.

The optional "=" applies to all flags that take an argument, so you can,
 for example, say
        
        -pgmL=/etc/foo

 I hope that's ok.  (It's an unforced change; just fitted in.)

I hope we'll add more -X flags, to replace the portmanteau - fglasgow-exts
 which does everything!

 I have updated the manual, but doubtless missed something.



]
[Unused import
[EMAIL PROTECTED]
[turning back on case liberation when using hpc
[EMAIL PROTECTED]
[remove debugging code accidentally left in
Simon Marlow <[EMAIL PROTECTED]>**20070620125742]
[Use .NOTPARALLEL for the libraries Makefile
Ian Lynagh <[EMAIL PROTECTED]>**20070620120723]
[Improve the handling of deriving, in error cases
[EMAIL PROTECTED]

 I'd been too ambitious with error handling for 'deriving', and got it
 entirely wrong.  This fixes it.  See extensive
        Note [Exotic derived instance contexts]
 in TcSimplify.  (Most of the extra lines are comments!)

]
[More refactoring in TcSimplify
[EMAIL PROTECTED]

This re-jig tides up the top-level simplification, and combines in one
 well-commented function, approximateImplications, the rather ad-hoc
 way of simplifying implication constraints during type inference.

 Error messages get a bit better too.

]
[Fix egregious sharing bug in LiberateCase
[EMAIL PROTECTED]

 Andy Gill writes: consider the following code

        f = g (case v of
                 V a b -> a : t f)

 where g is expensive. Liberate case will turn this into

        f = g (case v of
                V a b -> a : t (letrec f = g (case v of
                                              V a b -> a : f t)
                                 in f)
              )
 Yikes! We evaluate g twice. This leads to a O(2^n) explosion
 if g calls back to the same code recursively.

 This may be the same as Trac #1366.


]
[Turning off case liberation when using the hpc option, for now
[EMAIL PROTECTED]

 Consider the following code

      f = g (case v of
               V a b -> a : t f)

 where g is expensive. Liberate case will turn this into

      f = g (case v of
              V a b -> a : t (letrec f = g (case v of
                                            V a b -> a : f t)
                               in f)
            )

 Yikes! We evaluate g twice. This leads to a O(2^n) explosion
 if g calls back to the same code recursively.

This happen sometimes in HPC, because every tick is a liberate- able case,
 but is a general problem to case liberation (I think).

]
[Add --core-only flag to push-all
Ian Lynagh <[EMAIL PROTECTED]>**20070619200546]
[Add a push-all script
Ian Lynagh <[EMAIL PROTECTED]>**20070619192820]
[Improve misleading warning (Trac #1422)
[EMAIL PROTECTED]
[Fix a bug in the handling of implication constraints (Trac #1430)
[EMAIL PROTECTED]

 Trac #1430 showed up quite a nasty bug in the handling of implication
 constraints when we are *inferring* the type of a function.
 See Note [Inference and implication constraints]:

We can't (or at least don't) abstract over implications. But we might have an implication constraint (perhaps arising from a nested pattern
   match) like
        C a => D a
when we are now trying to quantify over 'a'. Our best approximation is to make (D a) part of the inferred context, so we can use that to
   discharge the implication. Hence getImplicWanteds.

My solution is not marvellous, but it's better than before. I transferred
 function getDefaultableDicts from Inst to TcSimplify (since it's only
 called there).  Many of the remaining 50 new lines are comments.  But
 there is undoubtedly more code than before (sigh).

 Test is tc228.



]
[Comments only
[EMAIL PROTECTED]
[Remove erroneous requirement to import Control.Monad.Fix when using mdo
[EMAIL PROTECTED]

 See Trac #1426

]
[First cut at documentation for HPC option in GHC
[EMAIL PROTECTED]
[Build package ndp if present
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20070619011510]
[typo
Simon Marlow <[EMAIL PROTECTED]>**20070618111817]
[More debugger output order consistency
Ian Lynagh <[EMAIL PROTECTED]>**20070618102850]
[Several changes to the code dealing with newtypes in :print
Pepe Iborra <[EMAIL PROTECTED]>**20070617193435

I simplified the code, killed some unreachable blocks, and renamed it so that it corresponds more accurately with what is explained in the technical report

http://www.dsic.upv.es/docs/bib-dig/informes/etd-04042007-111431/ papernew2.pdf

 Also, fixed a bug related to newtypes in the pretty printer

]
[Remove now non-existant "Breakpoints" entry from package.conf.in
Pepe Iborra <[EMAIL PROTECTED]>**20070613092102]
[Sort names before printing them in the debugger so output order is consistent
Ian Lynagh <[EMAIL PROTECTED]>**20070617215205]
[Use %d rather than %zd on Windows
Ian Lynagh <[EMAIL PROTECTED]>**20070616193745]
[Add missing quotes in generated script
Ian Lynagh <[EMAIL PROTECTED]>**20070615184527]
[Fix size mismatch errors in mkDerivedConstants.c
Ian Lynagh <[EMAIL PROTECTED]>**20070615182337]
[workaround for #1421 (Solaris linker being picky about .size)
Simon Marlow <[EMAIL PROTECTED]>**20070614095727]
[I didn't quite fix #1424 completely - hopefully this gets it right
Simon Marlow <[EMAIL PROTECTED]>**20070613144505]
[FIX #1424: x86_64 NCG generated wrong code for foreign call with >8 double args
Simon Marlow <[EMAIL PROTECTED]>**20070613142431
 I guess we have a missing test... I'll add one
]
[another fix for -hb: we appear to be freeing the hash table and arena twice
Simon Marlow <[EMAIL PROTECTED]>**20070613111552]
[FIX #1418 (partially)
Simon Marlow <[EMAIL PROTECTED]>**20070613102928
 When the con_desc field of an info table was made into a relative
 reference, this had the side effect of making the profiling fields
(closure_desc and closure_type) also relative, but only when compiling
 via C, and the heap profiler was still treating them as absolute,
 leading to crashes when profiling with -hd or -hy.

 This patch fixes up the story to be consistent: these fields really
 should be relative (otherwise we couldn't make shared versions of the
 profiling libraries), so I've made them relative and fixed up the RTS
 to know about this.
]
[should be using GET_CON_DESC() to get the constructor name
Simon Marlow <[EMAIL PROTECTED]>**20070613095201]
[warning police
Simon Marlow <[EMAIL PROTECTED]>**20070613095144]
[Use $(if...) to get lazy tests instead of if..endif in a few places
Simon Marlow <[EMAIL PROTECTED]>**20070613085138
 This means it should be possible to set GhcUnregisterised=YES in
 build.mk and the rest of the settings should follow automatically
 (GhcWithNativeCodeGen, SplitObjs, GhcWithSMP).
]
[TAG 2007-06-12
Ian Lynagh <[EMAIL PROTECTED]>**20070612213440]
Patch bundle hash:
9677c93143a2b339c5e095cb7d5afec1997dfdbd
_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to