module GHC.Unit.Module.Status
   ( HscBackendAction(..), HscRecompStatus (..)
   )
where

import GHC.Prelude

import GHC.Unit
import GHC.Unit.Module.ModGuts
import GHC.Unit.Module.ModIface

import GHC.Utils.Fingerprint
import GHC.Utils.Outputable
import GHC.Unit.Home.ModInfo

-- | Status of a module in incremental compilation
data HscRecompStatus
    -- | Nothing to do because code already exists.
    = HscUpToDate ModIface HomeModLinkable
    -- | Recompilation of module, or update of interface is required. Optionally
    -- pass the old interface hash to avoid updating the existing interface when
    -- it has not changed.
    | HscRecompNeeded (Maybe Fingerprint)

-- | Action to perform in backend compilation
data HscBackendAction
    -- | Update the boot and signature file results.
    = HscUpdate ModIface
    -- | Recompile this module.
    | HscRecomp
        { HscBackendAction -> CgGuts
hscs_guts           :: CgGuts
          -- ^ Information for the code generator.
        , HscBackendAction -> ModLocation
hscs_mod_location   :: !ModLocation
          -- ^ Module info
        , HscBackendAction -> PartialModIface
hscs_partial_iface  :: !PartialModIface
          -- ^ Partial interface
        , HscBackendAction -> Maybe Fingerprint
hscs_old_iface_hash :: !(Maybe Fingerprint)
          -- ^ Old interface hash for this compilation, if an old interface file
          -- exists. Pass to `hscMaybeWriteIface` when writing the interface to
          -- avoid updating the existing interface when the interface isn't
          -- changed.
        }


instance Outputable HscBackendAction where
  ppr :: HscBackendAction -> SDoc
ppr (HscUpdate ModIface
mi) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Update:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface
mi))
  ppr (HscRecomp CgGuts
_ ModLocation
ml PartialModIface
_mi Maybe Fingerprint
_mf) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Recomp:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ModLocation -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModLocation
ml