140 likes | 266 Views
Automatic MPI to AMPI Conversion using Photran Stas Negara , Kuo-Chuan Pan, Gengbin Zheng, Natasha Negara, Ralph Johnson, Laxmikant Kal é, Paul Ricker 8 th Annual Workshop on Charm++ and its Applications April 28, 2010. Presentation outline. MPI to AMPI code transformation Tool Evaluation
E N D
Automatic MPI to AMPI Conversion using PhotranStas Negara, Kuo-Chuan Pan, Gengbin Zheng, Natasha Negara, Ralph Johnson, Laxmikant Kalé, Paul Ricker8th Annual Workshop on Charm++ and its ApplicationsApril 28, 2010
Presentation outline • MPI to AMPI code transformation • Tool • Evaluation • Future work
MPI to AMPI code transformation (1 of 5) • Remove global variables • Write pack/unpack subroutine • Rename main PROGRAM to MPI_MAIN subroutine
MPI to AMPI code transformation (2 of 5) MODULE MyMod REAL :: p, r INTEGER, PRIVATE :: i, j ... END MODULE PROGRAM MyProg INTEGER :: i COMMON /CB/ i i = 3 CALL PrintVal END PROGRAM SUBROUTINE PrintVal INTEGER :: j COMMON /CB/ j print *, “j=“, j END SUBROUTINE Fortran global variables: • Module variables • Saved subprogram variables • Common block variables SUBROUTINE MySub REAL, SAVE :: p, r INTEGER :: c = 0, i ... END SUBROUTINE
MPI to AMPI code transformation (3 of 5) Global variables privatization: • Generate stubs for the derived type and its containing module • Add an extra parameter to each subprogram* and every call site • Remove every global variable: • Declare the corresponding field in the derived type • Replace every access to the variable with the access to the corresponding field • Delete global variable
MPI to AMPI code transformation (4 of 5) PROGRAM MyProg USE GenMod TYPE(GenType) :: p INTEGER :: i COMMON /CB/ i i = 3 CALL PrintVal(p) END PROGRAM PROGRAM MyProg USE GenMod TYPE(GenType) :: p INTEGER :: i COMMON /CB/ i i = 3 CALL PrintVal(p) END PROGRAM PROGRAM MyProg USE GenMod TYPE(GenType) :: p INTEGER :: i COMMON /CB/ i p%f = 3 CALL PrintVal(p) END PROGRAM PROGRAM MyProg USE GenMod TYPE(GenType) :: p p%f = 3 CALL PrintVal(p) END PROGRAM SUBROUTINE PrintVal INTEGER :: j COMMON /CB/ j print *, “j=“, j END SUBROUTINE MODULE GenMod TYPE GenType END TYPE END MODULE SUBROUTINE PrintVal(p) USE GenMod TYPE(GenType) :: p INTEGER :: j COMMON /CB/ j print *, “j=“, j END SUBROUTINE MODULE GenMod TYPE GenType END TYPE END MODULE SUBROUTINE PrintVal(p) USE GenMod TYPE(GenType) :: p INTEGER :: j COMMON /CB/ j print *, “j=“, j END SUBROUTINE MODULE GenMod TYPE GenType INTEGER :: f END TYPE END MODULE SUBROUTINE PrintVal(p) USE GenMod TYPE(GenType) :: p INTEGER :: j COMMON /CB/ j print *, “j=“, p%f END SUBROUTINE MODULE GenMod TYPE GenType INTEGER :: f END TYPE END MODULE SUBROUTINE PrintVal(p) USE GenMod TYPE(GenType) :: p print *, “j=“, p%f END SUBROUTINE MODULE GenMod TYPE GenType INTEGER :: f END TYPE END MODULE PROGRAM MyProg INTEGER :: i COMMON /CB/ i i = 3 CALL PrintVal END PROGRAM
MPI to AMPI code transformation (5 of 5) MODULE GenMod TYPE GenType REAL, ALLOCATABLE :: ar(:) END TYPE END MODULE SUBROUTINE GenPUP(p, g) USE pupmod USE GenMod TYPE(GenType) :: g LOGICAL :: isAllocated INTEGER :: p, n(2) IF (.not. fpup_isunpacking(p)) THEN isAllocated = allocated(g%ar) ENDIF CALL fpup_logical(p, isAllocated) IF (isAllocated) THEN IF (fpup_isunpacking(p)) THEN CALL fpup_ints(p, n, 2) ALLOCATE(g%ar(n(1):n(2))) ELSE n(1) = LBOUND(g%ar, DIM=1) n(2) = UBOUND(g%ar, DIM=1) CALL fpup_ints(p, n, 2) ENDIF CALL fpup_doubles(p, g%ar, SIZE(g%ar)) IF (fpup_isdeleting(p)) THEN DEALLOCATE(g%ar) ENDIF ENDIF END SUBROUTINE
Implemented in Java Based on Photran IDE Operates on Fortran 90 Requires “pure” Fortran code Completely automates the transformation, except packing/unpacking of derived types Accessible as a refactoring in Photran Tool (1 of 2)
Evaluation (1 of 4) • Evaluated on FLASH project • Transformed 2D simulation of Sedov-Taylor explosion • Ran experiments on NCSA Abe using 16 physical processors • Employed GreedyLB and RefineLB • Achieved up to 8% improvement due to load balancing
Future work • Automatically generate pack/unpack code for derived types • Minimize overhead of the transformation • Continue evaluation: • More complex and larger problems • More sophisticated load balancers