module GHC.Platform.Profile
( Profile (..)
, profileBuildTag
, profileConstants
, profileIsProfiling
, profileWordSizeInBytes
)
where
import GHC.Prelude
import GHC.Platform
import GHC.Platform.Ways
data Profile = Profile
{ Profile -> Platform
profilePlatform :: !Platform
, Profile -> Ways
profileWays :: !Ways
}
profileConstants :: Profile -> PlatformConstants
{-# INLINE profileConstants #-}
profileConstants :: Profile -> PlatformConstants
profileConstants Profile
profile = Platform -> PlatformConstants
platformConstants (Profile -> Platform
profilePlatform Profile
profile)
profileIsProfiling :: Profile -> Bool
{-# INLINE profileIsProfiling #-}
profileIsProfiling :: Profile -> Bool
profileIsProfiling Profile
profile = Profile -> Ways
profileWays Profile
profile Ways -> Way -> Bool
`hasWay` Way
WayProf
profileWordSizeInBytes :: Profile -> Int
{-# INLINE profileWordSizeInBytes #-}
profileWordSizeInBytes :: Profile -> Int
profileWordSizeInBytes Profile
profile = Platform -> Int
platformWordSizeInBytes (Profile -> Platform
profilePlatform Profile
profile)
profileBuildTag :: Profile -> String
profileBuildTag :: Profile -> String
profileBuildTag Profile
profile
| Platform -> Bool
platformUnregisterised Platform
platform = Char
'u'forall a. a -> [a] -> [a]
:String
wayTag
| Bool
otherwise = String
wayTag
where
platform :: Platform
platform = Profile -> Platform
profilePlatform Profile
profile
wayTag :: String
wayTag = Ways -> String
waysBuildTag (Profile -> Ways
profileWays Profile
profile)