source: CPL/oasis3-mct/branches/OASIS3-MCT_5.0_branch/lib/mct/benchmarks/importBench.F90 @ 6331

Last change on this file since 6331 was 6331, checked in by aclsce, 17 months ago

Moved oasis-mct_5.0 in oasis3-mct/branches directory.

File size: 7.3 KB
Line 
1! Av import/export benchmark
2!
3 program importBench
4
5  use m_MCTWorld,only : MCTWorld_init => init
6  use m_MCTWorld,only : MCTWorld_clean => clean
7  use m_MCTWorld,only : ThisMCTWorld
8  use m_AttrVect,only : AttrVect
9  use m_AttrVect,only : AttrVect_init => init
10  use m_AttrVect,only : AttrVect_nRattr => nRattr
11  use m_AttrVect,only : AttrVect_nIattr => nIattr
12  use m_AttrVect,only : AttrVect_size => lsize
13  use m_AttrVect,only : AttrVect_indexRA => indexRA
14  use m_AttrVect,only : AttrVect_importRA => importRAttr
15  use m_AttrVect,only : AttrVect_exportRA => exportRAttr
16
17  use m_mpif90
18  use m_ioutil, only : luavail
19
20  implicit none
21
22! declarations
23  include 'mpif.h'
24
25  character(len=*), parameter :: myname='MCT_importBench'
26
27  integer, parameter :: nTrials=1000 ! Number of timing measurements
28                                     ! per test.  Keep high WRT
29                                     ! value of MaxNumAtts to ensure
30                                     ! timings are representative
31
32  integer, parameter :: lmax = 17 ! Maximum AV length = 2**(lmax-1)
33                                  ! Don't increase--segv on login.mcs
34                                  ! for larger values!
35
36  integer, parameter :: MaxNumAtts = 26 ! maximum number of
37                                        ! attributes used in
38                                        ! timing tests.  Leave
39                                        ! fixed for now!
40
41  character(len=2*MaxNumAtts-1) :: dummyAList ! character array for
42                                              ! synthetic attribute
43                                              ! lists
44
45  integer comm1, mysize,myproc,ier,i
46
47  real*8, dimension(:), pointer :: inputData(:)
48  real*8, dimension(:), pointer :: outputData(:)
49
50  integer :: currLength, k, l, n
51  integer :: colInd, lettInd, attInd, charInd
52
53  real*8 :: startTime, finishTime
54  real*8, dimension(:), pointer :: impTimings
55  real*8, dimension(:), pointer :: expTimings
56  real*8 :: impMeanTime, expMeanTime
57  real*8 :: impStdDevTime, expStdDevTime
58
59  integer :: impAvD, impMinD, impMaxD, impSDD
60  integer :: expAvD, expMinD, expMaxD, expSDD
61
62  type(AttrVect) :: myAV
63
64!
65! Initialize MPI and copy MPI_COMM_WORLD...
66!
67  call MPI_init(ier)
68
69  call mpi_comm_size(MPI_COMM_WORLD, mysize,ier)
70  call mpi_comm_rank(MPI_COMM_WORLD, myproc,ier)
71  write(0,*) myproc, "MPI size proc", mysize
72
73  call mpi_comm_dup(MPI_COMM_WORLD,comm1,ier)
74
75  myproc = 0
76
77! create storage impTimings(:) and expTimings(:)
78!
79  allocate(impTimings(nTrials), expTimings(nTrials), stat=ier)
80  write(0,'(a,2(a,i8))') myname,':: nTrials = ',nTrials,' ier=',ier
81
82! set up files for timing statistics and open them
83!
84  impAvD = luavail()
85  open(impAvD, file='benchAV_importAvgTime.d',status='new')
86  impMinD = luavail()
87  open(impMinD, file='benchAV_importMinTime.d',status='new')
88  impMaxD = luavail()
89  open(impMaxD, file='benchAV_importMaxTime.d',status='new')
90  impSDD = luavail()
91  open(impSDD, file='benchAV_importStdDevTime.d',status='new')
92  expAvD = luavail()
93  open(expAvD, file='benchAV_exportAvgTime.d',status='new')
94  expMinD = luavail()
95  open(expMinD, file='benchAV_exportMinTime.d',status='new')
96  expMaxD = luavail()
97  open(expMaxD, file='benchAV_exportMaxTime.d',status='new')
98  expSDD = luavail()
99  open(expSDD, file='benchAV_exportStdDevTime.d',status='new')
100
101! Initialize MCTWorld
102  call MCTWorld_init(1,MPI_COMM_WORLD,comm1,1)
103
104  dummyAList = ''
105  do k=1,MaxNumAtts
106
107    ! construct dummy attribute list AttrVect_init() invoked with
108    ! trim(dummyAList) as a string literal argument for rList (see below)
109    if(k == 1) then ! bootstrap the process with just a single attribute
110      dummyAList(k:k) = achar(65) ! the letter 'A'
111    else
112      colInd = 2 * (k-1)
113      lettInd = 2*k - 1
114      dummyAList(colInd:colInd) = achar(58) ! a colon ':'
115      dummyAList(lettInd:lettInd) = achar(64+k)
116    endif
117
118    do l=1,lmax
119!
120! Set current AV length currLength, create inputData(:) and outputData(:),
121! and initialize entries of inputData(:)...
122!
123      currLength = 2 ** (l-1)
124      ! write(0,'(a,2(a,i8))') myname,":: l = ",l," currLength = ",currLength
125
126      allocate(inputData(currLength), outputData(currLength),stat=ier)
127      do i=1,currLength
128        inputData(i)=real(i)
129      end do
130
131      ! create an Av with k attributes
132      call AttrVect_init(myAV, rList=trim(dummyAList), lsize=currLength)
133
134      ! Import/Export timing tests:
135      impMeanTime = 0.
136      expMeanTime = 0.
137      do n=1,nTrials
138        ! circulate through the k attributes so that we get more-or-less
139        ! equal representation of the attributes among the import/export
140        ! calls.  Setting nTrials to a large number ensures the disparities
141        ! among how frequently the attributes are called will be minimal.
142        attInd = mod(n,k)
143        charInd = 65 + attInd ! offset from "A"
144        startTime = MPI_WTIME()
145        call AttrVect_importRA(myAV, achar(charInd), inputData, currLength)
146        finishTime = MPI_WTIME()
147        impTimings(n) = finishTime - startTime
148        impMeanTime = impMeanTime + impTimings(n)
149
150        startTime = MPI_WTIME()
151        call AttrVect_exportRA(myAV, achar(charInd), outputData, currLength)
152        finishTime = MPI_WTIME()
153        expTimings(n) = finishTime - startTime
154        expMeanTime = expMeanTime + expTimings(n)
155
156     end do
157     impMeanTime = impMeanTime / float(nTrials)
158     expMeanTime = expMeanTime / float(nTrials)
159     ! Compute Standard Deviation for timings
160     impStdDevTime = 0.
161     expStdDevTime = 0.
162     do n=1,nTrials
163       impStdDevTime = impStdDevTime + (impTimings(n) - impMeanTime)**2
164       expStdDevTime = expStdDevTime + (expTimings(n) - expMeanTime)**2
165     end do
166     impStdDevTime = sqrt(impStdDevTime / float(nTrials-1))
167     expStdDevTime = sqrt(expStdDevTime / float(nTrials-1))
168
169     write(*,'(a,2(a,i8),4(a,g12.6))') myname, &
170                ":: Import timings for k=",k,"attributes.  AV length=", &
171                currLength," elements: Mean = ",impMeanTime," Min= ", &
172                minval (impTimings)," Max = ",maxval(impTimings), &
173                " Std. Dev. = ",impStdDevTime
174
175     write(*,'(a,2(a,i8),4(a,g12.6))') myname, &
176                ":: Export timings for k=",k,"attributes.  AV length=", &
177                currLength," elements: Mean = ",expMeanTime," Min = ", &
178                minval(expTimings)," Max = ",maxval(expTimings), &
179                " Std. Dev. = ",impStdDevTime
180
181     ! Write statistics to individual files for subsequent
182     !  visualization:
183     write(impAvD,'(2(i8,2x),g12.6)') l-1, k, impMeanTime
184     write(impMinD,'(2(i8,2x),g12.6)') l-1, k, minval(impTimings)
185     write(impMaxD,'(2(i8,2x),g12.6)') l-1, k, maxval(impTimings)
186     write(impSDD,'(2(i8,2x),g12.6)') l-1, k, impStdDevTime
187     write(expAvD,'(2(i8,2x),g12.6)') l-1, k, expMeanTime
188     write(expMinD,'(2(i8,2x),g12.6)') l-1, k, minval(expTimings)
189     write(expMaxD,'(2(i8,2x),g12.6)') l-1, k, maxval(expTimings)
190     write(expSDD,'(2(i8,2x),g12.6)') l-1, k, expStdDevTime
191
192     ! Clean up for this value of l:
193!     write(*,'(2a,i8)') myname,':: cleaning up for l = ',l
194     deallocate(inputData, outputData,stat=ier)
195
196     end do ! l=1,lmax
197  end do ! k=1,MaxNumAtts
198
199! Close output files:
200  close(impAvD)
201  close(impMinD)
202  close(impMaxD)
203  close(impSDD)
204  close(expAvD)
205  close(expMinD)
206  close(expMaxD)
207  close(expSDD)
208
209  call MCTWorld_clean
210!  write(*,'(2a,i8)') myname,':: clean up completed for l = ',l
211
212!  call MPI_FINALIZE(MPI_COMM_WORLD, ier)
213
214 end program importBench
215
Note: See TracBrowser for help on using the repository browser.