module GHC.Driver.Config.HsToCore.Ticks
  ( initTicksConfig
  )
where

import GHC.Prelude

import Data.Maybe (catMaybes)

import GHC.Driver.Backend
import GHC.Driver.Session
import GHC.HsToCore.Ticks

initTicksConfig :: DynFlags -> TicksConfig
initTicksConfig :: DynFlags -> TicksConfig
initTicksConfig DynFlags
dflags = TicksConfig
  { ticks_passes :: [TickishType]
ticks_passes       = DynFlags -> [TickishType]
coveragePasses DynFlags
dflags
  , ticks_profAuto :: ProfAuto
ticks_profAuto     = DynFlags -> ProfAuto
profAuto DynFlags
dflags
  , ticks_countEntries :: Bool
ticks_countEntries = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_ProfCountEntries DynFlags
dflags
  }

coveragePasses :: DynFlags -> [TickishType]
coveragePasses :: DynFlags -> [TickishType]
coveragePasses DynFlags
dflags = [Maybe TickishType] -> [TickishType]
forall a. [Maybe a] -> [a]
catMaybes
  [ TickishType -> Bool -> Maybe TickishType
forall {a}. a -> Bool -> Maybe a
ifA TickishType
Breakpoints (Bool -> Maybe TickishType) -> Bool -> Maybe TickishType
forall a b. (a -> b) -> a -> b
$ Backend -> Bool
backendWantsBreakpointTicks (Backend -> Bool) -> Backend -> Bool
forall a b. (a -> b) -> a -> b
$ DynFlags -> Backend
backend DynFlags
dflags
  , TickishType -> Bool -> Maybe TickishType
forall {a}. a -> Bool -> Maybe a
ifA TickishType
HpcTicks (Bool -> Maybe TickishType) -> Bool -> Maybe TickishType
forall a b. (a -> b) -> a -> b
$ GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_Hpc DynFlags
dflags
  , TickishType -> Bool -> Maybe TickishType
forall {a}. a -> Bool -> Maybe a
ifA TickishType
ProfNotes (Bool -> Maybe TickishType) -> Bool -> Maybe TickishType
forall a b. (a -> b) -> a -> b
$ DynFlags -> Bool
sccProfilingEnabled DynFlags
dflags Bool -> Bool -> Bool
&& DynFlags -> ProfAuto
profAuto DynFlags
dflags ProfAuto -> ProfAuto -> Bool
forall a. Eq a => a -> a -> Bool
/= ProfAuto
NoProfAuto
  , TickishType -> Bool -> Maybe TickishType
forall {a}. a -> Bool -> Maybe a
ifA TickishType
SourceNotes (Bool -> Maybe TickishType) -> Bool -> Maybe TickishType
forall a b. (a -> b) -> a -> b
$ DynFlags -> Bool
needSourceNotes DynFlags
dflags
  ]
  where ifA :: a -> Bool -> Maybe a
ifA a
x Bool
cond = if Bool
cond then a -> Maybe a
forall a. a -> Maybe a
Just a
x else Maybe a
forall a. Maybe a
Nothing