Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
What's new
10
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Open sidebar
Shayne Fletcher
Glasgow Haskell Compiler
Commits
60ee7636
Commit
60ee7636
authored
Jul 20, 2012
by
Simon Peyton Jones
Browse files
Options
Browse Files
Download
Plain Diff
Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
parents
0b20ae91
a0ba88be
Changes
123
Expand all
Hide whitespace changes
Inline
Side-by-side
Showing
123 changed files
with
3265 additions
and
2663 deletions
+3265
-2663
compiler/basicTypes/Literal.lhs
compiler/basicTypes/Literal.lhs
+5
-4
compiler/basicTypes/Module.lhs
compiler/basicTypes/Module.lhs
+2
-2
compiler/basicTypes/Name.lhs
compiler/basicTypes/Name.lhs
+1
-1
compiler/basicTypes/OccName.lhs
compiler/basicTypes/OccName.lhs
+1
-1
compiler/basicTypes/Unique.lhs
compiler/basicTypes/Unique.lhs
+81
-88
compiler/cmm/BlockId.hs
compiler/cmm/BlockId.hs
+1
-0
compiler/cmm/Cmm.hs
compiler/cmm/Cmm.hs
+0
-5
compiler/cmm/CmmBuildInfoTables.hs
compiler/cmm/CmmBuildInfoTables.hs
+0
-4
compiler/cmm/CmmLayoutStack.hs
compiler/cmm/CmmLayoutStack.hs
+0
-3
compiler/cmm/CmmLint.hs
compiler/cmm/CmmLint.hs
+0
-3
compiler/cmm/CmmNode.hs
compiler/cmm/CmmNode.hs
+0
-6
compiler/cmm/CmmProcPoint.hs
compiler/cmm/CmmProcPoint.hs
+0
-3
compiler/cmm/CmmUtils.hs
compiler/cmm/CmmUtils.hs
+0
-5
compiler/cmm/Hoopl.hs
compiler/cmm/Hoopl.hs
+0
-3
compiler/cmm/Hoopl/Dataflow.hs
compiler/cmm/Hoopl/Dataflow.hs
+0
-7
compiler/cmm/OldPprCmm.hs
compiler/cmm/OldPprCmm.hs
+1
-0
compiler/cmm/PprC.hs
compiler/cmm/PprC.hs
+137
-144
compiler/cmm/PprCmm.hs
compiler/cmm/PprCmm.hs
+1
-0
compiler/cmm/PprCmmDecl.hs
compiler/cmm/PprCmmDecl.hs
+1
-0
compiler/cmm/PprCmmExpr.hs
compiler/cmm/PprCmmExpr.hs
+1
-0
compiler/codeGen/CgCon.lhs
compiler/codeGen/CgCon.lhs
+9
-8
compiler/codeGen/CgHeapery.lhs
compiler/codeGen/CgHeapery.lhs
+242
-249
compiler/codeGen/CgUtils.hs
compiler/codeGen/CgUtils.hs
+1
-2
compiler/codeGen/StgCmmCon.hs
compiler/codeGen/StgCmmCon.hs
+9
-9
compiler/codeGen/StgCmmEnv.hs
compiler/codeGen/StgCmmEnv.hs
+2
-4
compiler/codeGen/StgCmmUtils.hs
compiler/codeGen/StgCmmUtils.hs
+1
-1
compiler/coreSyn/CoreLint.lhs
compiler/coreSyn/CoreLint.lhs
+0
-2
compiler/coreSyn/CoreUnfold.lhs
compiler/coreSyn/CoreUnfold.lhs
+1
-1
compiler/coreSyn/ExternalCore.lhs
compiler/coreSyn/ExternalCore.lhs
+3
-1
compiler/coreSyn/MkCore.lhs
compiler/coreSyn/MkCore.lhs
+2
-2
compiler/coreSyn/MkExternalCore.lhs
compiler/coreSyn/MkExternalCore.lhs
+1
-1
compiler/coreSyn/PprCore.lhs
compiler/coreSyn/PprCore.lhs
+1
-0
compiler/coreSyn/PprExternalCore.lhs
compiler/coreSyn/PprExternalCore.lhs
+4
-1
compiler/deSugar/Check.lhs
compiler/deSugar/Check.lhs
+1
-1
compiler/deSugar/DsBinds.lhs
compiler/deSugar/DsBinds.lhs
+1
-1
compiler/deSugar/DsForeign.lhs
compiler/deSugar/DsForeign.lhs
+4
-1
compiler/deSugar/MatchLit.lhs
compiler/deSugar/MatchLit.lhs
+7
-3
compiler/ghc.cabal.in
compiler/ghc.cabal.in
+1
-2
compiler/ghci/ByteCodeGen.lhs
compiler/ghci/ByteCodeGen.lhs
+1
-1
compiler/ghci/ByteCodeLink.lhs
compiler/ghci/ByteCodeLink.lhs
+4
-4
compiler/hsSyn/Convert.lhs
compiler/hsSyn/Convert.lhs
+1
-1
compiler/hsSyn/HsLit.lhs
compiler/hsSyn/HsLit.lhs
+2
-2
compiler/hsSyn/HsSyn.lhs
compiler/hsSyn/HsSyn.lhs
+1
-0
compiler/iface/BinIface.hs
compiler/iface/BinIface.hs
+1
-0
compiler/iface/FlagChecker.hs
compiler/iface/FlagChecker.hs
+2
-2
compiler/iface/LoadIface.lhs
compiler/iface/LoadIface.lhs
+1
-0
compiler/main/DriverPipeline.hs
compiler/main/DriverPipeline.hs
+3
-3
compiler/main/DynFlags.hs
compiler/main/DynFlags.hs
+73
-13
compiler/main/ErrUtils.lhs
compiler/main/ErrUtils.lhs
+12
-3
compiler/main/InteractiveEval.hs
compiler/main/InteractiveEval.hs
+0
-4
compiler/main/StaticFlagParser.hs
compiler/main/StaticFlagParser.hs
+0
-11
compiler/main/StaticFlags.hs
compiler/main/StaticFlags.hs
+0
-9
compiler/main/SysTools.lhs
compiler/main/SysTools.lhs
+6
-15
compiler/nativeGen/AsmCodeGen.lhs
compiler/nativeGen/AsmCodeGen.lhs
+12
-13
compiler/nativeGen/PIC.hs
compiler/nativeGen/PIC.hs
+32
-32
compiler/nativeGen/PPC/CodeGen.hs
compiler/nativeGen/PPC/CodeGen.hs
+10
-9
compiler/nativeGen/PPC/Ppr.hs
compiler/nativeGen/PPC/Ppr.hs
+1
-0
compiler/nativeGen/PprBase.hs
compiler/nativeGen/PprBase.hs
+0
-5
compiler/nativeGen/RegAlloc/Graph/Main.hs
compiler/nativeGen/RegAlloc/Graph/Main.hs
+0
-1
compiler/nativeGen/RegAlloc/Graph/SpillClean.hs
compiler/nativeGen/RegAlloc/Graph/SpillClean.hs
+7
-1
compiler/nativeGen/RegAlloc/Linear/State.hs
compiler/nativeGen/RegAlloc/Linear/State.hs
+1
-0
compiler/nativeGen/SPARC/CodeGen.hs
compiler/nativeGen/SPARC/CodeGen.hs
+9
-8
compiler/nativeGen/SPARC/Ppr.hs
compiler/nativeGen/SPARC/Ppr.hs
+384
-388
compiler/nativeGen/X86/CodeGen.hs
compiler/nativeGen/X86/CodeGen.hs
+13
-11
compiler/nativeGen/X86/Ppr.hs
compiler/nativeGen/X86/Ppr.hs
+335
-327
compiler/parser/Lexer.x
compiler/parser/Lexer.x
+3
-5
compiler/parser/ParserCore.y
compiler/parser/ParserCore.y
+1
-1
compiler/prelude/PrelRules.lhs
compiler/prelude/PrelRules.lhs
+15
-11
compiler/profiling/CostCentre.lhs
compiler/profiling/CostCentre.lhs
+1
-1
compiler/rename/RnEnv.lhs
compiler/rename/RnEnv.lhs
+401
-408
compiler/rename/RnExpr.lhs
compiler/rename/RnExpr.lhs
+1
-1
compiler/simplCore/FloatOut.lhs
compiler/simplCore/FloatOut.lhs
+1
-0
compiler/simplCore/SimplCore.lhs
compiler/simplCore/SimplCore.lhs
+1
-1
compiler/simplCore/Simplify.lhs
compiler/simplCore/Simplify.lhs
+10
-9
compiler/specialise/Rules.lhs
compiler/specialise/Rules.lhs
+1
-1
compiler/typecheck/TcCanonical.lhs
compiler/typecheck/TcCanonical.lhs
+19
-19
compiler/typecheck/TcEnv.lhs
compiler/typecheck/TcEnv.lhs
+1
-0
compiler/typecheck/TcInstDcls.lhs
compiler/typecheck/TcInstDcls.lhs
+1
-1
compiler/typecheck/TcRnMonad.lhs
compiler/typecheck/TcRnMonad.lhs
+1
-0
compiler/typecheck/TcSMonad.lhs
compiler/typecheck/TcSMonad.lhs
+95
-60
compiler/typecheck/TcSimplify.lhs
compiler/typecheck/TcSimplify.lhs
+184
-120
compiler/typecheck/TcSplice.lhs
compiler/typecheck/TcSplice.lhs
+1
-0
compiler/typecheck/TcTyClsDecls.lhs
compiler/typecheck/TcTyClsDecls.lhs
+1
-1
compiler/types/Type.lhs
compiler/types/Type.lhs
+1
-0
compiler/utils/Binary.hs
compiler/utils/Binary.hs
+17
-18
compiler/utils/BufWrite.hs
compiler/utils/BufWrite.hs
+9
-2
compiler/utils/FastString.lhs
compiler/utils/FastString.lhs
+171
-151
compiler/utils/Fingerprint.hsc
compiler/utils/Fingerprint.hsc
+2
-68
compiler/utils/Outputable.lhs
compiler/utils/Outputable.lhs
+15
-18
compiler/utils/Panic.lhs
compiler/utils/Panic.lhs
+0
-6
compiler/utils/Pretty.lhs
compiler/utils/Pretty.lhs
+7
-5
compiler/utils/StringBuffer.lhs
compiler/utils/StringBuffer.lhs
+1
-5
compiler/utils/md5.c
compiler/utils/md5.c
+0
-241
configure.ac
configure.ac
+3
-3
docs/users_guide/flags.xml
docs/users_guide/flags.xml
+1
-1
ghc.mk
ghc.mk
+3
-3
ghc/Main.hs
ghc/Main.hs
+5
-7
ghc/ghc-cross.wrapper
ghc/ghc-cross.wrapper
+1
-0
includes/Cmm.h
includes/Cmm.h
+2
-2
includes/mkDerivedConstants.cross.awk
includes/mkDerivedConstants.cross.awk
+350
-0
includes/mkSizeMacros.cross.awk
includes/mkSizeMacros.cross.awk
+82
-0
includes/rts/EventLogFormat.h
includes/rts/EventLogFormat.h
+10
-3
includes/rts/OSThreads.h
includes/rts/OSThreads.h
+25
-2
includes/rts/prof/CCS.h
includes/rts/prof/CCS.h
+2
-2
includes/stg/Regs.h
includes/stg/Regs.h
+5
-5
libraries/bin-package-db/bin-package-db.cabal
libraries/bin-package-db/bin-package-db.cabal
+1
-1
libraries/tarballs/time-1.4.0.1.tar.gz
libraries/tarballs/time-1.4.0.1.tar.gz
+0
-0
rts/RtsAPI.c
rts/RtsAPI.c
+15
-0
rts/RtsProbes.d
rts/RtsProbes.d
+12
-8
rts/Schedule.c
rts/Schedule.c
+12
-1
rts/Task.c
rts/Task.c
+16
-1
rts/Task.h
rts/Task.h
+42
-1
rts/Trace.c
rts/Trace.c
+46
-0
rts/Trace.h
rts/Trace.h
+67
-22
rts/eventlog/EventLog.c
rts/eventlog/EventLog.c
+83
-1
rts/eventlog/EventLog.h
rts/eventlog/EventLog.h
+18
-8
rts/posix/OSThreads.c
rts/posix/OSThreads.c
+30
-0
rts/win32/OSThreads.c
rts/win32/OSThreads.c
+7
-1
rules/cross-compiling.mk
rules/cross-compiling.mk
+24
-0
utils/genapply/GenApply.hs
utils/genapply/GenApply.hs
+3
-3
utils/ghc-cabal/ghc-cabal.cabal
utils/ghc-cabal/ghc-cabal.cabal
+1
-1
utils/ghc-pkg/Main.hs
utils/ghc-pkg/Main.hs
+2
-0
utils/hpc/hpc-bin.cabal
utils/hpc/hpc-bin.cabal
+3
-3
No files found.
compiler/basicTypes/Literal.lhs
View file @
60ee7636
...
...
@@ -84,7 +84,7 @@ data Literal
-- First the primitive guys
MachChar Char -- ^ @Char#@ - at least 31 bits. Create with 'mkMachChar'
| MachStr Fast
String
-- ^ A string-literal: stored and emitted
| MachStr Fast
Bytes
-- ^ A string-literal: stored and emitted
-- UTF-8 encoded, we'll arrange to decode it
-- at runtime. Also emitted with a @'\0'@
-- terminator. Create with 'mkMachString'
...
...
@@ -248,7 +248,8 @@ mkMachChar = MachChar
-- | Creates a 'Literal' of type @Addr#@, which is appropriate for passing to
-- e.g. some of the \"error\" functions in GHC.Err such as @GHC.Err.runtimeError@
mkMachString :: String -> Literal
mkMachString s = MachStr (mkFastString s) -- stored UTF-8 encoded
-- stored UTF-8 encoded
mkMachString s = MachStr (fastStringToFastBytes $ mkFastString s)
mkLitInteger :: Integer -> Type -> Literal
mkLitInteger = LitInteger
...
...
@@ -436,7 +437,7 @@ pprLiteral :: (SDoc -> SDoc) -> Literal -> SDoc
-- to wrap parens around literals that occur in
-- a context requiring an atomic thing
pprLiteral _ (MachChar ch) = pprHsChar ch
pprLiteral _ (MachStr s) = pprHs
String
s
pprLiteral _ (MachStr s) = pprHs
Bytes
s
pprLiteral _ (MachInt i) = pprIntVal i
pprLiteral _ (MachDouble d) = double (fromRat d)
pprLiteral _ (MachNullAddr) = ptext (sLit "__NULL")
...
...
@@ -469,7 +470,7 @@ Hash values should be zero or a positive integer. No negatives please.
\begin{code}
hashLiteral :: Literal -> Int
hashLiteral (MachChar c) = ord c + 1000 -- Keep it out of range of common ints
hashLiteral (MachStr s) = hashF
S
s
hashLiteral (MachStr s) = hashF
B
s
hashLiteral (MachNullAddr) = 0
hashLiteral (MachInt i) = hashInteger i
hashLiteral (MachInt64 i) = hashInteger i
...
...
compiler/basicTypes/Module.lhs
View file @
60ee7636
...
...
@@ -191,7 +191,7 @@ pprModuleName :: ModuleName -> SDoc
pprModuleName (ModuleName nm) =
getPprStyle $ \ sty ->
if codeStyle sty
then
f
text (zEncodeFS nm)
then
z
text (zEncodeFS nm)
else ftext nm
moduleNameFS :: ModuleName -> FastString
...
...
@@ -271,7 +271,7 @@ pprPackagePrefix p mod = getPprStyle doc
| codeStyle sty =
if p == mainPackageId
then empty -- never qualify the main package in code
else
f
text (zEncodeFS (packageIdFS p)) <> char '_'
else
z
text (zEncodeFS (packageIdFS p)) <> char '_'
| qualModule sty mod = ftext (packageIdFS (modulePackageId mod)) <> char ':'
-- the PrintUnqualified tells us which modules have to
-- be qualified with package names
...
...
compiler/basicTypes/Name.lhs
View file @
60ee7636
...
...
@@ -514,7 +514,7 @@ ppr_occ_name occ = ftext (occNameFS occ)
-- In code style, we Z-encode the strings. The results of Z-encoding each FastString are
-- cached behind the scenes in the FastString implementation.
ppr_z_occ_name :: OccName -> SDoc
ppr_z_occ_name occ =
f
text (zEncodeFS (occNameFS occ))
ppr_z_occ_name occ =
z
text (zEncodeFS (occNameFS occ))
-- Prints (if mod information is available) "Defined at <loc>" or
-- "Defined in <mod>" information for a Name.
...
...
compiler/basicTypes/OccName.lhs
View file @
60ee7636
...
...
@@ -265,7 +265,7 @@ pprOccName :: OccName -> SDoc
pprOccName (OccName sp occ)
= getPprStyle $ \ sty ->
if codeStyle sty
then
f
text (zEncodeFS occ)
then
z
text (zEncodeFS occ)
else pp_occ <> pp_debug sty
where
pp_debug sty | debugStyle sty = braces (pprNameSpaceBrief sp)
...
...
compiler/basicTypes/Unique.lhs
View file @
60ee7636
...
...
@@ -18,50 +18,43 @@ Haskell).
\begin{code}
{-# LANGUAGE BangPatterns #-}
{-# OPTIONS -fno-warn-tabs #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and
-- detab the module (please do the detabbing in a separate patch). See
-- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
-- for details
module Unique (
-- * Main data types
Unique, Uniquable(..),
-- ** Constructors, desctructors and operations on 'Unique's
hasKey,
Unique, Uniquable(..),
-- ** Constructors, desctructors and operations on 'Unique's
hasKey,
pprUnique,
pprUnique,
mkUniqueGrimily,
-- Used in UniqSupply only!
getKey, getKeyFastInt,
-- Used in Var, UniqFM, Name only!
mkUniqueGrimily,
-- Used in UniqSupply only!
getKey, getKeyFastInt,
-- Used in Var, UniqFM, Name only!
mkUnique, unpkUnique, -- Used in BinIface only
incrUnique,
-- Used for renumbering
deriveUnique,
-- Ditto
newTagUnique,
-- Used in CgCase
initTyVarUnique,
incrUnique,
-- Used for renumbering
deriveUnique,
-- Ditto
newTagUnique,
-- Used in CgCase
initTyVarUnique,
-- ** Making built-in uniques
-- ** Making built-in uniques
-- now all the built-in Uniques (and functions to make them)
-- [the Oh-So-Wonderful Haskell module system wins again...]
mkAlphaTyVarUnique,
mkPrimOpIdUnique,
mkTupleTyConUnique, mkTupleDataConUnique,
mkPreludeMiscIdUnique, mkPreludeDataConUnique,
mkPreludeTyConUnique, mkPreludeClassUnique,
mkPArrDataConUnique,
-- now all the built-in Uniques (and functions to make them)
-- [the Oh-So-Wonderful Haskell module system wins again...]
mkAlphaTyVarUnique,
mkPrimOpIdUnique,
mkTupleTyConUnique, mkTupleDataConUnique,
mkPreludeMiscIdUnique, mkPreludeDataConUnique,
mkPreludeTyConUnique, mkPreludeClassUnique,
mkPArrDataConUnique,
mkVarOccUnique, mkDataOccUnique, mkTvOccUnique, mkTcOccUnique,
mkRegSingleUnique, mkRegPairUnique, mkRegClassUnique, mkRegSubUnique,
mkCostCentreUnique,
mkBuiltinUnique,
mkBuiltinUnique,
mkPseudoUniqueD,
mkPseudoUniqueE,
mkPseudoUniqueH
mkPseudoUniqueE,
mkPseudoUniqueH
) where
#include "HsVersions.h"
...
...
@@ -79,13 +72,13 @@ import GHC.Exts (indexCharOffAddr#, Char(..))
#else
import Data.Array
#endif
import Data.Char
( chr, ord )
import Data.Char
( chr, ord )
\end{code}
%************************************************************************
%*
*
%*
*
\subsection[Unique-type]{@Unique@ type and operations}
%*
*
%*
*
%************************************************************************
The @Chars@ are ``tag letters'' that identify the @UniqueSupply@.
...
...
@@ -104,15 +97,15 @@ Now come the functions which construct uniques from their pieces, and vice versa
The stuff about unique *supplies* is handled further down this module.
\begin{code}
unpkUnique
:: Unique -> (Char, Int)
-- The reverse
unpkUnique
:: Unique -> (Char, Int)
-- The reverse
mkUniqueGrimily :: Int -> Unique
-- A trap-door for UniqSupply
getKey
:: Unique -> Int
-- for Var
getKeyFastInt
:: Unique -> FastInt
-- for Var
mkUniqueGrimily :: Int -> Unique
-- A trap-door for UniqSupply
getKey
:: Unique -> Int
-- for Var
getKeyFastInt
:: Unique -> FastInt
-- for Var
incrUnique
:: Unique -> Unique
deriveUnique
:: Unique -> Int -> Unique
newTagUnique
:: Unique -> Char -> Unique
incrUnique
:: Unique -> Unique
deriveUnique
:: Unique -> Int -> Unique
newTagUnique
:: Unique -> Char -> Unique
\end{code}
...
...
@@ -139,8 +132,8 @@ newTagUnique u c = mkUnique c i where (_,i) = unpkUnique u
-- and as long as the Char fits in 8 bits, which we assume anyway!
mkUnique :: Char -> Int -> Unique
-- Builds a unique from pieces
-- NOT EXPORTED, so that we can see all the Chars that
mkUnique :: Char -> Int -> Unique
-- Builds a unique from pieces
-- NOT EXPORTED, so that we can see all the Chars that
-- are used in this one module
mkUnique c i
= MkUnique (tag `bitOrFastInt` bits)
...
...
@@ -150,10 +143,10 @@ mkUnique c i
unpkUnique (MkUnique u)
= let
-- as long as the Char may have its eighth bit set, we
-- really do need the logical right-shift here!
tag = cBox (fastChr (u `shiftRLFastInt` _ILIT(24)))
i = iBox (u `bitAndFastInt` _ILIT(16777215){-``0x00ffffff''-})
-- as long as the Char may have its eighth bit set, we
-- really do need the logical right-shift here!
tag = cBox (fastChr (u `shiftRLFastInt` _ILIT(24)))
i = iBox (u `bitAndFastInt` _ILIT(16777215){-``0x00ffffff''-})
in
(tag, i)
\end{code}
...
...
@@ -161,9 +154,9 @@ unpkUnique (MkUnique u)
%************************************************************************
%*
*
%*
*
\subsection[Uniquable-class]{The @Uniquable@ class}
%*
*
%*
*
%************************************************************************
\begin{code}
...
...
@@ -171,8 +164,8 @@ unpkUnique (MkUnique u)
class Uniquable a where
getUnique :: a -> Unique
hasKey
:: Uniquable a => a -> Unique -> Bool
x `hasKey` k
= getUnique x == k
hasKey
:: Uniquable a => a -> Unique -> Bool
x `hasKey` k
= getUnique x == k
instance Uniquable FastString where
getUnique fs = mkUniqueGrimily (iBox (uniqueOfFS fs))
...
...
@@ -183,9 +176,9 @@ instance Uniquable Int where
%************************************************************************
%*
*
%*
*
\subsection[Unique-instances]{Instance declarations for @Unique@}
%*
*
%*
*
%************************************************************************
And the whole point (besides uniqueness) is fast equality. We don't
...
...
@@ -243,9 +236,9 @@ instance Show Unique where
\end{code}
%************************************************************************
%*
*
%*
*
\subsection[Utils-base62]{Base-62 numbers}
%*
*
%*
*
%************************************************************************
A character-stingy way to read/write numbers (notably Uniques).
...
...
@@ -258,12 +251,12 @@ iToBase62 n_
= ASSERT(n_ >= 0) go (iUnbox n_) ""
where
go n cs | n <# _ILIT(62)
= case chooseChar62 n of { c -> c `seq` (c : cs) }
| otherwise
=
case (quotRem (iBox n) 62) of { (q_, r_) ->
= case chooseChar62 n of { c -> c `seq` (c : cs) }
| otherwise
=
case (quotRem (iBox n) 62) of { (q_, r_) ->
case iUnbox q_ of { q -> case iUnbox r_ of { r ->
case (chooseChar62 r) of { c -> c `seq`
(go q (c : cs)) }}}}
case (chooseChar62 r) of { c -> c `seq`
(go q (c : cs)) }}}}
chooseChar62 :: FastInt -> Char
{-# INLINE chooseChar62 #-}
...
...
@@ -279,29 +272,29 @@ iToBase62 n_
\end{code}
%************************************************************************
%*
*
%*
*
\subsection[Uniques-prelude]{@Uniques@ for wired-in Prelude things}
%*
*
%*
*
%************************************************************************
Allocation of unique supply characters:
v,t,u : for renumbering value-, type- and usage- vars.
B: builtin
C-E: pseudo uniques
(used in native-code generator)
X: uniques derived by deriveUnique
_: unifiable tyvars (above)
0-9: prelude things below
(no numbers left any more..)
:: (prelude) parallel array data constructors
other a-z: lower case chars for unique supplies. Used so far:
d
desugarer
f
AbsC flattener
g
SimplStg
n
Native codegen
r
Hsc name cache
s
simplifier
v,t,u : for renumbering value-, type- and usage- vars.
B: builtin
C-E: pseudo uniques
(used in native-code generator)
X: uniques derived by deriveUnique
_: unifiable tyvars (above)
0-9: prelude things below
(no numbers left any more..)
:: (prelude) parallel array data constructors
other a-z: lower case chars for unique supplies. Used so far:
d
desugarer
f
AbsC flattener
g
SimplStg
n
Native codegen
r
Hsc name cache
s
simplifier
\begin{code}
mkAlphaTyVarUnique :: Int -> Unique
...
...
@@ -322,10 +315,10 @@ mkPreludeClassUnique i = mkUnique '2' i
-- The first is for the tycon itself; the latter two
-- are for the generic to/from Ids. See TysWiredIn.mk_tc_gen_info.
mkPreludeTyConUnique i
= mkUnique '3' (3*i)
mkTupleTyConUnique BoxedTuple a
= mkUnique '4' (3*a)
mkTupleTyConUnique UnboxedTuple a
= mkUnique '5' (3*a)
mkTupleTyConUnique ConstraintTuple a
= mkUnique 'k' (3*a)
mkPreludeTyConUnique i
= mkUnique '3' (3*i)
mkTupleTyConUnique BoxedTuple a
= mkUnique '4' (3*a)
mkTupleTyConUnique UnboxedTuple a
= mkUnique '5' (3*a)
mkTupleTyConUnique ConstraintTuple a
= mkUnique 'k' (3*a)
-- Data constructor keys occupy *two* slots. The first is used for the
-- data constructor itself and its wrapper function (the function that
...
...
@@ -333,16 +326,16 @@ mkTupleTyConUnique ConstraintTuple a = mkUnique 'k' (3*a)
-- used for the worker function (the function that builds the constructor
-- representation).
mkPreludeDataConUnique i
= mkUnique '6' (2*i)
-- Must be alphabetic
mkTupleDataConUnique BoxedTuple a = mkUnique '7' (2*a)
-- ditto (*may* be used in C labels)
mkPreludeDataConUnique i
= mkUnique '6' (2*i)
-- Must be alphabetic
mkTupleDataConUnique BoxedTuple a = mkUnique '7' (2*a)
-- ditto (*may* be used in C labels)
mkTupleDataConUnique UnboxedTuple a = mkUnique '8' (2*a)
mkTupleDataConUnique ConstraintTuple a = mkUnique 'h' (2*a)
mkPrimOpIdUnique op = mkUnique '9' op
mkPreludeMiscIdUnique i = mkUnique '0' i
-- No numbers left anymore, so I pick something different for the character tag
mkPArrDataConUnique a
= mkUnique ':' (2*a)
-- No numbers left anymore, so I pick something different for the character tag
mkPArrDataConUnique a
= mkUnique ':' (2*a)
-- The "tyvar uniques" print specially nicely: a, b, c, etc.
-- See pprUnique for details
...
...
@@ -371,7 +364,7 @@ mkVarOccUnique, mkDataOccUnique, mkTvOccUnique, mkTcOccUnique :: FastString -> U
-- See Note [The Unique of an OccName] in OccName
mkVarOccUnique fs = mkUnique 'i' (iBox (uniqueOfFS fs))
mkDataOccUnique fs = mkUnique 'd' (iBox (uniqueOfFS fs))
mkTvOccUnique
fs = mkUnique 'v' (iBox (uniqueOfFS fs))
mkTcOccUnique
fs = mkUnique 'c' (iBox (uniqueOfFS fs))
mkTvOccUnique
fs = mkUnique 'v' (iBox (uniqueOfFS fs))
mkTcOccUnique
fs = mkUnique 'c' (iBox (uniqueOfFS fs))
\end{code}
compiler/cmm/BlockId.hs
View file @
60ee7636
{- BlockId module should probably go away completely, being superseded by Label -}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module
BlockId
(
BlockId
,
mkBlockId
-- ToDo: BlockId should be abstract, but it isn't yet
,
BlockSet
,
BlockEnv
...
...
compiler/cmm/Cmm.hs
View file @
60ee7636
-- Cmm representations using Hoopl's Graph CmmNode e x.
{-# LANGUAGE GADTs #-}
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
#
if
__GLASGOW_HASKELL__
>=
703
-- GHC 7.0.1 improved incomplete pattern warnings with GADTs
{-# OPTIONS_GHC -fwarn-incomplete-patterns #-}
#
endif
module
Cmm
(
-- * Cmm top-level datatypes
...
...
compiler/cmm/CmmBuildInfoTables.hs
View file @
60ee7636
...
...
@@ -48,11 +48,7 @@ import qualified Data.Set as Set
import
Control.Monad
foldSet
::
(
a
->
b
->
b
)
->
b
->
Set
a
->
b
#
if
__GLASGOW_HASKELL__
<
704
foldSet
=
Set
.
fold
#
else
foldSet
=
Set
.
foldr
#
endif
----------------------------------------------------------------
-- Building InfoTables
...
...
compiler/cmm/CmmLayoutStack.hs
View file @
60ee7636
{-# LANGUAGE RecordWildCards, GADTs #-}
#
if
__GLASGOW_HASKELL__
<
701
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
#
endif
module
CmmLayoutStack
(
cmmLayoutStack
,
setInfoTableStackMap
)
where
...
...
compiler/cmm/CmmLint.hs
View file @
60ee7636
...
...
@@ -6,9 +6,6 @@
--
-----------------------------------------------------------------------------
{-# LANGUAGE GADTs #-}
#
if
__GLASGOW_HASKELL__
<
701
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
#
endif
module
CmmLint
(
cmmLint
,
cmmLintGraph
)
where
...
...
compiler/cmm/CmmNode.hs
View file @
60ee7636
...
...
@@ -8,12 +8,6 @@
-- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
-- for details
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
#
if
__GLASGOW_HASKELL__
>=
703
-- GHC 7.0.1 improved incomplete pattern warnings with GADTs
{-# OPTIONS_GHC -fwarn-incomplete-patterns #-}
#
endif
module
CmmNode
(
CmmNode
(
..
),
ForeignHint
(
..
),
CmmFormal
,
CmmActual
,
UpdFrameOffset
,
Convention
(
..
),
ForeignConvention
(
..
),
ForeignTarget
(
..
),
...
...
compiler/cmm/CmmProcPoint.hs
View file @
60ee7636
{-# LANGUAGE GADTs, DisambiguateRecordFields #-}
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
#
if
__GLASGOW_HASKELL__
<
701
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
#
endif
module
CmmProcPoint
(
ProcPointSet
,
Status
(
..
)
...
...
compiler/cmm/CmmUtils.hs
View file @
60ee7636
...
...
@@ -8,11 +8,6 @@
{-# OPTIONS_GHC -fno-warn-deprecations #-}
-- Warnings from deprecated blockToNodeList
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
#
if
__GLASGOW_HASKELL__
>=
703
-- GHC 7.0.1 improved incomplete pattern warnings with GADTs
{-# OPTIONS_GHC -fwarn-incomplete-patterns #-}
#
endif
-----------------------------------------------------------------------------
...
...
compiler/cmm/Hoopl.hs
View file @
60ee7636
#
if
__GLASGOW_HASKELL__
<
701
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}
#
endif
module
Hoopl
(
module
Compiler
.
Hoopl
,
module
Hoopl
.
Dataflow
,
...
...
compiler/cmm/Hoopl/Dataflow.hs
View file @
60ee7636
...
...
@@ -10,15 +10,8 @@
--
{-# LANGUAGE RankNTypes, ScopedTypeVariables, GADTs, EmptyDataDecls, PatternGuards, TypeFamilies, MultiParamTypeClasses #-}
#
if
__GLASGOW_HASKELL__
>=
703
{-# OPTIONS_GHC -fprof-auto-top #-}
#
endif
#
if
__GLASGOW_HASKELL__
>=
701
{-# LANGUAGE Trustworthy #-}
#
endif
#
if
__GLASGOW_HASKELL__
<
701
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
#
endif
module
Hoopl.Dataflow
(
DataflowLattice
(
..
),
OldFact
(
..
),
NewFact
(
..
),
Fact
,
mkFactBase
...
...
compiler/cmm/OldPprCmm.hs
View file @
60ee7636
...
...
@@ -32,6 +32,7 @@
-- A useful example pass over Cmm is in nativeGen/MachCodeGen.hs
--
{-# OPTIONS_GHC -fno-warn-orphans #-}
module
OldPprCmm
(
pprStmt
,
module
PprCmmDecl
,
...
...
compiler/cmm/PprC.hs
View file @
60ee7636
This diff is collapsed.
Click to expand it.
compiler/cmm/PprCmm.hs
View file @
60ee7636
...
...
@@ -30,6 +30,7 @@
--
-- A useful example pass over Cmm is in nativeGen/MachCodeGen.hs
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE GADTs, TypeFamilies, FlexibleContexts #-}
module
PprCmm
(
module
PprCmmDecl
...
...
compiler/cmm/PprCmmDecl.hs
View file @
60ee7636
...
...
@@ -32,6 +32,7 @@
-- A useful example pass over Cmm is in nativeGen/MachCodeGen.hs
--
{-# OPTIONS_GHC -fno-warn-orphans #-}
module
PprCmmDecl
(
writeCmms
,
pprCmms
,
pprCmmGroup
,
pprSection
,
pprStatic
)
...
...
compiler/cmm/PprCmmExpr.hs
View file @
60ee7636
...
...
@@ -32,6 +32,7 @@
-- A useful example pass over Cmm is in nativeGen/MachCodeGen.hs
--
{-# OPTIONS_GHC -fno-warn-orphans #-}
module
PprCmmExpr
(
pprExpr
,
pprLit
,
pprExpr9
{-only to import in OldPprCmm. When it dies, remove the export -}
...
...
compiler/codeGen/CgCon.lhs
View file @
60ee7636
...
...
@@ -119,9 +119,10 @@ buildDynCon :: Id -- Name of the thing to which this constr will
-> FCode CgIdInfo -- Return details about how to find it
buildDynCon binder ccs con args
= do dflags <- getDynFlags
buildDynCon' (targetPlatform dflags) binder ccs con args
buildDynCon'
dflags
(targetPlatform dflags) binder ccs con args
buildDynCon' :: Platform
buildDynCon' :: DynFlags
-> Platform
-> Id
-> CostCentreStack
-> DataCon
...
...
@@ -148,7 +149,7 @@ which have exclusively size-zero (VoidRep) args, we generate no code
at all.
\begin{code}
buildDynCon' _ binder _ con []
buildDynCon' _
_
binder _ con []
= returnFC (taggedStableIdInfo binder
(mkLblExpr (mkClosureLabel (dataConName con)
(idCafInfo binder)))
...
...
@@ -183,9 +184,9 @@ because they don't support cross package data references well.
\begin{code}
buildDynCon' platform binder _ con [arg_amode]
buildDynCon'
dflags
platform binder _ con [arg_amode]
| maybeIntLikeCon con
, platformOS platform /= OSMinGW32 || not opt
_PIC
, platformOS platform /= OSMinGW32 || not
(d
opt
Opt_PIC dflags)
, (_, CmmLit (CmmInt val _)) <- arg_amode
, let val_int = (fromIntegral val) :: Int
, val_int <= mAX_INTLIKE && val_int >= mIN_INTLIKE
...
...
@@ -195,9 +196,9 @@ buildDynCon' platform binder _ con [arg_amode]
intlike_amode = CmmLit (cmmLabelOffW intlike_lbl offsetW)
; returnFC (taggedStableIdInfo binder intlike_amode (mkConLFInfo con) con) }
buildDynCon' platform binder _ con [arg_amode]
buildDynCon'
dflags
platform binder _ con [arg_amode]
| maybeCharLikeCon con
, platformOS platform /= OSMinGW32 || not opt
_PIC
, platformOS platform /= OSMinGW32 || not
(d
opt
Opt_PIC dflags)
, (_, CmmLit (CmmInt val _)) <- arg_amode
, let val_int = (fromIntegral val) :: Int
, val_int <= mAX_CHARLIKE && val_int >= mIN_CHARLIKE
...
...
@@ -212,7 +213,7 @@ buildDynCon' platform binder _ con [arg_amode]
Now the general case.
\begin{code}
buildDynCon' _ binder ccs con args
buildDynCon' _
_
binder ccs con args
= do {
; let
(closure_info, amodes_w_offsets) = layOutDynConstr con args
...
...
compiler/codeGen/CgHeapery.lhs
View file @
60ee7636
This diff is collapsed.
Click to expand it.
compiler/codeGen/CgUtils.hs
View file @
60ee7636
...
...
@@ -92,8 +92,7 @@ addIdReps ids = [(idCgRep id, id) | id <- ids]
-------------------------------------------------------------------------
cgLit
::
Literal
->
FCode
CmmLit
cgLit
(
MachStr
s
)
=
newByteStringCLit
(
bytesFS
s
)
-- not unpackFS; we want the UTF-8 byte stream.
cgLit
(
MachStr
s
)
=
newByteStringCLit
(
bytesFB
s
)
cgLit
other_lit
=
return
(
mkSimpleLit
other_lit
)
mkSimpleLit
::
Literal
->
CmmLit
...
...
compiler/codeGen/StgCmmCon.hs
View file @
60ee7636
...
...
@@ -40,7 +40,6 @@ import Literal
import
PrelInfo
import
Outputable
import
Platform
import
StaticFlags
import
Util