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     
   }
  deriving (Profile -> Profile -> Bool
(Profile -> Profile -> Bool)
-> (Profile -> Profile -> Bool) -> Eq Profile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Profile -> Profile -> Bool
== :: Profile -> Profile -> Bool
$c/= :: Profile -> Profile -> Bool
/= :: Profile -> Profile -> Bool
Eq, Eq Profile
Eq Profile =>
(Profile -> Profile -> Ordering)
-> (Profile -> Profile -> Bool)
-> (Profile -> Profile -> Bool)
-> (Profile -> Profile -> Bool)
-> (Profile -> Profile -> Bool)
-> (Profile -> Profile -> Profile)
-> (Profile -> Profile -> Profile)
-> Ord Profile
Profile -> Profile -> Bool
Profile -> Profile -> Ordering
Profile -> Profile -> Profile
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Profile -> Profile -> Ordering
compare :: Profile -> Profile -> Ordering
$c< :: Profile -> Profile -> Bool
< :: Profile -> Profile -> Bool
$c<= :: Profile -> Profile -> Bool
<= :: Profile -> Profile -> Bool
$c> :: Profile -> Profile -> Bool
> :: Profile -> Profile -> Bool
$c>= :: Profile -> Profile -> Bool
>= :: Profile -> Profile -> Bool
$cmax :: Profile -> Profile -> Profile
max :: Profile -> Profile -> Profile
$cmin :: Profile -> Profile -> Profile
min :: Profile -> Profile -> Profile
Ord, Int -> Profile -> ShowS
[Profile] -> ShowS
Profile -> String
(Int -> Profile -> ShowS)
-> (Profile -> String) -> ([Profile] -> ShowS) -> Show Profile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Profile -> ShowS
showsPrec :: Int -> Profile -> ShowS
$cshow :: Profile -> String
show :: Profile -> String
$cshowList :: [Profile] -> ShowS
showList :: [Profile] -> ShowS
Show, ReadPrec [Profile]
ReadPrec Profile
Int -> ReadS Profile
ReadS [Profile]
(Int -> ReadS Profile)
-> ReadS [Profile]
-> ReadPrec Profile
-> ReadPrec [Profile]
-> Read Profile
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Profile
readsPrec :: Int -> ReadS Profile
$creadList :: ReadS [Profile]
readList :: ReadS [Profile]
$creadPrec :: ReadPrec Profile
readPrec :: ReadPrec Profile
$creadListPrec :: ReadPrec [Profile]
readListPrec :: ReadPrec [Profile]
Read)
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'Char -> ShowS
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)