{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE LambdaCase #-}
module GHC.StgToJS.Linker.Types
  ( JSLinkConfig (..)
  , LinkPlan (..)
  )
where
import GHC.StgToJS.Object
import GHC.Unit.Types
import GHC.Utils.Outputable (Outputable(..),text,ppr, hang, IsDoc (vcat), IsLine (hcat))
import Data.Map.Strict      (Map)
import Data.Set             (Set)
import qualified Data.Set        as S
import System.IO
import Prelude
data JSLinkConfig = JSLinkConfig
  { JSLinkConfig -> Bool
lcNoJSExecutables :: !Bool         
  , JSLinkConfig -> Bool
lcNoHsMain        :: !Bool         
  , JSLinkConfig -> Bool
lcNoRts           :: !Bool         
  , JSLinkConfig -> Bool
lcNoStats         :: !Bool         
  , JSLinkConfig -> Bool
lcForeignRefs     :: !Bool         
  , JSLinkConfig -> Bool
lcCombineAll      :: !Bool         
  , JSLinkConfig -> Bool
lcForceEmccRts    :: !Bool
      
      
  , JSLinkConfig -> Bool
lcLinkCsources    :: !Bool
      
      
  }
data LinkPlan = LinkPlan
  { LinkPlan -> Map Module LocatedBlockInfo
lkp_block_info :: Map Module LocatedBlockInfo
      
  , LinkPlan -> Set BlockRef
lkp_dep_blocks :: Set BlockRef
      
  , LinkPlan -> Set FilePath
lkp_archives   :: !(Set FilePath)
      
      
  , LinkPlan -> Set FilePath
lkp_objs_js   :: !(Set FilePath)
      
  , LinkPlan -> Set FilePath
lkp_objs_cc   :: !(Set FilePath)
      
  }
instance Outputable LinkPlan where
  ppr :: LinkPlan -> SDoc
ppr LinkPlan
s = SDoc -> Int -> SDoc -> SDoc
hang (FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text FilePath
"LinkPlan") Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat
            
            
            
            [ [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hcat [ FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text FilePath
"Blocks: ", Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Set BlockRef -> Int
forall a. Set a -> Int
S.size (LinkPlan -> Set BlockRef
lkp_dep_blocks LinkPlan
s))]
            , SDoc -> Int -> SDoc -> SDoc
hang (FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text FilePath
"Archives:") Int
2 ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ((FilePath -> SDoc) -> [FilePath] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text (Set FilePath -> [FilePath]
forall a. Set a -> [a]
S.toList (LinkPlan -> Set FilePath
lkp_archives LinkPlan
s))))
            , SDoc -> Int -> SDoc -> SDoc
hang (FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text FilePath
"Extra JS objects:") Int
2 ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ((FilePath -> SDoc) -> [FilePath] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text (Set FilePath -> [FilePath]
forall a. Set a -> [a]
S.toList (LinkPlan -> Set FilePath
lkp_objs_js LinkPlan
s))))
            , SDoc -> Int -> SDoc -> SDoc
hang (FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text FilePath
"Extra Cc objects:") Int
2 ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ((FilePath -> SDoc) -> [FilePath] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text (Set FilePath -> [FilePath]
forall a. Set a -> [a]
S.toList (LinkPlan -> Set FilePath
lkp_objs_cc LinkPlan
s))))
            ]