{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module GHC.CmmToAsm.BlockLayout
    ( sequenceTop, backendMaintainsCfg)
where
#include "GhclibHsVersions.h"
import GHC.Prelude
import GHC.Driver.Ppr     (pprTrace)
import GHC.CmmToAsm.Instr
import GHC.CmmToAsm.Monad
import GHC.CmmToAsm.CFG
import GHC.CmmToAsm.Types
import GHC.CmmToAsm.Config
import GHC.Cmm.BlockId
import GHC.Cmm
import GHC.Cmm.Dataflow.Collections
import GHC.Cmm.Dataflow.Label
import GHC.Platform
import GHC.Types.Unique.FM
import GHC.Utils.Misc
import GHC.Data.Graph.Directed
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Data.Maybe
import GHC.Data.List.SetOps (removeDups)
import GHC.Data.OrdList
import Data.List (sortOn, sortBy, nub)
import Data.Foldable (toList)
import qualified Data.Set as Set
import Data.STRef
import Control.Monad.ST.Strict
import Control.Monad (foldM, unless)
import GHC.Data.UnionFind
neighbourOverlapp :: Int
neighbourOverlapp :: Int
neighbourOverlapp = Int
2
type FrontierMap = LabelMap ([BlockId],BlockChain)
newtype BlockChain
    = BlockChain { BlockChain -> OrdList BlockId
chainBlocks :: (OrdList BlockId) }
instance Eq BlockChain where
    BlockChain OrdList BlockId
b1 == :: BlockChain -> BlockChain -> Bool
== BlockChain OrdList BlockId
b2 = forall a. Eq a => OrdList a -> OrdList a -> Bool
strictlyEqOL OrdList BlockId
b1 OrdList BlockId
b2
instance Ord (BlockChain) where
   (BlockChain OrdList BlockId
lbls1) compare :: BlockChain -> BlockChain -> Ordering
`compare` (BlockChain OrdList BlockId
lbls2)
       = ASSERT(toList lbls1 /= toList lbls2 || lbls1 `strictlyEqOL` lbls2)
         forall a. Ord a => OrdList a -> OrdList a -> Ordering
strictlyOrdOL OrdList BlockId
lbls1 OrdList BlockId
lbls2
instance Outputable (BlockChain) where
    ppr :: BlockChain -> SDoc
ppr (BlockChain OrdList BlockId
blks) =
        SDoc -> SDoc
parens (String -> SDoc
text String
"Chain:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr (forall a. OrdList a -> [a]
fromOL forall a b. (a -> b) -> a -> b
$ OrdList BlockId
blks) )
chainFoldl :: (b -> BlockId -> b) -> b -> BlockChain -> b
chainFoldl :: forall b. (b -> BlockId -> b) -> b -> BlockChain -> b
chainFoldl b -> BlockId -> b
f b
z (BlockChain OrdList BlockId
blocks) = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' b -> BlockId -> b
f b
z OrdList BlockId
blocks
noDups :: [BlockChain] -> Bool
noDups :: [BlockChain] -> Bool
noDups [BlockChain]
chains =
    let chainBlocks :: [BlockId]
chainBlocks = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap BlockChain -> [BlockId]
chainToBlocks [BlockChain]
chains :: [BlockId]
        ([BlockId]
_blocks, [NonEmpty BlockId]
dups) = forall a. (a -> a -> Ordering) -> [a] -> ([a], [NonEmpty a])
removeDups forall a. Ord a => a -> a -> Ordering
compare [BlockId]
chainBlocks
    in if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [NonEmpty BlockId]
dups then Bool
True
        else forall a. String -> SDoc -> a -> a
pprTrace String
"Duplicates:" (forall a. Outputable a => a -> SDoc
ppr (forall a b. (a -> b) -> [a] -> [b]
map forall (t :: * -> *) a. Foldable t => t a -> [a]
toList [NonEmpty BlockId]
dups) SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
"chains" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr [BlockChain]
chains ) Bool
False
inFront :: BlockId -> BlockChain -> Bool
inFront :: BlockId -> BlockChain -> Bool
inFront BlockId
bid (BlockChain OrdList BlockId
seq)
  = forall a. OrdList a -> a
headOL OrdList BlockId
seq forall a. Eq a => a -> a -> Bool
== BlockId
bid
chainSingleton :: BlockId -> BlockChain
chainSingleton :: BlockId -> BlockChain
chainSingleton BlockId
lbl
    = OrdList BlockId -> BlockChain
BlockChain (forall a. a -> OrdList a
unitOL BlockId
lbl)
chainFromList :: [BlockId] -> BlockChain
chainFromList :: [BlockId] -> BlockChain
chainFromList = OrdList BlockId -> BlockChain
BlockChain forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> OrdList a
toOL
chainSnoc :: BlockChain -> BlockId -> BlockChain
chainSnoc :: BlockChain -> BlockId -> BlockChain
chainSnoc (BlockChain OrdList BlockId
blks) BlockId
lbl
  = OrdList BlockId -> BlockChain
BlockChain (OrdList BlockId
blks forall a. OrdList a -> a -> OrdList a
`snocOL` BlockId
lbl)
chainCons :: BlockId -> BlockChain -> BlockChain
chainCons :: BlockId -> BlockChain -> BlockChain
chainCons BlockId
lbl (BlockChain OrdList BlockId
blks)
  = OrdList BlockId -> BlockChain
BlockChain (BlockId
lbl forall a. a -> OrdList a -> OrdList a
`consOL` OrdList BlockId
blks)
chainConcat :: BlockChain -> BlockChain -> BlockChain
chainConcat :: BlockChain -> BlockChain -> BlockChain
chainConcat (BlockChain OrdList BlockId
blks1) (BlockChain OrdList BlockId
blks2)
  = OrdList BlockId -> BlockChain
BlockChain (OrdList BlockId
blks1 forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList BlockId
blks2)
chainToBlocks :: BlockChain -> [BlockId]
chainToBlocks :: BlockChain -> [BlockId]
chainToBlocks (BlockChain OrdList BlockId
blks) = forall a. OrdList a -> [a]
fromOL OrdList BlockId
blks
breakChainAt :: BlockId -> BlockChain
             -> (BlockChain,BlockChain)
breakChainAt :: BlockId -> BlockChain -> (BlockChain, BlockChain)
breakChainAt BlockId
bid (BlockChain OrdList BlockId
blks)
    | Bool -> Bool
not (BlockId
bid forall a. Eq a => a -> a -> Bool
== forall a. [a] -> a
head [BlockId]
rblks)
    = forall a. String -> a
panic String
"Block not in chain"
    | Bool
otherwise
    = (OrdList BlockId -> BlockChain
BlockChain (forall a. [a] -> OrdList a
toOL [BlockId]
lblks),
       OrdList BlockId -> BlockChain
BlockChain (forall a. [a] -> OrdList a
toOL [BlockId]
rblks))
  where
    ([BlockId]
lblks, [BlockId]
rblks) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break (\BlockId
lbl -> BlockId
lbl forall a. Eq a => a -> a -> Bool
== BlockId
bid) (forall a. OrdList a -> [a]
fromOL OrdList BlockId
blks)
takeR :: Int -> BlockChain -> [BlockId]
takeR :: Int -> BlockChain -> [BlockId]
takeR Int
n (BlockChain OrdList BlockId
blks) =
    forall a. Int -> [a] -> [a]
take Int
n forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. OrdList a -> [a]
fromOLReverse forall a b. (a -> b) -> a -> b
$ OrdList BlockId
blks
takeL :: Int -> BlockChain -> [BlockId]
takeL :: Int -> BlockChain -> [BlockId]
takeL Int
n (BlockChain OrdList BlockId
blks) =
    forall a. Int -> [a] -> [a]
take Int
n forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. OrdList a -> [a]
fromOL forall a b. (a -> b) -> a -> b
$ OrdList BlockId
blks
combineNeighbourhood  :: [CfgEdge] 
                      -> [BlockChain] 
                      -> ([BlockChain], Set.Set (BlockId,BlockId))
                      
                      
                      
combineNeighbourhood :: [CfgEdge] -> [BlockChain] -> ([BlockChain], Set (BlockId, BlockId))
combineNeighbourhood [CfgEdge]
edges [BlockChain]
chains
    = 
    
      [CfgEdge]
-> FrontierMap
-> FrontierMap
-> Set (BlockId, BlockId)
-> ([BlockChain], Set (BlockId, BlockId))
applyEdges [CfgEdge]
edges FrontierMap
endFrontier FrontierMap
startFrontier (forall a. Set a
Set.empty)
    where
        
        endFrontier, startFrontier :: FrontierMap
        endFrontier :: FrontierMap
endFrontier =
            forall (map :: * -> *) a. IsMap map => [(KeyOf map, a)] -> map a
mapFromList forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\BlockChain
chain ->
                                let ends :: [BlockId]
ends = BlockChain -> [BlockId]
getEnds BlockChain
chain :: [BlockId]
                                    entry :: ([BlockId], BlockChain)
entry = ([BlockId]
ends,BlockChain
chain)
                                in forall a b. (a -> b) -> [a] -> [b]
map (\BlockId
x -> (BlockId
x,([BlockId], BlockChain)
entry)) [BlockId]
ends ) [BlockChain]
chains
        startFrontier :: FrontierMap
startFrontier =
            forall (map :: * -> *) a. IsMap map => [(KeyOf map, a)] -> map a
mapFromList forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\BlockChain
chain ->
                                let front :: [BlockId]
front = BlockChain -> [BlockId]
getFronts BlockChain
chain
                                    entry :: ([BlockId], BlockChain)
entry = ([BlockId]
front,BlockChain
chain)
                                in forall a b. (a -> b) -> [a] -> [b]
map (\BlockId
x -> (BlockId
x,([BlockId], BlockChain)
entry)) [BlockId]
front) [BlockChain]
chains
        applyEdges :: [CfgEdge] -> FrontierMap -> FrontierMap -> Set.Set (BlockId, BlockId)
                   -> ([BlockChain], Set.Set (BlockId,BlockId))
        applyEdges :: [CfgEdge]
-> FrontierMap
-> FrontierMap
-> Set (BlockId, BlockId)
-> ([BlockChain], Set (BlockId, BlockId))
applyEdges [] FrontierMap
chainEnds FrontierMap
_chainFronts Set (BlockId, BlockId)
combined =
            (forall a. Ord a => [a] -> [a]
ordNub forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd forall a b. (a -> b) -> a -> b
$ forall (map :: * -> *) a. IsMap map => map a -> [a]
mapElems FrontierMap
chainEnds, Set (BlockId, BlockId)
combined)
        applyEdges ((CfgEdge BlockId
from BlockId
to EdgeInfo
_w):[CfgEdge]
edges) FrontierMap
chainEnds FrontierMap
chainFronts Set (BlockId, BlockId)
combined
            | Just ([BlockId]
c1_e,BlockChain
c1) <- forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
mapLookup BlockId
from FrontierMap
chainEnds
            , Just ([BlockId]
c2_f,BlockChain
c2) <- forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
mapLookup BlockId
to FrontierMap
chainFronts
            , BlockChain
c1 forall a. Eq a => a -> a -> Bool
/= BlockChain
c2 
            = let newChain :: BlockChain
newChain = BlockChain -> BlockChain -> BlockChain
chainConcat BlockChain
c1 BlockChain
c2
                  newChainFrontier :: [BlockId]
newChainFrontier = BlockChain -> [BlockId]
getFronts BlockChain
newChain
                  newChainEnds :: [BlockId]
newChainEnds = BlockChain -> [BlockId]
getEnds BlockChain
newChain
                  newFronts :: FrontierMap
                  newFronts :: FrontierMap
newFronts =
                    let withoutOld :: FrontierMap
withoutOld =
                            forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\FrontierMap
m BlockId
b -> forall (map :: * -> *) a. IsMap map => KeyOf map -> map a -> map a
mapDelete BlockId
b FrontierMap
m :: FrontierMap) FrontierMap
chainFronts ([BlockId]
c2_f forall a. [a] -> [a] -> [a]
++ BlockChain -> [BlockId]
getFronts BlockChain
c1)
                        entry :: ([BlockId], BlockChain)
entry =
                            ([BlockId]
newChainFrontier,BlockChain
newChain) 
                    in forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\FrontierMap
m BlockId
x -> forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> a -> map a -> map a
mapInsert BlockId
x ([BlockId], BlockChain)
entry FrontierMap
m)
                              FrontierMap
withoutOld [BlockId]
newChainFrontier
                  newEnds :: FrontierMap
newEnds =
                    let withoutOld :: FrontierMap
withoutOld = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\FrontierMap
m BlockId
b -> forall (map :: * -> *) a. IsMap map => KeyOf map -> map a -> map a
mapDelete BlockId
b FrontierMap
m) FrontierMap
chainEnds ([BlockId]
c1_e forall a. [a] -> [a] -> [a]
++ BlockChain -> [BlockId]
getEnds BlockChain
c2)
                        entry :: ([BlockId], BlockChain)
entry = ([BlockId]
newChainEnds,BlockChain
newChain) 
                    in forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\FrontierMap
m BlockId
x -> forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> a -> map a -> map a
mapInsert BlockId
x ([BlockId], BlockChain)
entry FrontierMap
m)
                              FrontierMap
withoutOld [BlockId]
newChainEnds
              in
                
                
                
                
                
                
                
                
                
                
                
                
                
                 [CfgEdge]
-> FrontierMap
-> FrontierMap
-> Set (BlockId, BlockId)
-> ([BlockChain], Set (BlockId, BlockId))
applyEdges [CfgEdge]
edges FrontierMap
newEnds FrontierMap
newFronts (forall a. Ord a => a -> Set a -> Set a
Set.insert (BlockId
from,BlockId
to) Set (BlockId, BlockId)
combined)
            | Bool
otherwise
            = [CfgEdge]
-> FrontierMap
-> FrontierMap
-> Set (BlockId, BlockId)
-> ([BlockChain], Set (BlockId, BlockId))
applyEdges [CfgEdge]
edges FrontierMap
chainEnds FrontierMap
chainFronts Set (BlockId, BlockId)
combined
        getFronts :: BlockChain -> [BlockId]
getFronts BlockChain
chain = Int -> BlockChain -> [BlockId]
takeL Int
neighbourOverlapp BlockChain
chain
        getEnds :: BlockChain -> [BlockId]
getEnds BlockChain
chain = Int -> BlockChain -> [BlockId]
takeR Int
neighbourOverlapp BlockChain
chain
mergeChains :: [CfgEdge] -> [BlockChain]
            -> (BlockChain)
mergeChains :: [CfgEdge] -> [BlockChain] -> BlockChain
mergeChains [CfgEdge]
edges [BlockChain]
chains
    = forall a. (forall s. ST s a) -> a
runST forall a b. (a -> b) -> a -> b
$ do
        let addChain :: map (Point s BlockChain)
-> BlockChain -> ST s (map (Point s BlockChain))
addChain map (Point s BlockChain)
m0 BlockChain
chain = do
                Point s BlockChain
ref <- forall a s. a -> ST s (Point s a)
fresh BlockChain
chain
                forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall b. (b -> BlockId -> b) -> b -> BlockChain -> b
chainFoldl (\map (Point s BlockChain)
m' BlockId
b -> forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> a -> map a -> map a
mapInsert BlockId
b Point s BlockChain
ref map (Point s BlockChain)
m') map (Point s BlockChain)
m0 BlockChain
chain
        LabelMap (Point s BlockChain)
chainMap' <- forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (\LabelMap (Point s BlockChain)
m0 BlockChain
c -> forall {map :: * -> *} {s}.
(KeyOf map ~ BlockId, IsMap map) =>
map (Point s BlockChain)
-> BlockChain -> ST s (map (Point s BlockChain))
addChain LabelMap (Point s BlockChain)
m0 BlockChain
c) forall (map :: * -> *) a. IsMap map => map a
mapEmpty [BlockChain]
chains
        forall s.
[CfgEdge] -> LabelMap (Point s BlockChain) -> ST s BlockChain
merge [CfgEdge]
edges LabelMap (Point s BlockChain)
chainMap'
    where
        
        
        
        
        merge :: forall s. [CfgEdge] -> LabelMap (Point s BlockChain) -> ST s BlockChain
        merge :: forall s.
[CfgEdge] -> LabelMap (Point s BlockChain) -> ST s BlockChain
merge [] LabelMap (Point s BlockChain)
chains = do
            [BlockChain]
chains' <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall s a. Point s a -> ST s a
find forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (forall a. Eq a => [a] -> [a]
nub forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall s a. Point s a -> ST s (Point s a)
repr forall a b. (a -> b) -> a -> b
$ forall (map :: * -> *) a. IsMap map => map a -> [a]
mapElems LabelMap (Point s BlockChain)
chains)) :: ST s [BlockChain]
            forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' BlockChain -> BlockChain -> BlockChain
chainConcat (forall a. [a] -> a
head [BlockChain]
chains') (forall a. [a] -> [a]
tail [BlockChain]
chains')
        merge ((CfgEdge BlockId
from BlockId
to EdgeInfo
_):[CfgEdge]
edges) LabelMap (Point s BlockChain)
chains
        
        
          = do
            Bool
same <- forall s a. Point s a -> Point s a -> ST s Bool
equivalent Point s BlockChain
cFrom Point s BlockChain
cTo
            forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
same forall a b. (a -> b) -> a -> b
$ do
              BlockChain
cRight <- forall s a. Point s a -> ST s a
find Point s BlockChain
cTo
              BlockChain
cLeft <- forall s a. Point s a -> ST s a
find Point s BlockChain
cFrom
              Point s BlockChain
new_point <- forall a s. a -> ST s (Point s a)
fresh (BlockChain -> BlockChain -> BlockChain
chainConcat BlockChain
cLeft BlockChain
cRight)
              forall s a. Point s a -> Point s a -> ST s ()
union Point s BlockChain
cTo Point s BlockChain
new_point
              forall s a. Point s a -> Point s a -> ST s ()
union Point s BlockChain
cFrom Point s BlockChain
new_point
            forall s.
[CfgEdge] -> LabelMap (Point s BlockChain) -> ST s BlockChain
merge [CfgEdge]
edges LabelMap (Point s BlockChain)
chains
          where
            cFrom :: Point s BlockChain
cFrom = forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"mergeChains:chainMap:from" forall a b. (a -> b) -> a -> b
$ forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
mapLookup BlockId
from LabelMap (Point s BlockChain)
chains
            cTo :: Point s BlockChain
cTo = forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"mergeChains:chainMap:to"   forall a b. (a -> b) -> a -> b
$ forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
mapLookup BlockId
to   LabelMap (Point s BlockChain)
chains
buildChains :: [CfgEdge] -> [BlockId]
            -> ( LabelMap BlockChain  
               , Set.Set (BlockId, BlockId)) 
buildChains :: [CfgEdge]
-> [BlockId] -> (LabelMap BlockChain, Set (BlockId, BlockId))
buildChains [CfgEdge]
edges [BlockId]
blocks
  = forall a. (forall s. ST s a) -> a
runST forall a b. (a -> b) -> a -> b
$ forall s.
LabelSet
-> LabelMap (STRef s BlockChain)
-> LabelMap (STRef s BlockChain)
-> [CfgEdge]
-> Set (BlockId, BlockId)
-> ST s (LabelMap BlockChain, Set (BlockId, BlockId))
buildNext forall set. IsSet set => set
setEmpty forall (map :: * -> *) a. IsMap map => map a
mapEmpty forall (map :: * -> *) a. IsMap map => map a
mapEmpty [CfgEdge]
edges forall a. Set a
Set.empty
  where
    
    
    
    
    
    
    buildNext :: forall s. LabelSet
              -> LabelMap (STRef s BlockChain) 
              -> LabelMap (STRef s BlockChain) 
              -> [CfgEdge] 
              -> Set.Set (BlockId, BlockId) 
              -> ST s   ( LabelMap BlockChain 
                        , Set.Set (BlockId, BlockId) 
                        )
    buildNext :: forall s.
LabelSet
-> LabelMap (STRef s BlockChain)
-> LabelMap (STRef s BlockChain)
-> [CfgEdge]
-> Set (BlockId, BlockId)
-> ST s (LabelMap BlockChain, Set (BlockId, BlockId))
buildNext LabelSet
placed LabelMap (STRef s BlockChain)
_chainStarts LabelMap (STRef s BlockChain)
chainEnds  [] Set (BlockId, BlockId)
linked = do
        LabelMap BlockChain
ends' <- forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence forall a b. (a -> b) -> a -> b
$ forall (map :: * -> *) a b. IsMap map => (a -> b) -> map a -> map b
mapMap forall s a. STRef s a -> ST s a
readSTRef LabelMap (STRef s BlockChain)
chainEnds :: ST s (LabelMap BlockChain)
        
        
        let unplaced :: [BlockId]
unplaced = forall a. (a -> Bool) -> [a] -> [a]
filter (\BlockId
x -> Bool -> Bool
not (forall set. IsSet set => ElemOf set -> set -> Bool
setMember BlockId
x LabelSet
placed)) [BlockId]
blocks
            singletons :: [(BlockId, BlockChain)]
singletons = forall a b. (a -> b) -> [a] -> [b]
map (\BlockId
x -> (BlockId
x,BlockId -> BlockChain
chainSingleton BlockId
x)) [BlockId]
unplaced :: [(BlockId,BlockChain)]
        forall (m :: * -> *) a. Monad m => a -> m a
return (forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\LabelMap BlockChain
m (BlockId
k,BlockChain
v) -> forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> a -> map a -> map a
mapInsert BlockId
k BlockChain
v LabelMap BlockChain
m) LabelMap BlockChain
ends' [(BlockId, BlockChain)]
singletons , Set (BlockId, BlockId)
linked)
    buildNext LabelSet
placed LabelMap (STRef s BlockChain)
chainStarts LabelMap (STRef s BlockChain)
chainEnds (CfgEdge
edge:[CfgEdge]
todo) Set (BlockId, BlockId)
linked
        | BlockId
from forall a. Eq a => a -> a -> Bool
== BlockId
to
        
        = forall s.
LabelSet
-> LabelMap (STRef s BlockChain)
-> LabelMap (STRef s BlockChain)
-> [CfgEdge]
-> Set (BlockId, BlockId)
-> ST s (LabelMap BlockChain, Set (BlockId, BlockId))
buildNext LabelSet
placed LabelMap (STRef s BlockChain)
chainStarts LabelMap (STRef s BlockChain)
chainEnds [CfgEdge]
todo (forall a. Ord a => a -> Set a -> Set a
Set.insert (BlockId
from,BlockId
to) Set (BlockId, BlockId)
linked)
        | Bool -> Bool
not (BlockId -> Bool
alreadyPlaced BlockId
from) Bool -> Bool -> Bool
&&
          Bool -> Bool
not (BlockId -> Bool
alreadyPlaced BlockId
to)
        = do
            
            STRef s BlockChain
chain' <- forall a s. a -> ST s (STRef s a)
newSTRef forall a b. (a -> b) -> a -> b
$ [BlockId] -> BlockChain
chainFromList [BlockId
from,BlockId
to]
            forall s.
LabelSet
-> LabelMap (STRef s BlockChain)
-> LabelMap (STRef s BlockChain)
-> [CfgEdge]
-> Set (BlockId, BlockId)
-> ST s (LabelMap BlockChain, Set (BlockId, BlockId))
buildNext
                (forall set. IsSet set => ElemOf set -> set -> set
setInsert BlockId
to (forall set. IsSet set => ElemOf set -> set -> set
setInsert BlockId
from LabelSet
placed))
                (forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> a -> map a -> map a
mapInsert BlockId
from STRef s BlockChain
chain' LabelMap (STRef s BlockChain)
chainStarts)
                (forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> a -> map a -> map a
mapInsert BlockId
to STRef s BlockChain
chain' LabelMap (STRef s BlockChain)
chainEnds)
                [CfgEdge]
todo
                (forall a. Ord a => a -> Set a -> Set a
Set.insert (BlockId
from,BlockId
to) Set (BlockId, BlockId)
linked)
        | (BlockId -> Bool
alreadyPlaced BlockId
from) Bool -> Bool -> Bool
&&
          (BlockId -> Bool
alreadyPlaced BlockId
to)
        , Just STRef s BlockChain
predChain <- forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
mapLookup BlockId
from LabelMap (STRef s BlockChain)
chainEnds
        , Just STRef s BlockChain
succChain <- forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
mapLookup BlockId
to LabelMap (STRef s BlockChain)
chainStarts
        , STRef s BlockChain
predChain forall a. Eq a => a -> a -> Bool
/= STRef s BlockChain
succChain 
          = STRef s BlockChain
-> STRef s BlockChain
-> ST s (LabelMap BlockChain, Set (BlockId, BlockId))
fuseChain STRef s BlockChain
predChain STRef s BlockChain
succChain
        | (BlockId -> Bool
alreadyPlaced BlockId
from) Bool -> Bool -> Bool
&&
          (BlockId -> Bool
alreadyPlaced BlockId
to)
          = forall s.
LabelSet
-> LabelMap (STRef s BlockChain)
-> LabelMap (STRef s BlockChain)
-> [CfgEdge]
-> Set (BlockId, BlockId)
-> ST s (LabelMap BlockChain, Set (BlockId, BlockId))
buildNext LabelSet
placed LabelMap (STRef s BlockChain)
chainStarts LabelMap (STRef s BlockChain)
chainEnds [CfgEdge]
todo Set (BlockId, BlockId)
linked
        | Bool
otherwise
          = ST s (LabelMap BlockChain, Set (BlockId, BlockId))
findChain
      where
        from :: BlockId
from = CfgEdge -> BlockId
edgeFrom CfgEdge
edge
        to :: BlockId
to   = CfgEdge -> BlockId
edgeTo   CfgEdge
edge
        alreadyPlaced :: BlockId -> Bool
alreadyPlaced BlockId
blkId = (forall set. IsSet set => ElemOf set -> set -> Bool
setMember BlockId
blkId LabelSet
placed)
        
        fuseChain :: STRef s BlockChain -> STRef s BlockChain
                  -> ST s   ( LabelMap BlockChain 
                            , Set.Set (BlockId, BlockId) 
                            )
        fuseChain :: STRef s BlockChain
-> STRef s BlockChain
-> ST s (LabelMap BlockChain, Set (BlockId, BlockId))
fuseChain STRef s BlockChain
fromRef STRef s BlockChain
toRef = do
            BlockChain
fromChain <- forall s a. STRef s a -> ST s a
readSTRef STRef s BlockChain
fromRef
            BlockChain
toChain <- forall s a. STRef s a -> ST s a
readSTRef STRef s BlockChain
toRef
            let newChain :: BlockChain
newChain = BlockChain -> BlockChain -> BlockChain
chainConcat BlockChain
fromChain BlockChain
toChain
            STRef s BlockChain
ref <- forall a s. a -> ST s (STRef s a)
newSTRef BlockChain
newChain
            let start :: BlockId
start = forall a. [a] -> a
head forall a b. (a -> b) -> a -> b
$ Int -> BlockChain -> [BlockId]
takeL Int
1 BlockChain
newChain
            let end :: BlockId
end = forall a. [a] -> a
head forall a b. (a -> b) -> a -> b
$ Int -> BlockChain -> [BlockId]
takeR Int
1 BlockChain
newChain
            
            
            forall s.
LabelSet
-> LabelMap (STRef s BlockChain)
-> LabelMap (STRef s BlockChain)
-> [CfgEdge]
-> Set (BlockId, BlockId)
-> ST s (LabelMap BlockChain, Set (BlockId, BlockId))
buildNext
                LabelSet
placed
                (forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> a -> map a -> map a
mapInsert BlockId
start STRef s BlockChain
ref forall a b. (a -> b) -> a -> b
$ forall (map :: * -> *) a. IsMap map => KeyOf map -> map a -> map a
mapDelete BlockId
to forall a b. (a -> b) -> a -> b
$ LabelMap (STRef s BlockChain)
chainStarts)
                (forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> a -> map a -> map a
mapInsert BlockId
end STRef s BlockChain
ref forall a b. (a -> b) -> a -> b
$ forall (map :: * -> *) a. IsMap map => KeyOf map -> map a -> map a
mapDelete BlockId
from forall a b. (a -> b) -> a -> b
$ LabelMap (STRef s BlockChain)
chainEnds)
                [CfgEdge]
todo
                (forall a. Ord a => a -> Set a -> Set a
Set.insert (BlockId
from,BlockId
to) Set (BlockId, BlockId)
linked)
        
        findChain :: ST s   ( LabelMap BlockChain 
                            , Set.Set (BlockId, BlockId) 
                            )
        findChain :: ST s (LabelMap BlockChain, Set (BlockId, BlockId))
findChain
          
          | BlockId -> Bool
alreadyPlaced BlockId
from
          , Just STRef s BlockChain
predChain <- forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
mapLookup BlockId
from LabelMap (STRef s BlockChain)
chainEnds
          = do
            BlockChain
chain <- forall s a. STRef s a -> ST s a
readSTRef STRef s BlockChain
predChain
            let newChain :: BlockChain
newChain = BlockChain -> BlockId -> BlockChain
chainSnoc BlockChain
chain BlockId
to
            forall s a. STRef s a -> a -> ST s ()
writeSTRef STRef s BlockChain
predChain BlockChain
newChain
            let chainEnds' :: LabelMap (STRef s BlockChain)
chainEnds' = forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> a -> map a -> map a
mapInsert BlockId
to STRef s BlockChain
predChain forall a b. (a -> b) -> a -> b
$ forall (map :: * -> *) a. IsMap map => KeyOf map -> map a -> map a
mapDelete BlockId
from LabelMap (STRef s BlockChain)
chainEnds
            
            
            forall s.
LabelSet
-> LabelMap (STRef s BlockChain)
-> LabelMap (STRef s BlockChain)
-> [CfgEdge]
-> Set (BlockId, BlockId)
-> ST s (LabelMap BlockChain, Set (BlockId, BlockId))
buildNext (forall set. IsSet set => ElemOf set -> set -> set
setInsert BlockId
to LabelSet
placed) LabelMap (STRef s BlockChain)
chainStarts LabelMap (STRef s BlockChain)
chainEnds' [CfgEdge]
todo (forall a. Ord a => a -> Set a -> Set a
Set.insert (BlockId
from,BlockId
to) Set (BlockId, BlockId)
linked)
          
          | BlockId -> Bool
alreadyPlaced BlockId
to
          , Just STRef s BlockChain
succChain <- forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
mapLookup BlockId
to LabelMap (STRef s BlockChain)
chainStarts
          = do
            BlockChain
chain <- forall s a. STRef s a -> ST s a
readSTRef STRef s BlockChain
succChain
            let newChain :: BlockChain
newChain = BlockId
from BlockId -> BlockChain -> BlockChain
`chainCons` BlockChain
chain
            forall s a. STRef s a -> a -> ST s ()
writeSTRef STRef s BlockChain
succChain BlockChain
newChain
            let chainStarts' :: LabelMap (STRef s BlockChain)
chainStarts' = forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> a -> map a -> map a
mapInsert BlockId
from STRef s BlockChain
succChain forall a b. (a -> b) -> a -> b
$ forall (map :: * -> *) a. IsMap map => KeyOf map -> map a -> map a
mapDelete BlockId
to LabelMap (STRef s BlockChain)
chainStarts
            
            
            forall s.
LabelSet
-> LabelMap (STRef s BlockChain)
-> LabelMap (STRef s BlockChain)
-> [CfgEdge]
-> Set (BlockId, BlockId)
-> ST s (LabelMap BlockChain, Set (BlockId, BlockId))
buildNext (forall set. IsSet set => ElemOf set -> set -> set
setInsert BlockId
from LabelSet
placed) LabelMap (STRef s BlockChain)
chainStarts' LabelMap (STRef s BlockChain)
chainEnds [CfgEdge]
todo (forall a. Ord a => a -> Set a -> Set a
Set.insert (BlockId
from,BlockId
to) Set (BlockId, BlockId)
linked)
          
          | Bool
otherwise
          = do
            let block :: BlockId
block    = if BlockId -> Bool
alreadyPlaced BlockId
to then BlockId
from else BlockId
to
            
            let newChain :: BlockChain
newChain = BlockId -> BlockChain
chainSingleton BlockId
block
            STRef s BlockChain
ref <- forall a s. a -> ST s (STRef s a)
newSTRef BlockChain
newChain
            forall s.
LabelSet
-> LabelMap (STRef s BlockChain)
-> LabelMap (STRef s BlockChain)
-> [CfgEdge]
-> Set (BlockId, BlockId)
-> ST s (LabelMap BlockChain, Set (BlockId, BlockId))
buildNext (forall set. IsSet set => ElemOf set -> set -> set
setInsert BlockId
block LabelSet
placed) (forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> a -> map a -> map a
mapInsert BlockId
block STRef s BlockChain
ref LabelMap (STRef s BlockChain)
chainStarts)
                      (forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> a -> map a -> map a
mapInsert BlockId
block STRef s BlockChain
ref LabelMap (STRef s BlockChain)
chainEnds) [CfgEdge]
todo (Set (BlockId, BlockId)
linked)
            where
              alreadyPlaced :: BlockId -> Bool
alreadyPlaced BlockId
blkId = (forall set. IsSet set => ElemOf set -> set -> Bool
setMember BlockId
blkId LabelSet
placed)
sequenceChain :: forall a i. Instruction i
              => LabelMap a 
              -> CFG 
              -> [GenBasicBlock i] 
              -> [GenBasicBlock i] 
sequenceChain :: forall a i.
Instruction i =>
LabelMap a -> CFG -> [GenBasicBlock i] -> [GenBasicBlock i]
sequenceChain LabelMap a
_info CFG
_weights    [] = []
sequenceChain LabelMap a
_info CFG
_weights    [GenBasicBlock i
x] = [GenBasicBlock i
x]
sequenceChain  LabelMap a
info CFG
weights     blocks :: [GenBasicBlock i]
blocks@((BasicBlock BlockId
entry [i]
_):[GenBasicBlock i]
_) =
    let directEdges :: [CfgEdge]
        directEdges :: [CfgEdge]
directEdges = forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Ord a => a -> a -> Ordering
compare) forall a b. (a -> b) -> a -> b
$ forall a. [Maybe a] -> [a]
catMaybes forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map CfgEdge -> Maybe CfgEdge
relevantWeight forall a b. (a -> b) -> a -> b
$ (CFG -> [CfgEdge]
infoEdgeList CFG
weights)
          where
            
            
            
            relevantWeight :: CfgEdge -> Maybe CfgEdge
            relevantWeight :: CfgEdge -> Maybe CfgEdge
relevantWeight edge :: CfgEdge
edge@(CfgEdge BlockId
from BlockId
to EdgeInfo
edgeInfo)
                | (EdgeInfo CmmSource { trans_cmmNode :: TransitionSource -> CmmNode O C
trans_cmmNode = CmmCall {} } EdgeWeight
_) <- EdgeInfo
edgeInfo
                
                = forall a. Maybe a
Nothing
                | forall (map :: * -> *) a. IsMap map => KeyOf map -> map a -> Bool
mapMember BlockId
to LabelMap a
info
                , EdgeWeight
w <- EdgeInfo -> EdgeWeight
edgeWeight EdgeInfo
edgeInfo
                
                = forall a. a -> Maybe a
Just (BlockId -> BlockId -> EdgeInfo -> CfgEdge
CfgEdge BlockId
from BlockId
to EdgeInfo
edgeInfo { edgeWeight :: EdgeWeight
edgeWeight = EdgeWeight
wforall a. Fractional a => a -> a -> a
/EdgeWeight
8 })
                | (EdgeInfo CmmSource { trans_cmmNode :: TransitionSource -> CmmNode O C
trans_cmmNode = CmmNode O C
exitNode } EdgeWeight
_) <- EdgeInfo
edgeInfo
                , forall {e :: Extensibility} {x :: Extensibility}.
CmmNode e x -> Bool
cantEliminate CmmNode O C
exitNode
                , EdgeWeight
w <- EdgeInfo -> EdgeWeight
edgeWeight EdgeInfo
edgeInfo
                
                
                
                = forall a. a -> Maybe a
Just (BlockId -> BlockId -> EdgeInfo -> CfgEdge
CfgEdge BlockId
from BlockId
to EdgeInfo
edgeInfo { edgeWeight :: EdgeWeight
edgeWeight = EdgeWeight
w forall a. Num a => a -> a -> a
* EdgeWeight
0.96875 })
                | Bool
otherwise
                = forall a. a -> Maybe a
Just CfgEdge
edge
                where
                  cantEliminate :: CmmNode e x -> Bool
cantEliminate CmmCondBranch {} = Bool
True
                  cantEliminate CmmSwitch {} = Bool
True
                  cantEliminate CmmNode e x
_ = Bool
False
        blockMap :: LabelMap (GenBasicBlock i)
        blockMap :: LabelMap (GenBasicBlock i)
blockMap
            = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\LabelMap (GenBasicBlock i)
m blk :: GenBasicBlock i
blk@(BasicBlock BlockId
lbl [i]
_ins) ->
                        forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> a -> map a -> map a
mapInsert BlockId
lbl GenBasicBlock i
blk LabelMap (GenBasicBlock i)
m)
                     forall (map :: * -> *) a. IsMap map => map a
mapEmpty [GenBasicBlock i]
blocks
        (LabelMap BlockChain
builtChains, Set (BlockId, BlockId)
builtEdges)
            = {-# SCC "buildChains" #-}
              
              
              [CfgEdge]
-> [BlockId] -> (LabelMap BlockChain, Set (BlockId, BlockId))
buildChains [CfgEdge]
directEdges (forall (map :: * -> *) a. IsMap map => map a -> [KeyOf map]
mapKeys LabelMap (GenBasicBlock i)
blockMap)
        rankedEdges :: [CfgEdge]
        
        rankedEdges :: [CfgEdge]
rankedEdges =
            forall a. (a -> Bool) -> [a] -> [a]
filter (\CfgEdge
edge -> Bool -> Bool
not (forall a. Ord a => a -> Set a -> Bool
Set.member (CfgEdge -> BlockId
edgeFrom CfgEdge
edge,CfgEdge -> BlockId
edgeTo CfgEdge
edge) Set (BlockId, BlockId)
builtEdges)) forall a b. (a -> b) -> a -> b
$
            [CfgEdge]
directEdges
        ([BlockChain]
neighbourChains, Set (BlockId, BlockId)
combined)
            = ASSERT(noDups $ mapElems builtChains)
              {-# SCC "groupNeighbourChains" #-}
            
              [CfgEdge] -> [BlockChain] -> ([BlockChain], Set (BlockId, BlockId))
combineNeighbourhood [CfgEdge]
rankedEdges (forall (map :: * -> *) a. IsMap map => map a -> [a]
mapElems LabelMap BlockChain
builtChains)
        allEdges :: [CfgEdge]
        allEdges :: [CfgEdge]
allEdges = {-# SCC allEdges #-}
                   forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (CfgEdge -> EdgeWeight
relevantWeight) forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. CfgEdge -> Bool
deadEdge) forall a b. (a -> b) -> a -> b
$ (CFG -> [CfgEdge]
infoEdgeList CFG
weights)
          where
            deadEdge :: CfgEdge -> Bool
            deadEdge :: CfgEdge -> Bool
deadEdge (CfgEdge BlockId
from BlockId
to EdgeInfo
_) = let e :: (BlockId, BlockId)
e = (BlockId
from,BlockId
to) in forall a. Ord a => a -> Set a -> Bool
Set.member (BlockId, BlockId)
e Set (BlockId, BlockId)
combined Bool -> Bool -> Bool
|| forall a. Ord a => a -> Set a -> Bool
Set.member (BlockId, BlockId)
e Set (BlockId, BlockId)
builtEdges
            relevantWeight :: CfgEdge -> EdgeWeight
            relevantWeight :: CfgEdge -> EdgeWeight
relevantWeight (CfgEdge BlockId
_ BlockId
_ EdgeInfo
edgeInfo)
                | EdgeInfo (CmmSource { trans_cmmNode :: TransitionSource -> CmmNode O C
trans_cmmNode = CmmCall {}}) EdgeWeight
_ <- EdgeInfo
edgeInfo
                
                = EdgeWeight
weightforall a. Fractional a => a -> a -> a
/(EdgeWeight
64.0)
                | Bool
otherwise
                = EdgeWeight
weight
              where
                
                weight :: EdgeWeight
weight = forall a. Num a => a -> a
negate (EdgeInfo -> EdgeWeight
edgeWeight EdgeInfo
edgeInfo)
        masterChain :: BlockChain
masterChain =
            {-# SCC "mergeChains" #-}
            
            [CfgEdge] -> [BlockChain] -> BlockChain
mergeChains [CfgEdge]
allEdges [BlockChain]
neighbourChains
        
        prepedChains :: [BlockChain]
prepedChains
            | BlockId -> BlockChain -> Bool
inFront BlockId
entry BlockChain
masterChain
            = [BlockChain
masterChain]
            | (BlockChain
rest,BlockChain
entry) <- BlockId -> BlockChain -> (BlockChain, BlockChain)
breakChainAt BlockId
entry BlockChain
masterChain
            = [BlockChain
entry,BlockChain
rest]
#if __GLASGOW_HASKELL__ <= 810
            | otherwise = pprPanic "Entry point eliminated" $
                            ppr masterChain
#endif
        blockList :: [BlockId]
blockList
            = ASSERT(noDups [masterChain])
              (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall a. OrdList a -> [a]
fromOL forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map BlockChain -> OrdList BlockId
chainBlocks [BlockChain]
prepedChains)
        
        chainPlaced :: LabelSet
chainPlaced = forall set. IsSet set => [ElemOf set] -> set
setFromList forall a b. (a -> b) -> a -> b
$ [BlockId]
blockList :: LabelSet
        unplaced :: [BlockId]
unplaced =
            let blocks :: [KeyOf LabelMap]
blocks = forall (map :: * -> *) a. IsMap map => map a -> [KeyOf map]
mapKeys LabelMap (GenBasicBlock i)
blockMap
                isPlaced :: BlockId -> Bool
isPlaced BlockId
b = forall set. IsSet set => ElemOf set -> set -> Bool
setMember (BlockId
b) LabelSet
chainPlaced
            in forall a. (a -> Bool) -> [a] -> [a]
filter (\BlockId
block -> Bool -> Bool
not (BlockId -> Bool
isPlaced BlockId
block)) [KeyOf LabelMap]
blocks
        placedBlocks :: [BlockId]
placedBlocks =
            
            
            
            ASSERT(null unplaced)
            
            
            if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [BlockId]
unplaced then [BlockId]
blockList else [BlockId]
blockList forall a. [a] -> [a] -> [a]
++ [BlockId]
unplaced
        getBlock :: BlockId -> GenBasicBlock i
getBlock BlockId
bid = forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"Block placement" forall a b. (a -> b) -> a -> b
$ forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
mapLookup BlockId
bid LabelMap (GenBasicBlock i)
blockMap
    in
        
        ASSERT(all (\bid -> mapMember bid blockMap) placedBlocks)
        forall a i.
Instruction i =>
LabelMap a -> [GenBasicBlock i] -> [GenBasicBlock i]
dropJumps LabelMap a
info forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map BlockId -> GenBasicBlock i
getBlock [BlockId]
placedBlocks
{-# SCC dropJumps #-}
dropJumps :: forall a i. Instruction i => LabelMap a -> [GenBasicBlock i]
          -> [GenBasicBlock i]
dropJumps :: forall a i.
Instruction i =>
LabelMap a -> [GenBasicBlock i] -> [GenBasicBlock i]
dropJumps LabelMap a
_    [] = []
dropJumps LabelMap a
info ((BasicBlock BlockId
lbl [i]
ins):[GenBasicBlock i]
todo)
    | Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall a b. (a -> b) -> a -> b
$ [i]
ins 
    , [BlockId
dest] <- forall instr. Instruction instr => instr -> [BlockId]
jumpDestsOfInstr (forall a. [a] -> a
last [i]
ins)
    , ((BasicBlock BlockId
nextLbl [i]
_) : [GenBasicBlock i]
_) <- [GenBasicBlock i]
todo
    , Bool -> Bool
not (forall (map :: * -> *) a. IsMap map => KeyOf map -> map a -> Bool
mapMember BlockId
dest LabelMap a
info)
    , BlockId
nextLbl forall a. Eq a => a -> a -> Bool
== BlockId
dest
    = forall i. BlockId -> [i] -> GenBasicBlock i
BasicBlock BlockId
lbl (forall a. [a] -> [a]
init [i]
ins) forall a. a -> [a] -> [a]
: forall a i.
Instruction i =>
LabelMap a -> [GenBasicBlock i] -> [GenBasicBlock i]
dropJumps LabelMap a
info [GenBasicBlock i]
todo
    | Bool
otherwise
    = forall i. BlockId -> [i] -> GenBasicBlock i
BasicBlock BlockId
lbl [i]
ins forall a. a -> [a] -> [a]
: forall a i.
Instruction i =>
LabelMap a -> [GenBasicBlock i] -> [GenBasicBlock i]
dropJumps LabelMap a
info [GenBasicBlock i]
todo
sequenceTop
    :: Instruction instr
    => NcgImpl statics instr jumpDest
    -> Maybe CFG 
    -> NatCmmDecl statics instr 
    -> NatCmmDecl statics instr
sequenceTop :: forall instr statics jumpDest.
Instruction instr =>
NcgImpl statics instr jumpDest
-> Maybe CFG
-> NatCmmDecl statics instr
-> NatCmmDecl statics instr
sequenceTop NcgImpl statics instr jumpDest
_       Maybe CFG
_           top :: NatCmmDecl statics instr
top@(CmmData Section
_ statics
_) = NatCmmDecl statics instr
top
sequenceTop NcgImpl statics instr jumpDest
ncgImpl Maybe CFG
edgeWeights (CmmProc LabelMap RawCmmStatics
info CLabel
lbl [GlobalReg]
live (ListGraph [GenBasicBlock instr]
blocks))
  = let
      config :: NCGConfig
config     = forall statics instr jumpDest.
NcgImpl statics instr jumpDest -> NCGConfig
ncgConfig NcgImpl statics instr jumpDest
ncgImpl
      platform :: Platform
platform   = NCGConfig -> Platform
ncgPlatform NCGConfig
config
    in forall d h g. h -> CLabel -> [GlobalReg] -> g -> GenCmmDecl d h g
CmmProc LabelMap RawCmmStatics
info CLabel
lbl [GlobalReg]
live forall a b. (a -> b) -> a -> b
$ forall i. [GenBasicBlock i] -> ListGraph i
ListGraph forall a b. (a -> b) -> a -> b
$ forall statics instr jumpDest.
NcgImpl statics instr jumpDest
-> LabelMap RawCmmStatics
-> [NatBasicBlock instr]
-> [NatBasicBlock instr]
ncgMakeFarBranches NcgImpl statics instr jumpDest
ncgImpl LabelMap RawCmmStatics
info forall a b. (a -> b) -> a -> b
$
         if 
            | NCGConfig -> Bool
ncgCfgBlockLayout NCGConfig
config
            , Platform -> Bool
backendMaintainsCfg Platform
platform
            , Just CFG
cfg <- Maybe CFG
edgeWeights
            -> {-# SCC layoutBlocks #-} forall a i.
Instruction i =>
LabelMap a -> CFG -> [GenBasicBlock i] -> [GenBasicBlock i]
sequenceChain LabelMap RawCmmStatics
info CFG
cfg [GenBasicBlock instr]
blocks
            
            | NCGConfig -> Bool
ncgCfgWeightlessLayout NCGConfig
config
               Bool -> Bool -> Bool
|| Bool -> Bool
not (Platform -> Bool
backendMaintainsCfg Platform
platform)
            -> {-# SCC layoutBlocks #-} forall inst a.
Instruction inst =>
Maybe CFG
-> LabelMap a -> [GenBasicBlock inst] -> [GenBasicBlock inst]
sequenceBlocks forall a. Maybe a
Nothing LabelMap RawCmmStatics
info [GenBasicBlock instr]
blocks
            
            | Bool
otherwise
            -> {-# SCC layoutBlocks #-} forall inst a.
Instruction inst =>
Maybe CFG
-> LabelMap a -> [GenBasicBlock inst] -> [GenBasicBlock inst]
sequenceBlocks Maybe CFG
edgeWeights LabelMap RawCmmStatics
info [GenBasicBlock instr]
blocks
sequenceBlocks :: Instruction inst => Maybe CFG -> LabelMap a
               -> [GenBasicBlock inst] -> [GenBasicBlock inst]
sequenceBlocks :: forall inst a.
Instruction inst =>
Maybe CFG
-> LabelMap a -> [GenBasicBlock inst] -> [GenBasicBlock inst]
sequenceBlocks Maybe CFG
_edgeWeight LabelMap a
_ [] = []
sequenceBlocks Maybe CFG
edgeWeights LabelMap a
infos (GenBasicBlock inst
entry:[GenBasicBlock inst]
blocks) =
    let entryNode :: Node BlockId (GenBasicBlock inst)
entryNode = forall t.
Instruction t =>
Maybe CFG -> GenBasicBlock t -> Node BlockId (GenBasicBlock t)
mkNode Maybe CFG
edgeWeights GenBasicBlock inst
entry
        bodyNodes :: [Node BlockId (GenBasicBlock inst)]
bodyNodes = forall a. [a] -> [a]
reverse
                    (forall a. [SCC a] -> [a]
flattenSCCs (forall instr.
Instruction instr =>
Maybe CFG
-> [NatBasicBlock instr]
-> [SCC (Node BlockId (NatBasicBlock instr))]
sccBlocks Maybe CFG
edgeWeights [GenBasicBlock inst]
blocks))
    in forall a i.
Instruction i =>
LabelMap a -> [GenBasicBlock i] -> [GenBasicBlock i]
dropJumps LabelMap a
infos forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i t1.
LabelMap i
-> [Node BlockId (GenBasicBlock t1)] -> [GenBasicBlock t1]
seqBlocks LabelMap a
infos forall a b. (a -> b) -> a -> b
$ ( Node BlockId (GenBasicBlock inst)
entryNode forall a. a -> [a] -> [a]
: [Node BlockId (GenBasicBlock inst)]
bodyNodes)
  
sccBlocks
        :: Instruction instr
        => Maybe CFG -> [NatBasicBlock instr]
        -> [SCC (Node BlockId (NatBasicBlock instr))]
sccBlocks :: forall instr.
Instruction instr =>
Maybe CFG
-> [NatBasicBlock instr]
-> [SCC (Node BlockId (NatBasicBlock instr))]
sccBlocks Maybe CFG
edgeWeights [NatBasicBlock instr]
blocks =
    forall key payload.
Uniquable key =>
[Node key payload] -> [SCC (Node key payload)]
stronglyConnCompFromEdgedVerticesUniqR
        (forall a b. (a -> b) -> [a] -> [b]
map (forall t.
Instruction t =>
Maybe CFG -> GenBasicBlock t -> Node BlockId (GenBasicBlock t)
mkNode Maybe CFG
edgeWeights) [NatBasicBlock instr]
blocks)
mkNode :: (Instruction t)
       => Maybe CFG -> GenBasicBlock t
       -> Node BlockId (GenBasicBlock t)
mkNode :: forall t.
Instruction t =>
Maybe CFG -> GenBasicBlock t -> Node BlockId (GenBasicBlock t)
mkNode Maybe CFG
edgeWeights block :: GenBasicBlock t
block@(BasicBlock BlockId
id [t]
instrs) =
    forall key payload. payload -> key -> [key] -> Node key payload
DigraphNode GenBasicBlock t
block BlockId
id [BlockId]
outEdges
  where
    outEdges :: [BlockId]
    outEdges :: [BlockId]
outEdges
      
      = [BlockId]
successor
      where
        successor :: [BlockId]
successor
          | Just [(BlockId, EdgeInfo)]
successors <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (CFG -> BlockId -> [(BlockId, EdgeInfo)]
`getSuccEdgesSorted` BlockId
id)
                                    Maybe CFG
edgeWeights 
          = case [(BlockId, EdgeInfo)]
successors of
            [] -> []
            ((BlockId
target,EdgeInfo
info):[(BlockId, EdgeInfo)]
_)
              | forall (t :: * -> *) a. Foldable t => t a -> Int
length [(BlockId, EdgeInfo)]
successors forall a. Ord a => a -> a -> Bool
> Int
2 Bool -> Bool -> Bool
|| EdgeInfo -> EdgeWeight
edgeWeight EdgeInfo
info forall a. Ord a => a -> a -> Bool
<= EdgeWeight
0 -> []
              | Bool
otherwise -> [BlockId
target]
          | Bool
otherwise
          = case forall instr. Instruction instr => instr -> [BlockId]
jumpDestsOfInstr (forall a. [a] -> a
last [t]
instrs) of
                [BlockId
one] -> [BlockId
one]
                [BlockId]
_many -> []
seqBlocks :: LabelMap i -> [Node BlockId (GenBasicBlock t1)]
                        -> [GenBasicBlock t1]
seqBlocks :: forall i t1.
LabelMap i
-> [Node BlockId (GenBasicBlock t1)] -> [GenBasicBlock t1]
seqBlocks LabelMap i
infos [Node BlockId (GenBasicBlock t1)]
blocks = UniqFM BlockId (GenBasicBlock t1, [BlockId])
-> [BlockId] -> [GenBasicBlock t1]
placeNext UniqFM BlockId (GenBasicBlock t1, [BlockId])
pullable0 [BlockId]
todo0
  where
    
    
    
    
    
    pullable0 :: UniqFM BlockId (GenBasicBlock t1, [BlockId])
pullable0 = forall key elt. Uniquable key => [(key, elt)] -> UniqFM key elt
listToUFM [ (BlockId
i,(GenBasicBlock t1
b,[BlockId]
n)) | DigraphNode GenBasicBlock t1
b BlockId
i [BlockId]
n <- [Node BlockId (GenBasicBlock t1)]
blocks ]
    todo0 :: [BlockId]
todo0     = forall a b. (a -> b) -> [a] -> [b]
map forall key payload. Node key payload -> key
node_key [Node BlockId (GenBasicBlock t1)]
blocks
    placeNext :: UniqFM BlockId (GenBasicBlock t1, [BlockId])
-> [BlockId] -> [GenBasicBlock t1]
placeNext UniqFM BlockId (GenBasicBlock t1, [BlockId])
_ [] = []
    placeNext UniqFM BlockId (GenBasicBlock t1, [BlockId])
pullable (BlockId
i:[BlockId]
rest)
        | Just ((GenBasicBlock t1, [BlockId])
block, UniqFM BlockId (GenBasicBlock t1, [BlockId])
pullable') <- forall elt.
UniqFM BlockId elt -> BlockId -> Maybe (elt, UniqFM BlockId elt)
lookupDeleteUFM UniqFM BlockId (GenBasicBlock t1, [BlockId])
pullable BlockId
i
        = UniqFM BlockId (GenBasicBlock t1, [BlockId])
-> [BlockId] -> (GenBasicBlock t1, [BlockId]) -> [GenBasicBlock t1]
place UniqFM BlockId (GenBasicBlock t1, [BlockId])
pullable' [BlockId]
rest (GenBasicBlock t1, [BlockId])
block
        | Bool
otherwise
        
        = UniqFM BlockId (GenBasicBlock t1, [BlockId])
-> [BlockId] -> [GenBasicBlock t1]
placeNext UniqFM BlockId (GenBasicBlock t1, [BlockId])
pullable [BlockId]
rest
    place :: UniqFM BlockId (GenBasicBlock t1, [BlockId])
-> [BlockId] -> (GenBasicBlock t1, [BlockId]) -> [GenBasicBlock t1]
place UniqFM BlockId (GenBasicBlock t1, [BlockId])
pullable [BlockId]
todo (GenBasicBlock t1
block,[])
                          = GenBasicBlock t1
block forall a. a -> [a] -> [a]
: UniqFM BlockId (GenBasicBlock t1, [BlockId])
-> [BlockId] -> [GenBasicBlock t1]
placeNext UniqFM BlockId (GenBasicBlock t1, [BlockId])
pullable [BlockId]
todo
    place UniqFM BlockId (GenBasicBlock t1, [BlockId])
pullable [BlockId]
todo (block :: GenBasicBlock t1
block@(BasicBlock BlockId
id [t1]
instrs),[BlockId
next])
        | forall (map :: * -> *) a. IsMap map => KeyOf map -> map a -> Bool
mapMember BlockId
next LabelMap i
infos
        = GenBasicBlock t1
block forall a. a -> [a] -> [a]
: UniqFM BlockId (GenBasicBlock t1, [BlockId])
-> [BlockId] -> [GenBasicBlock t1]
placeNext UniqFM BlockId (GenBasicBlock t1, [BlockId])
pullable [BlockId]
todo
        | Just ((GenBasicBlock t1, [BlockId])
nextBlock, UniqFM BlockId (GenBasicBlock t1, [BlockId])
pullable') <- forall elt.
UniqFM BlockId elt -> BlockId -> Maybe (elt, UniqFM BlockId elt)
lookupDeleteUFM UniqFM BlockId (GenBasicBlock t1, [BlockId])
pullable BlockId
next
        = forall i. BlockId -> [i] -> GenBasicBlock i
BasicBlock BlockId
id [t1]
instrs forall a. a -> [a] -> [a]
: UniqFM BlockId (GenBasicBlock t1, [BlockId])
-> [BlockId] -> (GenBasicBlock t1, [BlockId]) -> [GenBasicBlock t1]
place UniqFM BlockId (GenBasicBlock t1, [BlockId])
pullable' [BlockId]
todo (GenBasicBlock t1, [BlockId])
nextBlock
        | Bool
otherwise
        = GenBasicBlock t1
block forall a. a -> [a] -> [a]
: UniqFM BlockId (GenBasicBlock t1, [BlockId])
-> [BlockId] -> [GenBasicBlock t1]
placeNext UniqFM BlockId (GenBasicBlock t1, [BlockId])
pullable [BlockId]
todo
    place UniqFM BlockId (GenBasicBlock t1, [BlockId])
_ [BlockId]
_ (GenBasicBlock t1
_,[BlockId]
tooManyNextNodes)
        = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"seqBlocks" (forall a. Outputable a => a -> SDoc
ppr [BlockId]
tooManyNextNodes)
lookupDeleteUFM :: UniqFM BlockId elt -> BlockId
                -> Maybe (elt, UniqFM BlockId elt)
lookupDeleteUFM :: forall elt.
UniqFM BlockId elt -> BlockId -> Maybe (elt, UniqFM BlockId elt)
lookupDeleteUFM UniqFM BlockId elt
m BlockId
k = do 
    elt
v <- forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM UniqFM BlockId elt
m BlockId
k
    forall (m :: * -> *) a. Monad m => a -> m a
return (elt
v, forall key elt.
Uniquable key =>
UniqFM key elt -> key -> UniqFM key elt
delFromUFM UniqFM BlockId elt
m BlockId
k)
backendMaintainsCfg :: Platform -> Bool
backendMaintainsCfg :: Platform -> Bool
backendMaintainsCfg Platform
platform = case Platform -> Arch
platformArch Platform
platform of
    
    Arch
ArchX86_64 -> Bool
True
    Arch
_otherwise -> Bool
False