Skip to content

Commit

Permalink
Add LUN virtualizer
Browse files Browse the repository at this point in the history
the AMPI_LUN function returns the virtualized version of any LUN

see virtluntest.f90 for an example of usage, as it replaces
the manual LUN virtualization scheme used in luntest.f90
  • Loading branch information
ericjbohm committed May 25, 2022
1 parent dd59cc8 commit 63ce31e
Show file tree
Hide file tree
Showing 4 changed files with 268 additions and 5 deletions.
39 changes: 39 additions & 0 deletions tests/ampi/migratablelun/AMPI_LUN_Virtualized.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,39 @@
!***********************************************************************
! AMPI virtualization module for LUNs 12/30/2019
! *
!***********************************************************************
! initialize via AMPI_LUN_create()
! call AMPI_LUN(LUN) to return the virtualized LUN with idempotency
!
module AMPI_LUN_Virtualized
implicit none
save
! obtain AMPI rank
! multiply by LUN factor, default 100000
integer AMPI_LUN_thisrank
!$omp threadprivate(AMPI_LUN_thisrank)
integer :: AMPI_LUN_Factor=100000

contains

!-----------------------------------------------------------------------
subroutine AMPI_LUN_create(thisRank)

implicit none
integer, intent(in) :: thisRank


AMPI_LUN_thisrank = thisRank * AMPI_LUN_Factor

end subroutine AMPI_LUN_create
!-----------------------------------------------------------------------

integer function AMPI_LUN(inLUN) result(virt_LUN)
implicit none
integer, intent(in) :: inLUN

virt_lun= xor(inLUN, AMPI_LUN_thisrank);

end function AMPI_LUN

end module AMPI_LUN_Virtualized
42 changes: 37 additions & 5 deletions tests/ampi/migratablelun/Makefile
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
-include ../../common.mk
CHARMC=../../../bin/ampif90 $(OPTS)

all: migrateluntest migrateluntest-pie
all: migrateluntest migrateluntest-pie virtluntest virtluntest-pie

migrateluntest: AMPI_LUN_Migratable.o luntest.o pgm.o
$(CHARMC) -tlsglobals -fopenmp -o migrateluntest AMPI_LUN_Migratable.o luntest.o pgm.o
Expand All @@ -15,6 +15,19 @@ luntest.o: luntest.f90
AMPI_LUN_Migratable.o: AMPI_LUN_Migratable.f90
$(CHARMC) -tlsglobals -fopenmp -c AMPI_LUN_Migratable.f90 -o AMPI_LUN_Migratable.o

virtluntest: AMPI_LUN_Virtualized.o virtluntest.o pgm-v.o AMPI_LUN_Migratable.o
$(CHARMC) -tlsglobals -fopenmp -o virtluntest AMPI_LUN_Virtualized.o AMPI_LUN_Migratable.o virtluntest.o pgm-v.o

pgm-v.o: pgm-v.f90
$(CHARMC) -tlsglobals -fopenmp -c pgm-v.f90

virtluntest.o: virtluntest.f90
$(CHARMC) -tlsglobals -fopenmp -c virtluntest.f90 -o virtluntest.o

AMPI_LUN_Virtualized.o: AMPI_LUN_Virtualized.f90
$(CHARMC) -tlsglobals -fopenmp -c AMPI_LUN_Virtualized.f90 -o AMPI_LUN_Virtualized.o



migrateluntest-pie: AMPI_LUN_Migratable-pie.o luntest-pie.o pgm-pie.o
$(CHARMC) -pieglobals -o migrateluntest-pie AMPI_LUN_Migratable-pie.o luntest-pie.o pgm-pie.o
Expand All @@ -28,21 +41,40 @@ luntest-pie.o: luntest.f90
AMPI_LUN_Migratable-pie.o: AMPI_LUN_Migratable.f90
$(CHARMC) -pieglobals -standalone -c AMPI_LUN_Migratable.f90 -o AMPI_LUN_Migratable-pie.o


virtluntest-pie: AMPI_LUN_Virtualized-pie.o virtluntest-pie.o pgm-v-pie.o AMPI_LUN_Migratable.o
$(CHARMC) -pieglobals -o virtluntest-pie AMPI_LUN_Virtualized-pie.o AMPI_LUN_Migratable-pie.o virtluntest-pie.o pgm-v-pie.o

pgm-v-pie.o: pgm-v.f90
$(CHARMC) -pieglobals -standalone -c pgm-v.f90 -o pgm-v-pie.o

virtluntest-pie.o: virtluntest.f90
$(CHARMC) -pieglobals -standalone -c virtluntest.f90 -o virtluntest-pie.o

AMPI_LUN_Virtualized-pie.o: AMPI_LUN_Virtualized.f90
$(CHARMC) -pieglobals -standalone -c AMPI_LUN_Virtualized.f90 -o AMPI_LUN_Virtualized-pie.o


#
# clean up .o, .mod, .exe and EMACS backup files
#
clean:
rm -f *.o *.mod migrateluntest *~ conv-host charmrun ampirun
rm -f *.o *.mod migrateluntest *~ conv-host charmrun ampirun virtluntest output*.out

test: migrateluntest
test: migrateluntest virtluntest
$(call run, ./migrateluntest +p2 +vp4 +balancer GreedyRefineLB)
$(call run, ./virtluntest +p2 +vp4 +balancer GreedyRefineLB)

testp: migrateluntest
testp: migrateluntest virtluntest
$(call run, ./migrateluntest +p$(P) +vp$(P) +balancer GreedyRefineLB)
$(call run, ./migrateluntest +p$(P) +vp$$(( $(P) * 2 )) +balancer GreedyRefineLB)
$(call run, ./migrateluntest +p$(P) +vp$$(( $(P) * 4 )) +balancer GreedyRefineLB)
$(call run, ./virtluntest +p$(P) +vp$(P) +balancer GreedyRefineLB)
$(call run, ./virtluntest +p$(P) +vp$$(( $(P) * 2 )) +balancer GreedyRefineLB)
$(call run, ./virtluntest +p$(P) +vp$$(( $(P) * 4 )) +balancer GreedyRefineLB)

test-pie: migrateluntest-pie
test-pie: migrateluntest-pie virtluntest-pie
$(call run, ./migrateluntest-pie +p2 +vp4 +balancer GreedyRefineLB)
$(call run, ./virtluntest-pie +p2 +vp4 +balancer GreedyRefineLB)

test-all: test test-pie
26 changes: 26 additions & 0 deletions tests/ampi/migratablelun/pgm-v.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
subroutine MPI_Main
use AMPI_LUN_Migratable
use AMPI_LUN_Virtualized
use virtluntest, only: about_to_migrate, just_migrated, virtmigratablelun_test


implicit none
include 'mpif.h'

integer :: myrank, ierr, numranks

call MPI_Init(ierr)

call MPI_Comm_rank(MPI_COMM_WORLD, myrank, ierr)
call MPI_Comm_size(MPI_COMM_WORLD, numranks, ierr)
if (myrank.eq. 0) then
print *,"Initialized";
endif
call ampi_register_about_to_migrate(about_to_migrate, ierr);
call ampi_register_just_migrated(just_migrated, ierr);
call virtmigratablelun_test();


call MPI_Finalize(ierr)

end subroutine
166 changes: 166 additions & 0 deletions tests/ampi/migratablelun/virtluntest.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,166 @@
module virtluntest
use AMPI_LUN_Migratable
use AMPI_LUN_Virtualized
implicit none
include 'mpif.h'


contains

subroutine about_to_migrate
implicit none

integer :: rank, luncount, ierr

call mpi_comm_rank(MPI_COMM_WORLD, rank, ierr)
! write(*,*) rank, "About to migrate";
luncount = AMPI_LUN_close_registered();
end subroutine about_to_migrate

subroutine just_migrated
implicit none

integer :: rank, ierr
call mpi_comm_rank(MPI_COMM_WORLD, rank, ierr)

ierr= AMPI_LUN_reopen_registered();
! write(*,*) rank, " Just migrated";
end subroutine just_migrated



subroutine openluns()

integer readlun, writelun
integer registercount
character(1024)::writefilename
character(1024)::readfilename
character(10):: writeaction
character(10):: readaction
character*5 rankstring
integer rank, ierr, lun
call mpi_comm_rank(MPI_COMM_WORLD, rank, ierr);
writelun=AMPI_LUN(500);
readlun=AMPI_LUN(100);
write(rankstring,5) rank;
5 format(I4);
readaction='READ';
writeaction='WRITE';
writefilename='output' // trim(adjustl(rankstring)) //'.out';
! open(UNIT=writelun,FILE=writefilename,ACTION=writeaction);
registercount= AMPI_LUN_open(writelun,writefilename,writeaction);
readfilename='luntest.f90';
! open(UNIT=readlun,FILE=readfilename,ACTION=readaction);
registercount= AMPI_LUN_open(readlun,readfilename,readaction);
end subroutine openluns

function dowork(rank, iteration) result(operand)
implicit none

integer, intent(in)::rank, iteration
integer work, ierr, range
integer(8) operand
operand=1;
range=(rank+iteration);
! work scales with rank to create imbalance
do work=1, range
operand=work*operand;
end do
return
end function dowork

subroutine dooutput(iteration, invalue)
implicit none

integer, intent(in)::iteration
integer(8), intent(in)::invalue
integer rank, ierr, lun
!output the current value to lun for our rank number
call mpi_comm_rank(MPI_COMM_WORLD, rank, ierr);
lun=AMPI_LUN(500);
write(lun,*) invalue;
end subroutine dooutput

subroutine doinput(iteration)
implicit none

integer, intent(in)::iteration
integer :: readlun, ioi
character(100):: inchar
integer rank, ierr, lun
call mpi_comm_rank(MPI_COMM_WORLD, rank, ierr);
readlun=AMPI_LUN(100);
! we'll read a line

read(readlun,*) inchar;

end subroutine doinput

function checkoutput(rank, iteration) result(stat)
implicit none
integer, intent(in)::rank
integer, intent(in)::iteration
integer checklun, ierr, checkiteration
logical stat
character*5 rankstring
character(1024)::checkfilename
integer(8) checkvalue
integer(8) verifyvalue
stat=.TRUE.;
checklun=AMPI_LUN(200);
write(rankstring,15) rank;
15 format(I4);
checkfilename='output' // trim(adjustl(rankstring)) //'.out';
open(UNIT=checklun,FILE=checkfilename,ACTION="READ");
do checkiteration=1, iteration
read(checklun,*) checkvalue;
verifyvalue=dowork(rank,checkiteration);
if(verifyvalue .ne. checkvalue) then
stat=.FALSE.;
! else
! write (*,*) "checked that ",verifyvalue, " matches ", checkvalue;
end if
end do
return;
end function checkoutput

subroutine virtmigratablelun_test()
implicit none

integer :: iteration
integer :: AMPI_LB_FREQ, CHECK_FREQ
integer :: ierr, rank, numranks, virt
integer(8) :: computed
! create the lun registry
call AMPI_LUN_create_registry(10);

call mpi_comm_rank(MPI_COMM_WORLD, rank, ierr);
call MPI_Comm_size(MPI_COMM_WORLD, numranks, ierr)
! open some files and add them to the registry
call AMPI_LUN_create(rank);
call openluns();

!start iterating
AMPI_LB_FREQ=5;
CHECK_FREQ=18;


do iteration=1, 19
call doinput(iteration);
computed=dowork(rank,iteration);
call dooutput(iteration, computed);
IF(MOD(iteration,AMPI_LB_FREQ).EQ.0)THEN
call AMPI_MIGRATE(AMPI_INFO_LB_SYNC, IERR);
END IF
IF (MOD(iteration,CHECK_FREQ).EQ.0) THEN
call MPI_BARRIER(MPI_COMM_WORLD, ierr);
IF(checkoutput(MOD(rank+1,numranks),iteration)) THEN
write (*,*) "rank ",rank," check of rank ", MOD(rank+1,numranks), " succeeded at iter", iteration;
ELSE
call MPI_ABORT(MPI_COMM_WORLD,1, ierr);
END IF
END IF
END DO
end subroutine virtmigratablelun_test
end module virtluntest

0 comments on commit 63ce31e

Please sign in to comment.