never executed always true always false
    1 -- | Platform profiles
    2 module GHC.Platform.Profile
    3    ( Profile (..)
    4    , profileBuildTag
    5    , profileConstants
    6    , profileIsProfiling
    7    , profileWordSizeInBytes
    8    )
    9 where
   10 
   11 import GHC.Prelude
   12 
   13 import GHC.Platform
   14 import GHC.Platform.Ways
   15 
   16 -- | A platform profile fully describes the kind of objects that are generated
   17 -- for a platform.
   18 --
   19 -- 'Platform' doesn't fully describe the ABI of an object. Compiler ways
   20 -- (profiling, debug, dynamic) also modify the ABI.
   21 --
   22 data Profile = Profile
   23    { profilePlatform :: !Platform -- ^ Platform
   24    , profileWays     :: !Ways     -- ^ Ways
   25    }
   26 
   27 -- | Get platform constants
   28 profileConstants :: Profile -> PlatformConstants
   29 {-# INLINE profileConstants #-}
   30 profileConstants profile = platformConstants (profilePlatform profile)
   31 
   32 -- | Is profiling enabled
   33 profileIsProfiling :: Profile -> Bool
   34 {-# INLINE profileIsProfiling #-}
   35 profileIsProfiling profile = profileWays profile `hasWay` WayProf
   36 
   37 -- | Word size in bytes
   38 profileWordSizeInBytes :: Profile -> Int
   39 {-# INLINE profileWordSizeInBytes #-}
   40 profileWordSizeInBytes profile = platformWordSizeInBytes (profilePlatform profile)
   41 
   42 -- | Unique build tag for the profile
   43 profileBuildTag :: Profile -> String
   44 profileBuildTag profile
   45     -- profiles using unregisterised convention are not binary compatible with
   46     -- those that don't. Make sure to make it apparent in the tag so that our
   47     -- interface files can't be mismatched by mistake.
   48   | platformUnregisterised platform = 'u':wayTag
   49   | otherwise                       =     wayTag
   50   where
   51    platform = profilePlatform profile
   52    wayTag   = waysBuildTag (profileWays profile)