Skip to content

Commit

Permalink
fix permute
Browse files Browse the repository at this point in the history
  • Loading branch information
dpvanbalen committed May 29, 2024
1 parent c84ca7c commit 9424d5b
Show file tree
Hide file tree
Showing 4 changed files with 20 additions and 11 deletions.
3 changes: 3 additions & 0 deletions src/Data/Array/Accelerate/AST/Partitioned.hs
Original file line number Diff line number Diff line change
Expand Up @@ -419,6 +419,9 @@ data Both f g a = Both (f a) (g a) deriving (Show, Eq)
fst' (Both x _) = x
snd' (Both _ y) = y

instance (TupRmonoid f, TupRmonoid g) => TupRmonoid (Both f g) where
pair' (Both a b) (Both c d) = Both (pair' a c) (pair' b d)
unpair' (Both (unpair' -> (a, c)) (unpair' -> (b, d))) = (Both a b, Both c d)


zipArgs :: PreArgs f a -> PreArgs g a -> PreArgs (Both f g) a
Expand Down
3 changes: 2 additions & 1 deletion src/Data/Array/Accelerate/Backend.hs
Original file line number Diff line number Diff line change
Expand Up @@ -79,7 +79,8 @@ import qualified Data.Array.Accelerate.AST.Operation as Operation
import qualified Data.Array.Accelerate.Trafo.Partitioning.ILP.Graph as Graph
import Data.Array.Accelerate.Eval (EvalOp)
import Data.Array.Accelerate.Trafo.Partitioning.ILP.Solve (Objective)
import Data.Array.Accelerate.Trafo.NewNewFusion (Benchmarking(..))
import Data.Array.Accelerate.Trafo.Partitioning.ILP (Benchmarking)


class
( Desugar.DesugarAcc (Operation backend)
Expand Down
6 changes: 2 additions & 4 deletions src/Data/Array/Accelerate/Trafo/NewNewFusion.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,15 +49,13 @@ import Data.Array.Accelerate.Trafo.Partitioning.ILP.Solve (Objective (..))
import System.IO.Unsafe -- for debugging
#endif

data Benchmarking = GreedyFusion | NoFusion
deriving (Show, Eq)

convertAccBench :: (MakesILP op, Pretty.PrettyOp (Cluster op)) => Benchmarking -> OperationAcc op () a -> PartitionedAcc op () a
convertAccBench GreedyFusion = withSimplStats (greedy FusedEdges)
convertAccBench NoFusion = withSimplStats (no FusedEdges)
convertAccBench greedydir = withSimplStats (greedy greedydir FusedEdges)
convertAccBenchF :: (MakesILP op, Pretty.PrettyOp (Cluster op)) => Benchmarking -> OperationAfun op () a -> PartitionedAfun op () a
convertAccBenchF GreedyFusion = withSimplStats (greedyF FusedEdges)
convertAccBenchF NoFusion = withSimplStats (noF FusedEdges)
convertAccBenchF greedydir = withSimplStats (greedyF greedydir FusedEdges)


-- Array Fusion
Expand Down
19 changes: 13 additions & 6 deletions src/Data/Array/Accelerate/Trafo/Partitioning/ILP.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,8 @@ import qualified Data.Set as Set
import Lens.Micro ((^.), (%~), (<>~), (.~))
import Data.Maybe (isJust)

data Benchmarking = GreedyUp | GreedyDown | NoFusion
deriving (Show, Eq)

cbcFusion, gurobiFusion, cplexFusion, glpsolFusion, lpSolveFusion, scipFusion
:: (MakesILP op, Pretty.PrettyOp (Cluster op)) => Objective -> OperationAcc op () a -> PartitionedAcc op () a
Expand Down Expand Up @@ -107,18 +109,21 @@ greedyFusion' :: forall s op x y. (MakesILP op, ILPSolver s op)
=> (x -> (Information op, Map Label (Construction op)))
-> (Graph -> [ClusterLs] -> Map Label [ClusterLs] -> Map Label (Construction op) -> y)
-> s
-> Benchmarking
-> Objective
-> x
-> y
greedyFusion' k1 k2 s obj acc = fusedAcc
greedyFusion' k1 k2 s b obj acc = fusedAcc
where
(info'@(Info graph _ _), constrM') = k1 acc
nedges = graph^.fusibleEdges & Set.size
go :: Int -> Information op -> Information op
go n info -- loop over all fusible edges. Try to set the current one to fused, if there's still a legal solution, keep it fused and continue.
| n >= nedges = info
| otherwise = let
i:->j = graph^.fusibleEdges&Set.elemAt (nedges - n - 1)
i:->j = graph^.fusibleEdges&Set.elemAt (case b of
GreedyUp -> n
GreedyDown -> nedges - n - 1)
info'' = info&constr<>~(fused i j .==. int 0)
in go (n+1) $ if check info'' then info'' else info
check :: Information op -> Bool
Expand All @@ -137,15 +142,17 @@ greedyFusion' k1 k2 s obj acc = fusedAcc
Nothing -> error "Accelerate: No ILP solution found"
Just y -> y

greedy,no :: (MakesILP op, Pretty.PrettyOp (Cluster op)) => Objective -> OperationAcc op () a -> PartitionedAcc op () a
greedy :: (MakesILP op, Pretty.PrettyOp (Cluster op)) => Benchmarking -> Objective -> OperationAcc op () a -> PartitionedAcc op () a
greedy = greedyFusion gurobiCl
no :: (MakesILP op, Pretty.PrettyOp (Cluster op)) => Objective -> OperationAcc op () a -> PartitionedAcc op () a
no = noFusion gurobiCl
greedyF, noF :: (MakesILP op, Pretty.PrettyOp (Cluster op)) => Objective -> OperationAfun op () a -> PartitionedAfun op () a
greedyF :: (MakesILP op, Pretty.PrettyOp (Cluster op)) => Benchmarking -> Objective -> OperationAfun op () a -> PartitionedAfun op () a
greedyF = greedyFusionF gurobiCl
noF :: (MakesILP op, Pretty.PrettyOp (Cluster op)) => Objective -> OperationAfun op () a -> PartitionedAfun op () a
noF = noFusionF gurobiCl
greedyFusion :: (MakesILP op, ILPSolver s op, Pretty.PrettyOp (Cluster op)) => s -> Objective -> OperationAcc op () a -> PartitionedAcc op () a
greedyFusion :: (MakesILP op, ILPSolver s op, Pretty.PrettyOp (Cluster op)) => s -> Benchmarking -> Objective -> OperationAcc op () a -> PartitionedAcc op () a
greedyFusion = greedyFusion' makeFullGraph (reconstruct False)
greedyFusionF :: (MakesILP op, ILPSolver s op, Pretty.PrettyOp (Cluster op)) => s -> Objective -> OperationAfun op () a -> PartitionedAfun op () a
greedyFusionF :: (MakesILP op, ILPSolver s op, Pretty.PrettyOp (Cluster op)) => s -> Benchmarking -> Objective -> OperationAfun op () a -> PartitionedAfun op () a
greedyFusionF = greedyFusion' makeFullGraphF (reconstructF False)
noFusion :: (MakesILP op, ILPSolver s op, Pretty.PrettyOp (Cluster op)) => s -> Objective -> OperationAcc op () a -> PartitionedAcc op () a
noFusion = noFusion' makeFullGraph (reconstruct True)
Expand Down

0 comments on commit 9424d5b

Please sign in to comment.