never executed always true always false
    1 {-# LANGUAGE ConstraintKinds #-}
    2 {-# LANGUAGE TypeFamilies #-}
    3 
    4 {- |
    5 Module      : NITTA.Intermediate.DataFlow
    6 Description : DataFlow graph
    7 Copyright   : (c) Aleksandr Penskoi, 2021
    8 License     : BSD3
    9 Maintainer  : aleksandr.penskoi@gmail.com
   10 Stability   : experimental
   11 -}
   12 module NITTA.Intermediate.DataFlow (
   13     DataFlowGraph (..),
   14     fsToDataFlowGraph,
   15     addFuncToDataFlowGraph,
   16 ) where
   17 
   18 import Data.Default
   19 import Data.List qualified as L
   20 import Data.Set qualified as S
   21 import GHC.Generics
   22 import NITTA.Intermediate.Types
   23 import NITTA.Model.Problems.Refactor
   24 import NITTA.Utils.Base
   25 
   26 {- | Data flow graph - intermediate representation of application algorithm.
   27 Right now can be replaced by @[F v x]@, but for future features like
   28 conduction statement, we don't do that.
   29 -}
   30 data DataFlowGraph v x
   31     = DFLeaf (F v x)
   32     | DFCluster [DataFlowGraph v x]
   33     deriving (Show, Generic)
   34 
   35 instance Default (DataFlowGraph v x) where
   36     def = DFCluster []
   37 
   38 instance Eq (DataFlowGraph v x) where
   39     -- `show` used for avoid `Ord (DataFlowGraph v x)`
   40     (DFCluster c1) == (DFCluster c2) = S.fromList (map show c1) == S.fromList (map show c2)
   41     (DFLeaf f1) == (DFLeaf f2) = f1 == f2
   42     _ == _ = False
   43 
   44 instance Var v => Variables (DataFlowGraph v x) v where
   45     variables (DFLeaf fb) = variables fb
   46     variables (DFCluster g) = unionsMap variables g
   47 
   48 instance WithFunctions (DataFlowGraph v x) (F v x) where
   49     functions (DFLeaf f) = [f]
   50     functions (DFCluster g) = concatMap functions g
   51 
   52 instance (Var v, Val x) => BreakLoopProblem (DataFlowGraph v x) v x where
   53     breakLoopOptions _dfg = []
   54 
   55     breakLoopDecision dfg bl =
   56         let origin = recLoop bl
   57          in fsToDataFlowGraph $
   58                 (recLoopIn bl){funHistory = [origin]}
   59                     : (recLoopOut bl){funHistory = [origin]}
   60                     : (functions dfg L.\\ [origin])
   61 
   62 instance (Var v, Val x) => ConstantFoldingProblem (DataFlowGraph v x) v x where
   63     constantFoldingOptions _dfg = []
   64 
   65     constantFoldingDecision dfg ref@ConstantFolding{} =
   66         fsToDataFlowGraph $ constantFoldingDecision (functions dfg) ref
   67 
   68 instance (Var v, Val x) => OptimizeAccumProblem (DataFlowGraph v x) v x where
   69     optimizeAccumOptions _dfg = []
   70 
   71     optimizeAccumDecision dfg ref@OptimizeAccum{} =
   72         fsToDataFlowGraph $ optimizeAccumDecision (functions dfg) ref
   73 
   74 instance Var v => ResolveDeadlockProblem (DataFlowGraph v x) v x where
   75     resolveDeadlockOptions _dfg = []
   76 
   77     resolveDeadlockDecision dfg ResolveDeadlock{newBuffer, changeset} =
   78         fsToDataFlowGraph (newBuffer : map (patch changeset) (functions dfg))
   79 
   80 -- | Convert @[ F v x ]@ to 'DataFlowGraph'.
   81 fsToDataFlowGraph fs = DFCluster $ map DFLeaf fs
   82 
   83 addFuncToDataFlowGraph f (DFCluster items) = DFCluster (DFLeaf f : items)
   84 addFuncToDataFlowGraph f leaf = DFCluster [DFLeaf f, leaf]