diff --git a/Cabal/Distribution/Simple/Compiler.hs b/Cabal/Distribution/Simple/Compiler.hs
index faad14328a2a42a86fa7925cc244693a02531988..f217d73b404b54a279acce12c97ea5237fdfcd99 100644
--- a/Cabal/Distribution/Simple/Compiler.hs
+++ b/Cabal/Distribution/Simple/Compiler.hs
@@ -53,13 +53,19 @@ module Distribution.Simple.Compiler (
         parmakeSupported,
         reexportedModulesSupported,
         renamingPackageFlagsSupported,
-        packageKeySupported
+        packageKeySupported,
+
+        -- * Support for profiling detail levels
+        ProfDetailLevel(..),
+        knownProfDetailLevels,
+        flagToProfDetailLevel,
   ) where
 
 import Distribution.Compiler
 import Distribution.Version (Version(..))
 import Distribution.Text (display)
 import Language.Haskell.Extension (Language(Haskell98), Extension)
+import Distribution.Simple.Utils (lowercase)
 
 import Control.Monad (liftM)
 import Distribution.Compat.Binary (Binary)
@@ -285,3 +291,44 @@ ghcSupported key comp =
           case M.lookup key (compilerProperties comp) of
             Just "YES" -> True
             _          -> False
+
+-- ------------------------------------------------------------
+-- * Profiling detail level
+-- ------------------------------------------------------------
+
+-- | Some compilers (notably GHC) support profiling and can instrument
+-- programs so the system can account costs to different functions. There are
+-- different levels of detail that can be used for this accounting.
+-- For compilers that do not support this notion or the particular detail
+-- levels, this is either ignored or just capped to some similar level
+-- they do support.
+--
+data ProfDetailLevel = ProfDetailNone
+                     | ProfDetailDefault
+                     | ProfDetailExportedFunctions
+                     | ProfDetailToplevelFunctions
+                     | ProfDetailAllFunctions
+                     | ProfDetailOther String
+    deriving (Eq, Generic, Read, Show)
+
+instance Binary ProfDetailLevel
+
+flagToProfDetailLevel :: String -> ProfDetailLevel
+flagToProfDetailLevel "" = ProfDetailDefault
+flagToProfDetailLevel s  =
+    case lookup (lowercase s)
+                [ (name, value)
+                | (primary, aliases, value) <- knownProfDetailLevels
+                , name <- primary : aliases ]
+      of Just value -> value
+         Nothing    -> ProfDetailOther s
+
+knownProfDetailLevels :: [(String, [String], ProfDetailLevel)]
+knownProfDetailLevels =
+  [ ("default",            [],                  ProfDetailDefault)
+  , ("none",               [],                  ProfDetailNone)
+  , ("exported-functions", ["exported"],        ProfDetailExportedFunctions)
+  , ("toplevel-functions", ["toplevel", "top"], ProfDetailToplevelFunctions)
+  , ("all-functions",      ["all"],             ProfDetailAllFunctions)
+  ]
+
diff --git a/Cabal/Distribution/Simple/Configure.hs b/Cabal/Distribution/Simple/Configure.hs
index a94df2148ef7390a3c078d5a7e336bafc8c2d78a..861f8df00aebe8c2ef07a89613eb40ef7b316944 100644
--- a/Cabal/Distribution/Simple/Configure.hs
+++ b/Cabal/Distribution/Simple/Configure.hs
@@ -52,7 +52,7 @@ import Distribution.Compiler
 import Distribution.Utils.NubList
 import Distribution.Simple.Compiler
     ( CompilerFlavor(..), Compiler(..), compilerFlavor, compilerVersion
-    , compilerInfo
+    , compilerInfo, ProfDetailLevel(..), knownProfDetailLevels
     , showCompilerId, unsupportedLanguages, unsupportedExtensions
     , PackageDB(..), PackageDBStack, reexportedModulesSupported
     , packageKeySupported, renamingPackageFlagsSupported )
@@ -345,7 +345,6 @@ configure :: (GenericPackageDescription, HookedBuildInfo)
 configure (pkg_descr0, pbi) cfg
   = do  let distPref = fromFlag (configDistPref cfg)
             buildDir' = distPref </> "build"
-            verbosity = fromFlag (configVerbosity cfg)
 
         setupMessage verbosity "Configuring" (packageId pkg_descr0)
 
@@ -682,10 +681,24 @@ configure (pkg_descr0, pbi) cfg
             ++ "is not being built. Linking will fail if any executables "
             ++ "depend on the library."
 
-        let withProf_ = fromFlagOrDefault False (configProf cfg)
-            withProfExe_ = fromFlagOrDefault withProf_ $ configProfExe cfg
-            withProfLib_ = fromFlagOrDefault withProfExe_ $ configProfLib cfg
-        when (withProfExe_ && not withProfLib_) $ warn verbosity $
+        -- The --profiling flag sets the default for both libs and exes,
+        -- but can be overidden by --library-profiling, or the old deprecated
+        -- --executable-profiling flag.
+        let profEnabledLibOnly = configProfLib cfg
+            profEnabledBoth    = fromFlagOrDefault False (configProf cfg)
+            profEnabledLib = fromFlagOrDefault profEnabledBoth profEnabledLibOnly
+            profEnabledExe = fromFlagOrDefault profEnabledBoth (configProfExe cfg)
+
+        -- The --profiling-detail and --library-profiling-detail flags behave
+        -- similarly
+        profDetailLibOnly <- checkProfDetail (configProfLibDetail cfg)
+        profDetailBoth    <- liftM (fromFlagOrDefault ProfDetailDefault)
+                                   (checkProfDetail (configProfDetail cfg))
+        let profDetailLib = fromFlagOrDefault profDetailBoth profDetailLibOnly
+            profDetailExe = profDetailBoth
+
+        when (profEnabledExe && not profEnabledLib) $
+          warn verbosity $
                "Executables will be built with profiling, but library "
             ++ "profiling is disabled. Linking will fail if any executables "
             ++ "depend on the library."
@@ -717,10 +730,12 @@ configure (pkg_descr0, pbi) cfg
                     instantiatedWith    = hole_insts,
                     withPrograms        = programsConfig''',
                     withVanillaLib      = fromFlag $ configVanillaLib cfg,
-                    withProfLib         = withProfLib_,
+                    withProfLib         = profEnabledLib,
                     withSharedLib       = withSharedLib_,
                     withDynExe          = withDynExe_,
-                    withProfExe         = withProfExe_,
+                    withProfExe         = profEnabledExe,
+                    withProfLibDetail   = profDetailLib,
+                    withProfExeDetail   = profDetailExe,
                     withOptimization    = fromFlag $ configOptimization cfg,
                     withDebugInfo       = fromFlag $ configDebugInfo cfg,
                     withGHCiLib         = fromFlagOrDefault ghciLibByDefault $
@@ -768,6 +783,8 @@ configure (pkg_descr0, pbi) cfg
         return lbi
 
     where
+      verbosity = fromFlag (configVerbosity cfg)
+
       addExtraIncludeLibDirs pkg_descr =
           let extraBi = mempty { extraLibDirs = configExtraLibDirs cfg
                                , PD.includeDirs = configExtraIncludeDirs cfg}
@@ -779,6 +796,15 @@ configure (pkg_descr0, pbi) cfg
                       , executables = modifyExecutable  `map`
                                       executables pkg_descr}
 
+      checkProfDetail (Flag (ProfDetailOther other)) = do
+        warn verbosity $
+             "Unknown profiling detail level '" ++ other
+          ++ "', using default.\n"
+          ++ "The profiling detail levels are: " ++ intercalate ", "
+             [ name | (name, _, _) <- knownProfDetailLevels ]
+        return (Flag ProfDetailDefault)
+      checkProfDetail other = return other
+
 mkProgramsConfig :: ConfigFlags -> ProgramConfiguration -> ProgramConfiguration
 mkProgramsConfig cfg initialProgramsConfig = programsConfig
   where
diff --git a/Cabal/Distribution/Simple/GHC.hs b/Cabal/Distribution/Simple/GHC.hs
index 29e571ab2fb42c23ff1bcaf5b2e94bb3b0bf62c7..a4acf95df3a2ab03a5a237d562c885ef0228d22c 100644
--- a/Cabal/Distribution/Simple/GHC.hs
+++ b/Cabal/Distribution/Simple/GHC.hs
@@ -473,6 +473,8 @@ buildOrReplLib forRepl verbosity numJobs pkg_descr lbi lib clbi = do
 
       profOpts    = vanillaOpts `mappend` mempty {
                       ghcOptProfilingMode = toFlag True,
+                      ghcOptProfilingAuto = Internal.profDetailLevelFlag True
+                                              (withProfLibDetail lbi),
                       ghcOptHiSuffix      = toFlag "p_hi",
                       ghcOptObjSuffix     = toFlag "p_o",
                       ghcOptExtra         = toNubListR $ hcProfOptions GHC libBi,
@@ -761,10 +763,11 @@ buildOrReplExe forRepl verbosity numJobs _pkg_descr lbi
                    }
       profOpts   = baseOpts `mappend` mempty {
                       ghcOptProfilingMode  = toFlag True,
+                      ghcOptProfilingAuto  = Internal.profDetailLevelFlag False
+                                               (withProfExeDetail lbi),
                       ghcOptHiSuffix       = toFlag "p_hi",
                       ghcOptObjSuffix      = toFlag "p_o",
-                      ghcOptExtra          = toNubListR $
-                                             hcProfOptions GHC exeBi,
+                      ghcOptExtra          = toNubListR (hcProfOptions GHC exeBi),
                       ghcOptHPCDir         = hpcdir Hpc.Prof
                     }
       dynOpts    = baseOpts `mappend` mempty {
@@ -976,12 +979,14 @@ libAbiHash verbosity _pkg_descr lbi lib clbi = do
                        ghcOptObjSuffix   = toFlag "dyn_o",
                        ghcOptExtra       = toNubListR $ hcSharedOptions GHC libBi
                    }
-      profArgs = vanillaArgs `mappend` mempty {
+      profArgs   = vanillaArgs `mappend` mempty {
                      ghcOptProfilingMode = toFlag True,
+                     ghcOptProfilingAuto = Internal.profDetailLevelFlag True
+                                             (withProfLibDetail lbi),
                      ghcOptHiSuffix      = toFlag "p_hi",
                      ghcOptObjSuffix     = toFlag "p_o",
                      ghcOptExtra         = toNubListR $ hcProfOptions GHC libBi
-                 }
+                   }
       ghcArgs = if withVanillaLib lbi then vanillaArgs
            else if withSharedLib  lbi then sharedArgs
            else if withProfLib    lbi then profArgs
diff --git a/Cabal/Distribution/Simple/GHC/ImplInfo.hs b/Cabal/Distribution/Simple/GHC/ImplInfo.hs
index fad30235981bd5473f8ea85948fb6a5a7d52074b..46e1c43cc12b91b571e55a2bad4cc809a66f5549 100644
--- a/Cabal/Distribution/Simple/GHC/ImplInfo.hs
+++ b/Cabal/Distribution/Simple/GHC/ImplInfo.hs
@@ -47,6 +47,7 @@ data GhcImplInfo = GhcImplInfo
   , reportsNoExt         :: Bool -- ^ --supported-languages gives Ext and NoExt
   , alwaysNondecIndent   :: Bool -- ^ NondecreasingIndentation is always on
   , flagGhciScript       :: Bool -- ^ -ghci-script flag supported
+  , flagProfAuto         :: Bool -- ^ new style -fprof-auto* flags
   , flagPackageConf      :: Bool -- ^ use package-conf instead of package-db
   , flagDebugInfo        :: Bool -- ^ -g flag supported
   }
@@ -80,6 +81,7 @@ ghcVersionImplInfo (Version v _) = GhcImplInfo
   , reportsNoExt         = v >= [7]
   , alwaysNondecIndent   = v <  [7,1]
   , flagGhciScript       = v >= [7,2]
+  , flagProfAuto         = v >= [7,4]
   , flagPackageConf      = v <  [7,5]
   , flagDebugInfo        = v >= [7,10]
   }
@@ -100,6 +102,7 @@ ghcjsVersionImplInfo _ghcjsVer _ghcVer = GhcImplInfo
   , reportsNoExt         = True
   , alwaysNondecIndent   = False
   , flagGhciScript       = True
+  , flagProfAuto         = True
   , flagPackageConf      = False
   , flagDebugInfo        = False
   }
diff --git a/Cabal/Distribution/Simple/GHC/Internal.hs b/Cabal/Distribution/Simple/GHC/Internal.hs
index b161a52989135161bfd46e9655190c7f8cb577b5..ee1f6039577fa7513e8c8a5c238069e5a82a034c 100644
--- a/Cabal/Distribution/Simple/GHC/Internal.hs
+++ b/Cabal/Distribution/Simple/GHC/Internal.hs
@@ -25,7 +25,8 @@ module Distribution.Simple.GHC.Internal (
         getHaskellObjects,
         mkGhcOptPackages,
         substTopDir,
-        checkPackageDbEnvVar
+        checkPackageDbEnvVar,
+        profDetailLevelFlag,
  ) where
 
 import Distribution.Simple.GHC.ImplInfo ( GhcImplInfo (..) )
@@ -41,10 +42,11 @@ import Distribution.PackageDescription as PD
 import Distribution.Compat.Exception ( catchExit, catchIO )
 import Distribution.Lex (tokenizeQuotedWords)
 import Distribution.Simple.Compiler
-         ( CompilerFlavor(..), Compiler(..), DebugInfoLevel(..), OptimisationLevel(..) )
+         ( CompilerFlavor(..), Compiler(..), DebugInfoLevel(..)
+         , OptimisationLevel(..), ProfDetailLevel(..) )
 import Distribution.Simple.Program.GHC
 import Distribution.Simple.Setup
-         ( toFlag )
+         ( Flag, toFlag )
 import qualified Distribution.ModuleName as ModuleName
 import Distribution.Simple.Program
          ( Program(..), ConfiguredProgram(..), ProgramConfiguration
@@ -499,3 +501,14 @@ checkPackageDbEnvVar compilerName packagePathEnvVar = do
                ++ packagePathEnvVar ++ " is incompatible with Cabal. Use the "
                ++ "flag --package-db to specify a package database (it can be "
                ++ "used multiple times)."
+
+profDetailLevelFlag :: Bool -> ProfDetailLevel -> Flag GhcProfAuto
+profDetailLevelFlag forLib mpl =
+    case mpl of
+      ProfDetailNone                -> mempty
+      ProfDetailDefault | forLib    -> toFlag GhcProfAutoExported
+                        | otherwise -> toFlag GhcProfAutoToplevel
+      ProfDetailExportedFunctions   -> toFlag GhcProfAutoExported
+      ProfDetailToplevelFunctions   -> toFlag GhcProfAutoToplevel
+      ProfDetailAllFunctions        -> toFlag GhcProfAutoAll
+      ProfDetailOther _             -> mempty
diff --git a/Cabal/Distribution/Simple/LocalBuildInfo.hs b/Cabal/Distribution/Simple/LocalBuildInfo.hs
index 214f216969cc1b2580464af7becc59db2e04ef46..76cb64c97b548d78867467d8d552bbecfbf548b9 100644
--- a/Cabal/Distribution/Simple/LocalBuildInfo.hs
+++ b/Cabal/Distribution/Simple/LocalBuildInfo.hs
@@ -74,7 +74,7 @@ import Distribution.Package
          , PackageName )
 import Distribution.Simple.Compiler
          ( Compiler, compilerInfo, PackageDBStack, DebugInfoLevel
-         , OptimisationLevel )
+         , OptimisationLevel, ProfDetailLevel )
 import Distribution.Simple.PackageIndex
          ( InstalledPackageIndex, allPackages )
 import Distribution.ModuleName ( ModuleName )
@@ -139,6 +139,8 @@ data LocalBuildInfo = LocalBuildInfo {
         withSharedLib :: Bool,  -- ^Whether to build shared versions of libs.
         withDynExe    :: Bool,  -- ^Whether to link executables dynamically
         withProfExe   :: Bool,  -- ^Whether to build executables for profiling.
+        withProfLibDetail :: ProfDetailLevel, -- ^Level of automatic profile detail.
+        withProfExeDetail :: ProfDetailLevel, -- ^Level of automatic profile detail.
         withOptimization :: OptimisationLevel, -- ^Whether to build with optimization (if available).
         withDebugInfo :: DebugInfoLevel, -- ^Whether to emit debug info (if available).
         withGHCiLib   :: Bool,  -- ^Whether to build libs suitable for use with GHCi.
diff --git a/Cabal/Distribution/Simple/Program/GHC.hs b/Cabal/Distribution/Simple/Program/GHC.hs
index fbdc997023f5f77637fff3a84db4b4884b6dcee3..ad0967b20cd853300d77fc02f0afd57596979579 100644
--- a/Cabal/Distribution/Simple/Program/GHC.hs
+++ b/Cabal/Distribution/Simple/Program/GHC.hs
@@ -4,6 +4,7 @@ module Distribution.Simple.Program.GHC (
     GhcMode(..),
     GhcOptimisation(..),
     GhcDynLinkMode(..),
+    GhcProfAuto(..),
 
     ghcInvocation,
     renderGhcOptions,
@@ -161,6 +162,9 @@ data GhcOptions = GhcOptions {
   -- | Compile in profiling mode; the @ghc -prof@ flag.
   ghcOptProfilingMode :: Flag Bool,
 
+  -- | Automatically add profiling cost centers; the @ghc -fprof-auto*@ flags.
+  ghcOptProfilingAuto :: Flag GhcProfAuto,
+
   -- | Use the \"split object files\" feature; the @ghc -split-objs@ flag.
   ghcOptSplitObjs     :: Flag Bool,
 
@@ -230,6 +234,10 @@ data GhcDynLinkMode = GhcStaticOnly       -- ^ @-static@
                     | GhcStaticAndDynamic -- ^ @-static -dynamic-too@
  deriving (Show, Eq)
 
+data GhcProfAuto = GhcProfAutoAll       -- ^ @-fprof-auto@
+                 | GhcProfAutoToplevel  -- ^ @-fprof-auto-top@
+                 | GhcProfAutoExported  -- ^ @-fprof-auto-exported@
+ deriving (Show, Eq)
 
 runGHC :: Verbosity -> ConfiguredProgram -> Compiler -> GhcOptions -> IO ()
 runGHC verbosity ghcProg comp opts = do
@@ -283,6 +291,20 @@ renderGhcOptions comp opts
 
   , [ "-prof" | flagBool ghcOptProfilingMode ]
 
+  , case flagToMaybe (ghcOptProfilingAuto opts) of
+      _ | not (flagBool ghcOptProfilingMode)
+                                -> []
+      Nothing                   -> []
+      Just GhcProfAutoAll
+        | flagProfAuto implInfo -> ["-fprof-auto"]
+        | otherwise             -> ["-auto-all"] -- not the same, but close
+      Just GhcProfAutoToplevel
+        | flagProfAuto implInfo -> ["-fprof-auto-top"]
+        | otherwise             -> ["-auto-all"]
+      Just GhcProfAutoExported
+        | flagProfAuto implInfo -> ["-fprof-auto-exported"]
+        | otherwise             -> ["-auto"]
+
   , [ "-split-objs" | flagBool ghcOptSplitObjs ]
 
   , case flagToMaybe (ghcOptHPCDir opts) of
@@ -485,6 +507,7 @@ instance Monoid GhcOptions where
     ghcOptOptimisation       = mempty,
     ghcOptDebugInfo          = mempty,
     ghcOptProfilingMode      = mempty,
+    ghcOptProfilingAuto      = mempty,
     ghcOptSplitObjs          = mempty,
     ghcOptNumJobs            = mempty,
     ghcOptHPCDir             = mempty,
@@ -538,6 +561,7 @@ instance Monoid GhcOptions where
     ghcOptOptimisation       = combine ghcOptOptimisation,
     ghcOptDebugInfo          = combine ghcOptDebugInfo,
     ghcOptProfilingMode      = combine ghcOptProfilingMode,
+    ghcOptProfilingAuto      = combine ghcOptProfilingAuto,
     ghcOptSplitObjs          = combine ghcOptSplitObjs,
     ghcOptNumJobs            = combine ghcOptNumJobs,
     ghcOptHPCDir             = combine ghcOptHPCDir,
diff --git a/Cabal/Distribution/Simple/Setup.hs b/Cabal/Distribution/Simple/Setup.hs
index 16285270ffc8c86dc1291a008f9efe72ef414d88..e571c5c50731f9520e654d56596fc7c88dc1b6a9 100644
--- a/Cabal/Distribution/Simple/Setup.hs
+++ b/Cabal/Distribution/Simple/Setup.hs
@@ -85,6 +85,7 @@ import Distribution.Simple.Compiler
          ( CompilerFlavor(..), defaultCompilerFlavor, PackageDB(..)
          , DebugInfoLevel(..), flagToDebugInfoLevel
          , OptimisationLevel(..), flagToOptimisationLevel
+         , ProfDetailLevel(..), flagToProfDetailLevel
          , absolutePackageDBPath )
 import Distribution.Simple.Utils
          ( wrapText, wrapLine, lowercase, intercalate )
@@ -295,6 +296,10 @@ data ConfigFlags = ConfigFlags {
                                           -- executables.
     configProf          :: Flag Bool,     -- ^Enable profiling in the library
                                           -- and executables.
+    configProfDetail    :: Flag ProfDetailLevel, -- ^Profiling detail level
+                                          --  in the library and executables.
+    configProfLibDetail :: Flag ProfDetailLevel, -- ^Profiling  detail level
+                                                 -- in the library
     configConfigureArgs :: [String],      -- ^Extra arguments to @configure@
     configOptimization  :: Flag OptimisationLevel,  -- ^Enable optimization.
     configProgPrefix    :: Flag PathTemplate, -- ^Installed executable prefix.
@@ -351,6 +356,8 @@ defaultConfigFlags progConf = emptyConfigFlags {
     configDynExe       = Flag False,
     configProfExe      = NoFlag,
     configProf         = NoFlag,
+    configProfDetail   = NoFlag,
+    configProfLibDetail= NoFlag,
     configOptimization = Flag NormalOptimisation,
     configProgPrefix   = Flag (toPathTemplate ""),
     configProgSuffix   = Flag (toPathTemplate ""),
@@ -463,7 +470,7 @@ configureOptions showOrParseArgs =
          (boolOpt [] [])
 
       ,option "" ["profiling"]
-         "Executable profiling (requires library profiling)"
+         "Executable and library profiling"
          configProf (\v flags -> flags { configProf = v })
          (boolOpt [] [])
 
@@ -472,6 +479,19 @@ configureOptions showOrParseArgs =
          configProfExe (\v flags -> flags { configProfExe = v })
          (boolOpt [] [])
 
+      ,option "" ["profiling-detail"]
+         ("Profiling detail level for executable and library (default, " ++
+          "none, exported-functions, toplevel-functions,  all-functions).")
+         configProfDetail (\v flags -> flags { configProfDetail = v })
+         (reqArg' "level" (Flag . flagToProfDetailLevel)
+                          showProfDetailLevelFlag)
+
+      ,option "" ["library-profiling-detail"]
+         "Profiling detail level for libraries only."
+         configProfLibDetail (\v flags -> flags { configProfLibDetail = v })
+         (reqArg' "level" (Flag . flagToProfDetailLevel)
+                          showProfDetailLevelFlag)
+
       ,multiOption "optimization"
          configOptimization (\v flags -> flags { configOptimization = v })
          [optArg' "n" (Flag . flagToOptimisationLevel)
@@ -646,6 +666,17 @@ showPackageDbList = map showPackageDb
     showPackageDb (Just UserPackageDB)          = "user"
     showPackageDb (Just (SpecificPackageDB db)) = db
 
+showProfDetailLevelFlag :: Flag ProfDetailLevel -> [String]
+showProfDetailLevelFlag dl =
+  case dl of
+    NoFlag                           -> []
+    Flag ProfDetailNone              -> ["none"]
+    Flag ProfDetailDefault           -> ["default"]
+    Flag ProfDetailExportedFunctions -> ["exported-functions"]
+    Flag ProfDetailToplevelFunctions -> ["toplevel-functions"]
+    Flag ProfDetailAllFunctions      -> ["all-functions"]
+    Flag (ProfDetailOther other)     -> [other]
+
 
 parseDependency :: Parse.ReadP r (PackageName, InstalledPackageId)
 parseDependency = do
@@ -743,6 +774,8 @@ instance Monoid ConfigFlags where
     configDynExe        = mempty,
     configProfExe       = mempty,
     configProf          = mempty,
+    configProfDetail    = mempty,
+    configProfLibDetail = mempty,
     configConfigureArgs = mempty,
     configOptimization  = mempty,
     configProgPrefix    = mempty,
@@ -786,6 +819,8 @@ instance Monoid ConfigFlags where
     configDynExe        = combine configDynExe,
     configProfExe       = combine configProfExe,
     configProf          = combine configProf,
+    configProfDetail    = combine configProfDetail,
+    configProfLibDetail = combine configProfLibDetail,
     configConfigureArgs = combine configConfigureArgs,
     configOptimization  = combine configOptimization,
     configProgPrefix    = combine configProgPrefix,
diff --git a/Cabal/changelog b/Cabal/changelog
index 253c499cf90cce2fedbeb4d58422efdcb6d62102..7fff469b22a658c0a42e9cb475b286b9a5f38d25 100644
--- a/Cabal/changelog
+++ b/Cabal/changelog
@@ -5,6 +5,8 @@
 	* Include cabal_macros.h when running c2hs (#2600).
 	* Don't recompile C sources unless needed (#2601).
 	* Read 'builddir' option from 'CABAL_BUILDDIR' environment variable
+	* Enable '-fprof-auto-exported' for profiled libraries (#193).
+	* Enable '-fprof-auto-top' for profiled executables (#193).
 
 1.22.0.0 Johan Tibell <johan.tibell@gmail.com> January 2015
 	* Support GHC 7.10.
diff --git a/Cabal/doc/developing-packages.markdown b/Cabal/doc/developing-packages.markdown
index b91352ccb5a664b589650d11de26601bf916235f..3b3e6016a98c72cf637a2c43253d72696798ab8d 100644
--- a/Cabal/doc/developing-packages.markdown
+++ b/Cabal/doc/developing-packages.markdown
@@ -1372,6 +1372,21 @@ values for these fields.
 :   Additional options for GHC when the package is built with profiling
     enabled.
 
+    Note that as of Cabal-1.24, the default profiling detail level defaults to
+    `exported-functions` for libraries and `toplevel-funcitons` for
+    executables. For GHC these correspond to the flags `-fprof-auto-exported`
+    and `-fprof-auto-top`. Prior to Cabal-1.24 the level defaulted to `none`.
+    These levels can be adjusted by the person building the package with the
+    `--profiling-detail` and `--library-profiling-detail` flags.
+
+    It is typically better for the person building the package to pick the
+    profiling detail level rather than for the package author. So unless you
+    have special needs it is probably better not to specify any of the GHC
+    `-fprof-auto*` flags here. However if you wish to override the profiling
+    detail level, you can do so using the `ghc-prof-options` field: use
+    `-fno-prof-auto` or one of the other `-fprof-auto*` flags.
+
+
 `ghc-shared-options:` _token list_
 :   Additional options for GHC when the package is built as shared library.
 
diff --git a/Cabal/doc/installing-packages.markdown b/Cabal/doc/installing-packages.markdown
index 8d5c8e9cfecfc413a69d920b9a17b155d8353f9e..4dffb5a291ea9861ae4728b8b7edc991012a188b 100644
--- a/Cabal/doc/installing-packages.markdown
+++ b/Cabal/doc/installing-packages.markdown
@@ -626,24 +626,80 @@ be controlled with the following command line options.
 :   Build without optimization. This is suited for development: building
     will be quicker, but the resulting library or programs will be slower.
 
+`--enable-profiling`
+:   Build libraries and executables with profiling enabled (for compilers
+    that support profiling as a separate mode). For this to work, all
+    libraries used by this package must also have been built with profiling
+    support. For libraries this involves building an additional instance of
+    the library in addition to the normal non-profiling instance. For
+    executables it changes the single executable to be built in profiling mode.
+
+    This flag covers both libraries and executables, but can be overridden
+    by the `--enable-library-profiling` flag.
+
+    See also the `--profiling-detail` flag below.
+
+`--disable-profiling`
+:   (default) Do not enable profiling in generated libraries and executables.
+
 `--enable-library-profiling` or `-p`
-:   Request that an additional version of the library with profiling
-    features enabled be built and installed (only for implementations
-    that support profiling).
+:   As with `--enable-profiling` above, but it applies only for libraries. So
+    this generates an additional profiling instance of the library in addition
+    to the normal non-profiling instance.
+
+    The `--enable-profiling` flag controls the profiling mode for both
+    libraries and executables, but if different modes are desired for
+    libraries versus executables then use `--enable-library-profiling` as well.
 
 `--disable-library-profiling`
 :   (default) Do not generate an additional profiling version of the
     library.
 
-`--enable-profiling`
-:   Any executables generated should have profiling enabled (only for
-    implementations that support profiling). For this to work, all
-    libraries used by these executables must also have been built with
-    profiling support. The library will be built with profiling enabled (if
-    supported) unless `--disable-library-profiling` is specified.
+`--profiling-detail`[=_level_]
+:   Some compilers that support profiling, notably GHC, can allocate costs to
+    different parts of the program and there are different levels of
+    granularity or detail with which this can be done. In particular for GHC
+    this concept is called "cost centers", and GHC can automatically add cost
+    centers, and can do so in different ways.
+
+    This flag covers both libraries and executables, but can be overridden
+    by the `--library-profiling-detail` flag.
+
+    Currently this setting is ignored for compilers other than GHC. The levels
+    that cabal currently supports are:
+
+    `default`
+    :    For GHC this uses `exported-functions` for libraries and
+         `toplevel-functions` for executables.
+
+    `none`
+    :    No costs will be assigned to any code within this component.
+
+    `exported-functions`
+    :    Costs will be assigned at the granularity of all top level functions
+         exported from each module. In GHC specifically, this is for non-inline
+         functions.
+
+    `toplevel-functions`
+    :    Costs will be assigned at the granularity of all top level functions
+         in each module, whether they are exported from the module or not.
+         In GHC specifically, this is for non-inline functions.
+
+    `all-functions`
+    :    Costs will be assigned at the granularity of all functions in each
+         module, whether top level or local. In GHC specifically, this is for
+         non-inline toplevel or where-bound functions or values.
+
+    This flag is new in Cabal-1.24. Prior versions used the equivalent of
+    `none` above.
+
+`--library-profiling-detail`[=_level_]
+:   As with `--profiling-detail` above, but it applies only for libraries.
+
+    The level for both libraries and executables is set by the
+    `--profiling-detail` flag, but if different levels are desired for
+    libraries versus executables then use `--library-profiling-detail` as well.
 
-`--disable-profiling`
-:   (default) Do not enable profiling in generated executables.
 
 `--enable-library-vanilla`
 :   (default) Build ordinary libraries (as opposed to profiling
diff --git a/cabal-install/Distribution/Client/Config.hs b/cabal-install/Distribution/Client/Config.hs
index 6143c9e05e1b5dd851494d05ae2a2725d50a570a..2768c13f3f82cb5200ddab0ef4f5ec0833d2a72e 100644
--- a/cabal-install/Distribution/Client/Config.hs
+++ b/cabal-install/Distribution/Client/Config.hs
@@ -272,6 +272,8 @@ instance Monoid SavedConfig where
         configSharedLib           = combine configSharedLib,
         configDynExe              = combine configDynExe,
         configProfExe             = combine configProfExe,
+        configProfDetail          = combine configProfDetail,
+        configProfLibDetail       = combine configProfLibDetail,
         -- TODO: NubListify
         configConfigureArgs       = lastNonEmpty configConfigureArgs,
         configOptimization        = combine configOptimization,
diff --git a/cabal-install/Distribution/Client/Setup.hs b/cabal-install/Distribution/Client/Setup.hs
index 264e13982075d238e306a61da144e27587258d8a..759b13bc0123c740b131a8d38f47bb64f6f049ca 100644
--- a/cabal-install/Distribution/Client/Setup.hs
+++ b/cabal-install/Distribution/Client/Setup.hs
@@ -393,7 +393,7 @@ configureOptions = commandOptions configureCommand
 
 filterConfigureFlags :: ConfigFlags -> Version -> ConfigFlags
 filterConfigureFlags flags cabalLibVersion
-  | cabalLibVersion >= Version [1,22,0] [] = flags_latest
+  | cabalLibVersion >= Version [1,23,0] [] = flags_latest
   -- ^ NB: we expect the latest version to be the most common case.
   | cabalLibVersion <  Version [1,3,10] [] = flags_1_3_10
   | cabalLibVersion <  Version [1,10,0] [] = flags_1_10_0
@@ -403,13 +403,18 @@ filterConfigureFlags flags cabalLibVersion
   | cabalLibVersion <  Version [1,19,2] [] = flags_1_19_1
   | cabalLibVersion <  Version [1,21,1] [] = flags_1_20_0
   | cabalLibVersion <  Version [1,22,0] [] = flags_1_21_0
+  | cabalLibVersion <  Version [1,23,0] [] = flags_1_22_0
   | otherwise = flags_latest
   where
     -- Cabal >= 1.19.1 uses '--dependency' and does not need '--constraint'.
     flags_latest = flags        { configConstraints = [] }
 
+    -- Cabal < 1.23 doesn't know about '--profiling-detail'.
+    flags_1_22_0 = flags_latest { configProfDetail    = NoFlag
+                                , configProfLibDetail = NoFlag }
+
     -- Cabal < 1.22 doesn't know about '--disable-debug-info'.
-    flags_1_21_0 = flags_latest { configDebugInfo = NoFlag }
+    flags_1_21_0 = flags_1_22_0 { configDebugInfo = NoFlag }
 
     -- Cabal < 1.21.1 doesn't know about 'disable-relocatable'
     -- Cabal < 1.21.1 doesn't know about 'enable-profiling'