main-lucia.F90 36 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943
  1. program lucia_analysis
  2. !
  3. ! ===================================
  4. ! LUCIA post-processing analysis tool
  5. ! ===================================
  6. !
  7. ! Purpose:
  8. ! - Load balance an OASIS-based coupled system
  9. ! - Assess scalabilities of each model of the coupled system
  10. ! - Estimate coupling cost (interpolations) and models jitter
  11. !
  12. ! Getting started:
  13. !
  14. ! - compile your model with OASIS version newer than
  15. ! - launch coupled sytem with second LOGPRT parameter equal
  16. ! to -1 (in namcouple file)
  17. ! - process lucia.??.?????? files with lucia-mct script
  18. ! shell provided with the present FORTRAN program
  19. !
  20. implicit none
  21. !
  22. ! Information related to each coupled field
  23. !
  24. type FIELD_SEQUENCE
  25. integer*4 :: namID ! field rank in namcouple
  26. integer*4 :: source_model ! index of source model
  27. integer*4 :: target_model ! index of target model
  28. integer*4 :: source_comm_nb ! number of send actions from source
  29. integer*4 :: target_comm_nb ! number of receive actions from target
  30. end type FIELD_SEQUENCE
  31. ! Explicit logical flags
  32. logical :: l_put, l_before, l_exch_still_valid, l_exch_not_yet_valid, l_add_interp_time
  33. !
  34. character(len=9) :: c_verif ! Lucia identifyer (no more used)
  35. character(len=3) :: c_field_code ! code for field number or info provided during init
  36. character(len=24) :: c_field_name
  37. character(len=15) :: c_comm_type ! kind of exchange (put or get)
  38. ! Parameters
  39. character(len=3) :: c_ident_put = "put"
  40. character(len=3) :: c_ident_before = "Before"
  41. ! Buffer arrays
  42. character(len=3) :: c_test_name
  43. character(len=24) :: c_dummy
  44. character(len=300) :: c_argument, log_file_name
  45. !
  46. character(len=20), dimension(:,:), allocatable :: field_name
  47. character(len=10), dimension(:), allocatable :: model_name
  48. character(len=10), dimension(:), allocatable :: model_code ! model rank on OASIS sequence
  49. !
  50. ! for first static allocation, maximum number of coupling fields
  51. integer*4 :: max_nb_fields = 300
  52. !
  53. ! Indexes or temporary arrays
  54. integer*4 :: i, j, k, l, mi, narg, i_err, newf, tmp_field_code
  55. integer*4 :: nb_models
  56. integer*4 :: nb_tot_log_files, log_nb ! number of log file processed and index
  57. integer*4 :: cpl_field_nb ! total number of coupling fields
  58. ! same as NFIELDS parameter in namcouple
  59. integer*4 :: i_cpl ! coupling field index (namcouple order)
  60. integer*4 :: clk_i ! event index 1: before send
  61. ! 2: after send
  62. ! 3: before receive
  63. ! 4: after receive
  64. integer*4 :: before_send = 1
  65. integer*4 :: after_send = 2
  66. integer*4 :: before_recv = 3
  67. integer*4 :: after_recv = 4
  68. integer*4 :: after_send_or_recv = 2
  69. integer*4 :: max_comm_nb ! maximum nb of coupling tstep among coupling fields
  70. integer*4 :: i_first_exchg(2) ! indexes of first coupling field exchanged
  71. integer*4, dimension(:), allocatable :: nb_mpi ! array of mpi partition nb per model
  72. integer*4, dimension(:), allocatable :: i_stride ! stride for log file counting per model
  73. integer*4, dimension(:), allocatable :: i_file_count ! log file nb per model
  74. integer*4, dimension(:), allocatable :: valid_comm_nb ! nb of valid coupling tstep per model
  75. integer*4, dimension(:), allocatable :: first_valid_comm ! index of first valid communication
  76. integer*4, dimension(:), allocatable :: i_cpl_field ! index of coupling field in exchange sequence
  77. integer*4, dimension(:,:), allocatable :: field_code ! index of coupling fields in namcouple exchange
  78. integer*4, dimension(:,:), allocatable :: comm_type ! Communication type
  79. ! 0: get
  80. ! 1: put
  81. integer*4, dimension(:,:), allocatable :: comm_nb ! nb of coupling tstep per model and per field
  82. !
  83. real*8 :: r_clock ! read clock time
  84. real*8 :: r_min_time, r_max_time ! time boundaries
  85. real*8 :: r_reference = -1.E8 ! reference time
  86. real*8 :: r_mean ! tmp buffer
  87. real*8 :: temp_t ! tmp buffer
  88. real*8 :: r_impossible_value= 1.E13 ! reference time
  89. real*8 :: r_test_impossible= 1.E12 ! reference time
  90. real*8, dimension(:), allocatable :: calc_time, noncalc_time ! calculation and non calculation time per model
  91. ! Timing for interpolation time and jitter per model
  92. real*8, dimension(:), allocatable :: r_interp_measure, r_interp_time, r_jitter_time
  93. ! Evaluation of variance among log files
  94. real*8, dimension(:), allocatable :: send_spread, receive_spread, calc_spread
  95. real*8, dimension(:,:), allocatable :: start_time ! beginning of first coupling sequence
  96. real*8, dimension(:,:,:), allocatable :: min_clock_measure ! measure of min among log files
  97. real*8, dimension(:,:,:), allocatable :: max_clock_measure ! measure of max among log files
  98. real*8, dimension(:,:,:), allocatable :: calc_noncalc_measure ! calculation and non calculation time for each event
  99. !
  100. ! Informations on coupling fields
  101. type(FIELD_SEQUENCE), dimension(:), allocatable :: cpl_fields
  102. !
  103. ! external function
  104. integer*4 :: iargc
  105. !
  106. !
  107. ! GET THE NUMBER OF COMMAND LINE ARGUMENTS.
  108. !
  109. narg = iargc()
  110. !
  111. ! CHECK THE NUMBER OF COMMAND LINE ARGUMENTS.
  112. !
  113. if ( narg==0 ) then
  114. write (6,*)
  115. write (6,*) ' Error: Missing arguments'
  116. stop
  117. else if ( narg<6 ) then
  118. write (6,*) ' Wrong number of line arguments '
  119. write (6,*) ' Coupled models should be 2 at least '
  120. stop
  121. end if
  122. !
  123. ! 3 argument per model
  124. nb_models = narg / 3
  125. !
  126. ! ALLOCATIONS of nb_models dimensional arrays
  127. allocate(nb_mpi(nb_models))
  128. allocate(i_stride(nb_models))
  129. allocate(i_file_count(nb_models))
  130. allocate(i_cpl_field(nb_models))
  131. allocate(model_name(nb_models))
  132. allocate(model_code(nb_models))
  133. allocate(calc_time(nb_models))
  134. allocate(noncalc_time(nb_models))
  135. allocate(r_jitter_time(nb_models))
  136. allocate(send_spread(nb_models))
  137. allocate(receive_spread(nb_models))
  138. allocate(calc_spread(nb_models))
  139. allocate(r_interp_time(nb_models))
  140. allocate(valid_comm_nb(nb_models))
  141. allocate(first_valid_comm(nb_models))
  142. ! ALLOCATIONS of nb_models x max_nb_fields dimensional arrays
  143. allocate(field_name(nb_models, max_nb_fields))
  144. allocate(field_code(nb_models, max_nb_fields))
  145. allocate(comm_type(nb_models, max_nb_fields))
  146. allocate(comm_nb(nb_models, max_nb_fields))
  147. allocate(start_time(nb_models, max_nb_fields))
  148. comm_nb(:,:) = 0
  149. start_time(:,:) = r_impossible_value
  150. !
  151. ! DEFAULT VALUES FOR COMMAND LINE ARGUMENTS.
  152. !
  153. nb_mpi(:) = 1
  154. model_code(:) = "none"
  155. model_name(:) = "none"
  156. field_name(:,:) = "none"
  157. !
  158. ! 1. CHECK THE COMMAND LINE ARGUMENTS.
  159. !
  160. do i = 1, nb_models
  161. !
  162. ! GET MODEL RANK ON OASIS SEQUENCE
  163. call getarg( 3*i-2, model_code(i) )
  164. !
  165. ! GET LOG FILE NB
  166. call getarg( 3*i-1, c_argument )
  167. read(c_argument,'(i6)') i_stride(i)
  168. ! must be greater than 1
  169. i_stride(i) = MAX(i_stride(i),1)
  170. !
  171. ! GET NUMBER OF MPI SUBDOMAINS
  172. call getarg( 3*i, c_argument )
  173. read(c_argument,'(i6)') nb_mpi(i)
  174. ! check that stride still greater than 1
  175. i_stride(i) = MAX ( nb_mpi(i) / MAX((i_stride(i)-1),1), 1)
  176. !
  177. end do
  178. !
  179. ! 2. READ OASIS-LUCIA LOG FILES CONTAINT
  180. !
  181. ! DATA ARE READ FOR A FIRST TIME TO FIND ARRAYs LENGTH
  182. ! AND COUPLING FIELDS EXCHANGE SEQUENCE
  183. !
  184. write(6,*) ' '
  185. write(6,*) ' Processing OASIS LUCIA log files '
  186. write(6,*) ' '
  187. !
  188. i_cpl_field(:)=0
  189. ! Loop on model number
  190. do i = 1, nb_models
  191. !
  192. i_file_count(i) = 0
  193. k = 1
  194. write(6,*) 'Computed log files for model ', model_code(i), nb_mpi(i), i_stride(i)
  195. call flush(6)
  196. ! Loop on log file number
  197. do j = 0, nb_mpi(i), i_stride(i)
  198. ! Count number of log file per model
  199. i_file_count(i) = i_file_count(i) + 1
  200. write(log_file_name,'("lucia.",a2,".",i6.6)'),model_code(i),j
  201. write(6,'(TL16,A,1X)', advance='no') TRIM(log_file_name)
  202. call flush(6)
  203. OPEN (unit=10, &
  204. file=TRIM(log_file_name), &
  205. action="read", &
  206. status="OLD", &
  207. form="formatted", &
  208. iostat=i_err)
  209. if ( i_err .ne. 0 ) then
  210. write(6,*) 'Error opening ASCII file ', TRIM(log_file_name)
  211. stop
  212. end if
  213. ! write (6,*) ' open ', log_file_name
  214. !
  215. !
  216. ! FIRST GUESS: GET FIELD NAMES AND EXCHANGE TYPE
  217. !
  218. REWIND(10)
  219. i_err=0
  220. ! For each line of the log file
  221. DO WHILE ( i_err /= -1 )
  222. READ(10, '(A9,A3,A12,A4,F16.5)', iostat=i_err) &
  223. & c_verif, &
  224. & c_field_code, &
  225. & c_dummy, &
  226. & c_comm_type, &
  227. & r_clock
  228. ! EOF
  229. IF ( i_err == -1 ) cycle
  230. !
  231. ! if ( i == 2 ) write(6,*) ' file ', TRIM(c_verif), TRIM(c_field_code)
  232. ! Skip if initial synchro
  233. IF ( c_field_code(1:3) == "IT " ) cycle
  234. ! Skip if interpolation time measurement
  235. IF ( INDEX ( TRIM(c_comm_type),'rpo' ) /= 0 ) cycle
  236. ! Read model names
  237. IF ( c_field_code(1:3) == "MD " ) THEN
  238. IF ( TRIM(model_name(i)) == "none" ) model_name(i) = TRIM(c_dummy)
  239. cycle
  240. ENDIF
  241. ! Read field names as declared in namcouple
  242. IF ( c_field_code(1:3) == "SN " .or. c_field_code(1:3) == "RC " ) THEN
  243. BACKSPACE(10)
  244. READ(10, '(A9,A3,A5,A)', iostat=i_err) &
  245. & c_verif, &
  246. & c_field_code, &
  247. & c_dummy, &
  248. & c_field_name
  249. IF ( j == 0 ) THEN
  250. read(c_dummy(1:4),'(i4)') k
  251. field_name(i,k) = TRIM(c_field_name)
  252. ENDIF
  253. cycle
  254. ENDIF
  255. !
  256. ! PROCESS INFORMATION FROM STANDARD TIMING LINE
  257. !
  258. ! When coupling field list is empty (beginning)
  259. IF ( i_cpl_field(i) == 0 ) THEN
  260. ! Fill list with first field found
  261. i_cpl_field(i) = 1
  262. READ(c_field_code,'(i3)') field_code(i, i_cpl_field(i))
  263. ! Start counting coupling steps
  264. comm_nb(i,i_cpl_field(i)) = 1
  265. ! if ( i == 2 ) write(6,*) ' field ', TRIM(field_code(i, 1)), comm_nb(i,1)
  266. ! Identify if it is a put or a get communication
  267. IF ( INDEX ( TRIM(c_comm_type), c_ident_put ) /= 0 ) THEN
  268. ! This communication is a put
  269. comm_type(i, i_cpl_field(i)) = 0
  270. start_time(i,i_cpl_field(i)) = r_clock
  271. ELSE
  272. ! This communication is a get
  273. comm_type(i, i_cpl_field(i)) = 1
  274. start_time(i,i_cpl_field(i)) = r_clock
  275. ENDIF
  276. ! When field list is not empty (loop)
  277. ELSE
  278. ! Coupling field index initialized
  279. mi = 1
  280. newf = 0
  281. ! Check model field number already identified
  282. DO WHILE ( mi <= i_cpl_field(i) )
  283. read(c_field_code,'(i3)') tmp_field_code
  284. IF ( field_code(i, mi) == tmp_field_code ) &
  285. newf = mi
  286. mi = mi + 1
  287. END DO
  288. ! Another field found because not identified in the list
  289. IF ( newf == 0 ) THEN
  290. ! Fill list with new field found (same than above)
  291. i_cpl_field(i) = i_cpl_field(i) + 1
  292. READ(c_field_code,'(i3)') field_code(i, i_cpl_field(i))
  293. comm_nb(i,i_cpl_field(i)) = 1
  294. ! Identify if it is a put or a get communication
  295. IF ( INDEX ( TRIM(c_comm_type), c_ident_put ) /= 0 ) THEN
  296. ! This communication is a put
  297. comm_type(i, i_cpl_field(i)) = 0
  298. start_time(i,i_cpl_field(i)) = r_clock
  299. ELSE
  300. comm_type(i, i_cpl_field(i)) = 1
  301. start_time(i,i_cpl_field(i)) = r_clock
  302. ENDIF
  303. ! Just another coupling step for an already identified field
  304. ELSE
  305. comm_nb(i,newf) = comm_nb(i,newf) + 1
  306. END IF
  307. END IF
  308. ! End loop on read lines
  309. END DO
  310. CLOSE(10)
  311. ! End loop on log files
  312. END DO
  313. write(6,*) ' '
  314. !
  315. ! write(6,*) ' nbFields ', model_name(i) , i_cpl_field(i)
  316. ! do k = 1, i_cpl_field(i)
  317. ! write(6,*) ' Field ', field_code(i, k), comm_type(i,k)
  318. ! ENDDO
  319. !
  320. ! End loop on models
  321. END DO
  322. !
  323. ! Coupling fields counterd twice (as sent and received field)
  324. cpl_field_nb = SUM(i_cpl_field(:))/2
  325. ALLOCATE ( cpl_fields ( cpl_field_nb ) )
  326. !
  327. ! write(6,*) ' nb fields ', cpl_field_nb
  328. ! call flush(6)
  329. !
  330. !
  331. DO i = 1, nb_models
  332. ! Count total send/received fields (divide by proc number)
  333. comm_nb(i,:) = comm_nb(i,:) / i_file_count(i)
  334. END DO
  335. !
  336. ! 3. FIND EXCHANGE ORDER
  337. !
  338. j = 1
  339. ! loop on coupling fields
  340. DO WHILE ( j <= cpl_field_nb )
  341. ! Find the earliest exchange
  342. i_first_exchg = MINLOC(start_time(:,:))
  343. ! Index of model doing the first exchange
  344. mi = i_first_exchg(1)
  345. ! Index of first field exchanged
  346. i = i_first_exchg(2)
  347. ! only if it is a send field
  348. IF ( comm_type(mi,i) == 0 ) THEN
  349. ! Find the exchange number in OASIS sequence (namcouple)
  350. cpl_fields(j)%namID = field_code ( mi, i )
  351. ! Set its source model
  352. cpl_fields(j)%source_model = mi
  353. ! Set how many times this coupling field has been sent
  354. cpl_fields(j)%source_comm_nb = comm_nb( mi, i )
  355. !
  356. DO k = 1, nb_models
  357. IF ( k == mi ) cycle
  358. IF ( ANY ( field_code ( k, 1:i_cpl_field(k) ) == cpl_fields(j)%namID)) THEN
  359. ! Set its target model
  360. cpl_fields(j)%target_model = k
  361. DO l = 1, i_cpl_field(k)
  362. IF ( field_code(k,l) == cpl_fields(j)%namID ) &
  363. ! Set how many times this coupling field has been received
  364. cpl_fields(j)%target_comm_nb = comm_nb( k, l )
  365. END DO
  366. END IF
  367. END DO
  368. j = j + 1
  369. END IF
  370. start_time(mi,i) = r_impossible_value
  371. END DO
  372. !
  373. write (6,*) ' '
  374. write (6,*) ' "Lucia" analysis '
  375. write (6,*) ' '
  376. write (6,*) ' Exchanged fields (based on first exchange): '
  377. !
  378. write (6,*) ' From model : to model '
  379. DO i = 1, cpl_field_nb
  380. write (6,*) ' ', TRIM(model_name(cpl_fields(i)%source_model)), &
  381. ' ( ', TRIM(field_name(cpl_fields(i)%source_model,cpl_fields(i)%namID)), &
  382. ' ) ', TRIM(model_name(cpl_fields(i)%target_model)), &
  383. ' ( ', TRIM(field_name(cpl_fields(i)%target_model,cpl_fields(i)%namID)) , ' )'
  384. END DO
  385. ! write (6,*) ' '
  386. ! call flush(6)
  387. !
  388. ! 4. CHECK COMMUNICATION NUMBER CONCORDANCE
  389. !
  390. do i = 1, cpl_field_nb
  391. IF ( cpl_fields(i)%target_comm_nb /= cpl_fields(i)%source_comm_nb ) THEN
  392. write(6,*) ' WARNING - Coupler exchanges: ' , &
  393. TRIM(field_name(cpl_fields(i)%source_model,cpl_fields(i)%namID)) , &
  394. ' sent ', cpl_fields(i)%source_comm_nb, &
  395. ' but ', TRIM(field_name(cpl_fields(i)%target_model,cpl_fields(i)%namID)) , &
  396. ' received ', cpl_fields(i)%target_comm_nb
  397. !
  398. ! In case of unbalanced exchange number (abnormal stop),
  399. ! restrain communication number according to the last valid exchange number
  400. !
  401. cpl_fields(i)%source_comm_nb = MIN ( cpl_fields(i)%target_comm_nb, cpl_fields(i)%source_comm_nb)
  402. cpl_fields(i)%target_comm_nb = MIN ( cpl_fields(i)%target_comm_nb, cpl_fields(i)%source_comm_nb)
  403. ENDIF
  404. end do
  405. !
  406. ! Find valid number of coupling
  407. !
  408. do j = 1, cpl_field_nb
  409. ! OASIS sends = OASIS receives. Count only before event (/2)
  410. cpl_fields(j)%target_comm_nb = MIN ( cpl_fields(j)%source_comm_nb , cpl_fields(j)%target_comm_nb ) / 2
  411. ! Same number of "received" and "send" exchange
  412. cpl_fields(j)%source_comm_nb = cpl_fields(j)%target_comm_nb
  413. end do
  414. ! Substract 1 to number of coupling tstep
  415. ! (last exchange ignored to avoid side effect of termination phase)
  416. max_comm_nb = MAXVAL ( cpl_fields(:)%source_comm_nb ) - 1
  417. cpl_fields(:)%source_comm_nb = cpl_fields(:)%source_comm_nb - 1
  418. cpl_fields(:)%target_comm_nb = cpl_fields(:)%source_comm_nb
  419. ! Set the maximum number of coupling tstep per model
  420. valid_comm_nb(:) = 0
  421. do i = 1, nb_models
  422. do j = 1, cpl_field_nb
  423. IF ( cpl_fields(j)%source_model == i .or. cpl_fields(j)%target_model == i ) &
  424. valid_comm_nb(i) = MAX(valid_comm_nb(i),cpl_fields(j)%source_comm_nb)
  425. end do
  426. end do
  427. !
  428. ! 5. Allocate Timing Arrays
  429. ! - to fill with minimum or maximum clock time among log files
  430. ! before and after each coupling communications (put and get)
  431. ! and for each coupling field
  432. !
  433. ALLOCATE ( min_clock_measure ( cpl_field_nb, max_comm_nb , 4 ) )
  434. ALLOCATE ( max_clock_measure ( cpl_field_nb, max_comm_nb , 4 ) )
  435. ! initialize min/max counters
  436. min_clock_measure = r_impossible_value
  437. max_clock_measure = r_impossible_value * (-1.)
  438. !
  439. ! - to store calculation / non calculation time
  440. ! for each log file of the same model
  441. !
  442. ! calc_noncalc_measure ( : , 1 ) : total 'calculation' time
  443. ! calc_noncalc_measure ( : , 2 ) : total time spent during send operation
  444. ! calc_noncalc_measure ( : , 3 ) : total time spent during receive operation
  445. !
  446. nb_tot_log_files = SUM ( i_file_count(:) )
  447. ALLOCATE ( calc_noncalc_measure ( nb_tot_log_files, max_comm_nb, 3 ) )
  448. ALLOCATE ( r_interp_measure ( nb_tot_log_files ) )
  449. ! initialize measures total
  450. calc_noncalc_measure (:,:,:) = 0
  451. !
  452. ! 6. READ AGAIN OASIS-LUCIA LOG FILES CONTAINT
  453. ! AND FILL ARRAYS WITH ALL CLOCK TIME MEASURES
  454. !
  455. log_nb = 0
  456. r_max_time = r_impossible_value * (-1.)
  457. r_min_time = r_impossible_value
  458. ! Loop on model number
  459. DO i = 1, nb_models
  460. ! Loop on log file number
  461. DO j = 0, nb_mpi(i), i_stride(i)
  462. ! Count number of log file
  463. log_nb = log_nb + 1
  464. write(log_file_name,'("lucia.",a2,".",i6.6)'),model_code(i),j
  465. OPEN (unit=10, &
  466. file=TRIM(log_file_name), &
  467. action="read", &
  468. status="OLD", &
  469. form="formatted", &
  470. iostat=i_err)
  471. IF ( i_err .ne. 0 ) then
  472. write(6,*) 'Error opening ASCII file ', TRIM(log_file_name)
  473. STOP
  474. END IF
  475. REWIND(10)
  476. l_exch_still_valid = .true.
  477. l_exch_not_yet_valid = .true.
  478. c_test_name="not"
  479. mi = 0
  480. r_interp_measure(log_nb)=0
  481. l_add_interp_time=.false.
  482. i_err=0
  483. ! For each line of the log file
  484. DO WHILE ( i_err /= -1 .and. l_exch_still_valid )
  485. READ(10, '(A9,A3,A16,F16.5)', iostat=i_err) &
  486. & c_verif, &
  487. & c_field_code, &
  488. & c_comm_type, &
  489. & r_clock
  490. IF ( i_err == -1 ) CYCLE
  491. ! Substract first clock measure to store anomaly instead of raw value
  492. ! (to avoid too big values when additionning)
  493. IF ( c_field_code(1:3) == "IT " ) THEN
  494. r_reference = r_clock
  495. CYCLE
  496. ENDIF
  497. ! Skip model names
  498. IF ( c_field_code(1:3) == "MD " ) cycle
  499. ! Skip field names
  500. IF ( c_field_code(1:3) == "SN " .or. c_field_code(1:3) == "RC " ) cycle
  501. r_clock = r_clock - r_reference
  502. ! Special treatment for interpolation time :cumulated
  503. IF ( INDEX ( TRIM(c_comm_type), 'interpo' ) /= 0 ) then
  504. IF ( l_add_interp_time ) then
  505. r_interp_measure(log_nb) = r_interp_measure(log_nb) + r_clock
  506. l_add_interp_time=.false.
  507. ELSE
  508. r_interp_measure(log_nb) = r_interp_measure(log_nb) - r_clock
  509. l_add_interp_time=.true.
  510. ENDIF
  511. CYCLE
  512. ENDIF
  513. !
  514. ! PROCESS INFORMATION FROM STANDARD TIMING LINE
  515. !
  516. ! Get the name of the first field exchanged by this model
  517. IF ( TRIM(c_test_name) == "not" ) c_test_name=TRIM(c_field_code)
  518. ! write(6,*) 'c_comm_type ', c_comm_type
  519. ! write(6,*) 'c_test_name ', c_test_name
  520. ! write(6,*) 'TRIM(c_field_code) ', TRIM(c_field_code)
  521. !
  522. ! Find field name as declared in namcouple
  523. !
  524. k = 1
  525. DO WHILE ( k <= cpl_field_nb )
  526. READ(c_field_code,'(i3)') tmp_field_code
  527. IF ( cpl_fields(k)%namID == tmp_field_code ) &
  528. i_cpl = k
  529. k = k + 1
  530. END DO
  531. ! write(6,*) 'field number ', i_cpl
  532. !
  533. ! Determine if the exchange is a put or a get
  534. ! if the timing is set before or after the exchange
  535. l_put = .false.
  536. l_before = .false.
  537. !
  538. ! and attribute the corresponding index:
  539. ! 1: Before put
  540. ! 2: After put
  541. ! 3: Before get
  542. ! 4: After get
  543. IF ( INDEX ( TRIM(c_comm_type), c_ident_put ) /= 0 ) &
  544. l_put = .true.
  545. IF ( INDEX ( TRIM(c_comm_type), c_ident_before ) /= 0 ) &
  546. l_before = .true.
  547. IF ( l_before ) THEN
  548. IF ( l_put ) THEN
  549. clk_i = before_send
  550. ELSE
  551. clk_i = before_recv
  552. ENDIF
  553. ELSE
  554. IF ( l_put ) THEN
  555. clk_i = after_send
  556. ELSE
  557. clk_i = after_recv
  558. ENDIF
  559. ENDIF
  560. ! write(6,*) 'index number ', clk_i
  561. !
  562. ! Determine exchange validity
  563. !
  564. ! Measures start (coupler) the first time than a field is received
  565. ! This excludes restart reading sequence side effect if any
  566. !
  567. !
  568. IF ( l_exch_not_yet_valid .AND. cpl_fields(i_cpl)%source_comm_nb == valid_comm_nb(i) ) THEN
  569. l_exch_not_yet_valid = .false.
  570. ! Get the name of the first field exchanged by this model
  571. c_test_name = TRIM(c_field_code)
  572. ! and at what time it is
  573. r_min_time = MIN ( r_clock, r_min_time )
  574. END IF
  575. ! If before exchange of the first coupling field
  576. ! on a not yet valid exchange
  577. IF ( TRIM(c_field_code) == TRIM(c_test_name) .and. l_before &
  578. .and. .not. l_exch_not_yet_valid ) THEN
  579. ! Increase exchange number
  580. mi = mi + 1
  581. ! Before the last valid exchange
  582. IF ( mi <= valid_comm_nb(i) ) THEN
  583. ! calc/nocalc current index initialization
  584. calc_noncalc_measure ( log_nb, mi, 1 ) = &
  585. calc_noncalc_measure ( log_nb, mi, 1 ) - r_clock
  586. ENDIF
  587. ! After the first exchange
  588. IF ( mi > 1 ) THEN
  589. ! calc/nocalc previous index finalization
  590. calc_noncalc_measure ( log_nb, mi-1, 1 ) = &
  591. calc_noncalc_measure ( log_nb, mi-1, 1 ) + r_clock
  592. ENDIF
  593. ! Increase time counter to find timing of last exchange
  594. r_max_time = MAX ( r_clock, r_max_time )
  595. ! write(6,*) 'still valid ', l_exch_still_valid
  596. END IF
  597. ! Reach maximum number of valid exchanges
  598. IF ( mi > valid_comm_nb(i) ) &
  599. l_exch_still_valid = .false.
  600. ! Do not fill timer arrays if exchange not yet or no more valid
  601. IF ( l_exch_not_yet_valid .or. .not. l_exch_still_valid ) CYCLE
  602. ! write(6,*) 'not cycled ', TRIM(c_field_code)
  603. ! Fill mix/max array compared to previous log file measures
  604. min_clock_measure(i_cpl ,mi ,clk_i) = &
  605. MIN ( min_clock_measure(i_cpl ,mi ,clk_i), r_clock )
  606. max_clock_measure(i_cpl ,mi ,clk_i) = &
  607. MAX ( max_clock_measure(i_cpl ,mi ,clk_i), r_clock )
  608. ! Fill calc/noncalc array for each log file
  609. ! Sending time
  610. IF ( clk_i == after_send ) THEN
  611. calc_noncalc_measure ( log_nb, mi, 2 ) = &
  612. calc_noncalc_measure ( log_nb, mi, 2 ) + r_clock
  613. ELSE IF ( clk_i == before_send ) THEN
  614. calc_noncalc_measure ( log_nb, mi, 2 ) = &
  615. calc_noncalc_measure ( log_nb, mi, 2 ) - r_clock
  616. ! Receiving time
  617. ELSE IF ( clk_i == after_recv ) THEN
  618. calc_noncalc_measure ( log_nb, mi, 3 ) = &
  619. calc_noncalc_measure ( log_nb, mi, 3 ) + r_clock
  620. ELSE IF ( clk_i == before_recv ) THEN
  621. calc_noncalc_measure ( log_nb, mi, 3 ) = &
  622. calc_noncalc_measure ( log_nb, mi, 3 ) - r_clock
  623. ENDIF
  624. ! Calculation time
  625. IF ( MOD ( clk_i , after_send_or_recv ) == 1 ) THEN
  626. calc_noncalc_measure ( log_nb, mi, 1 ) = &
  627. calc_noncalc_measure ( log_nb, mi, 1 ) + r_clock
  628. ELSE
  629. calc_noncalc_measure ( log_nb, mi, 1 ) = &
  630. calc_noncalc_measure ( log_nb, mi, 1 ) - r_clock
  631. ENDIF
  632. ! End loop on read lines
  633. END DO
  634. CLOSE(10)
  635. ! End loop on log files
  636. END DO
  637. ! End loop on models
  638. END DO
  639. !
  640. ! 7. ANALYSIS
  641. !
  642. calc_time (:) = 0 ; noncalc_time (:) = 0
  643. send_spread (:) = 0 ; receive_spread (:) = 0; calc_spread (:) = 0
  644. !
  645. ! 7.1 ANALYSIS ON MAXIMUM MEAN VALUES AMONG LOG FILES
  646. !
  647. k = 1
  648. ! Loop on models
  649. DO i = 1, nb_models
  650. ! write(6,*), ' Model : ', i
  651. ! For most frequently coupled fields
  652. IF ( valid_comm_nb(i) == max_comm_nb ) THEN
  653. ! Start analysis on third exchange to avoid side effect
  654. first_valid_comm(i) = 3
  655. ELSE
  656. ! only on second for the others
  657. first_valid_comm(i) = 2
  658. END IF
  659. ! Special treatment for models not involved in coupling (IO servers)
  660. IF ( valid_comm_nb(i) == 0 ) first_valid_comm(i) = 1
  661. ! Loop on valid coupling tsteps
  662. DO j = first_valid_comm(i), valid_comm_nb(i)
  663. ! Maximum values over log files are added for all valid coupling tsteps
  664. ! ... for time spent by models on calculations
  665. calc_time (i) = calc_time (i) + MAXVAL(calc_noncalc_measure (k:k+i_file_count(i)-1, j, 1))
  666. ! ... for time spent by models on OASIS exchanges (send and receive operations)
  667. noncalc_time (i) = noncalc_time (i) + &
  668. MAXVAL(calc_noncalc_measure (k:k+i_file_count(i)-1, j, 2)) + &
  669. MAXVAL(calc_noncalc_measure (k:k+i_file_count(i)-1, j, 3))
  670. ! Variance among log file is calculated for those 2 values
  671. r_mean = SUM ( calc_noncalc_measure (k:k+i_file_count(i)-1, j, 2) ) / i_file_count(i)
  672. send_spread (i) = send_spread (i) + &
  673. SQRT ( SUM ( ( calc_noncalc_measure (k:k+i_file_count(i)-1, j, 2) - &
  674. r_mean ) ** 2 ) )
  675. r_mean = SUM ( calc_noncalc_measure (k:k+i_file_count(i)-1, j, 3) ) / i_file_count(i)
  676. receive_spread (i) = receive_spread (i) + &
  677. SQRT ( SUM ( ( calc_noncalc_measure (k:k+i_file_count(i)-1, j, 3) - &
  678. r_mean ) ** 2 ) )
  679. r_mean = SUM ( calc_noncalc_measure (k:k+i_file_count(i)-1, j, 1) ) / i_file_count(i)
  680. calc_spread (i) = calc_spread (i) + &
  681. SQRT ( SUM ( ( calc_noncalc_measure (k:k+i_file_count(i)-1, j, 1) - &
  682. r_mean ) ** 2 ) )
  683. !
  684. END DO
  685. ! Time spent on OASIS interpolation is a mean value among log files
  686. r_interp_time(i) = SUM(r_interp_measure(k:k+i_file_count(i)-1))/i_file_count(i)
  687. ! Counter on log file index among total log file number
  688. k = k + i_file_count(i)
  689. END DO
  690. !
  691. ! WRITE INFO ON STANDARD OUTPUT
  692. !
  693. ! Old analysis, no more active
  694. !
  695. ! WRITE(6,*) ' '
  696. ! WRITE(6,*), ' Component - Computation - Waiting time (s) - # cpl step '
  697. ! DO i = 1, nb_models
  698. ! WRITE(6,'(2X, A6, 5X, F10.2, A7, F6.2, A3, 5X, F10.2, A7, F6.2, A4, I4)'), &
  699. ! model_name(i), &
  700. ! calc_time(i), &
  701. ! ' ( +/- ', calc_spread(i) , ' ) ', &
  702. ! noncalc_time(i), &
  703. ! ' ( +/- ', send_spread(i)+receive_spread(i), ' ) ', &
  704. ! valid_comm_nb(i)-first_valid_comm(i)+1
  705. ! END DO
  706. ! WRITE(6,*), ' '
  707. ! call flush(6)
  708. !
  709. ! 7.2 ANALYSIS ON BOUNDARY VALUES AMONG LOG FILES
  710. !
  711. !
  712. r_min_time = 0. ; r_max_time = 0.
  713. !
  714. calc_time(:) = 0.
  715. noncalc_time(:) = 0.
  716. calc_time(:) = 0.
  717. r_jitter_time(:) = 0.
  718. ! loop on models
  719. DO k = 1, nb_models
  720. ! loop on coupling fields
  721. DO i = 1, cpl_field_nb
  722. ! If sent field
  723. IF ( cpl_fields(i)%source_model == k ) THEN
  724. ! loop on coupling time steps
  725. ! WARNING valid_comm_nb depends on cpl_field_nb (if different model
  726. ! with diff cpl time step)
  727. DO j = first_valid_comm(k), valid_comm_nb(k)
  728. ! If a timing is available for this coupling field at this coupling time step
  729. IF ( max_clock_measure (i,j,2) < r_test_impossible .and. max_clock_measure (i,j,1) < r_test_impossible ) &
  730. ! add sending time to the total of non calculation time
  731. noncalc_time(k) = max_clock_measure (i,j,2) - max_clock_measure (i,j,1) + &
  732. noncalc_time(k)
  733. ! WARNING : sending time starts when slowest mpi process check on log files is before sending
  734. ! and stops when slowest mpi process check on log files is after sending
  735. IF ( max_clock_measure (i,j,1) < r_test_impossible .and. ABS(min_clock_measure (i,j,1)) < r_test_impossible ) &
  736. ! Measure before sending between slowest and fastest mpi process check on log files
  737. r_jitter_time(k) = max_clock_measure (i,j,1) - min_clock_measure (i,j,1) + &
  738. r_jitter_time(k)
  739. ENDDO
  740. ! If received field
  741. ELSE IF ( cpl_fields(i)%target_model == k ) THEN
  742. ! loop on coupling time steps
  743. ! WARNING valid_comm_nb depends on cpl_field_nb (if different model
  744. ! with diff cpl time step)
  745. DO j = first_valid_comm(k), valid_comm_nb(k)
  746. ! If a timing is available for this coupling field at this coupling time step
  747. IF ( max_clock_measure (i,j,4) < r_test_impossible .and. max_clock_measure (i,j,3) < r_test_impossible ) &
  748. ! add receiving time to the total of non calculation time
  749. noncalc_time(k) = max_clock_measure (i,j,4) - max_clock_measure (i,j,3) + &
  750. noncalc_time(k)
  751. ! WARNING : receiving time starts when slowest mpi process check on log files is before receiving
  752. ! and stops when slowest mpi process check on log files is after receiving
  753. IF ( max_clock_measure (i,j,3) < r_test_impossible .and. ABS(min_clock_measure (i,j,3)) < r_test_impossible ) &
  754. ! Measure before receiving between slowest and fastest mpi process check on log files
  755. r_jitter_time(k) = max_clock_measure (i,j,3) - min_clock_measure (i,j,3) + &
  756. r_jitter_time(k)
  757. ENDDO
  758. ENDIF
  759. ENDDO
  760. !
  761. r_min_time = r_impossible_value * (-1.)
  762. r_max_time = r_impossible_value * (-1.)
  763. ! CALCULATE TIME BOUNDS
  764. l_put = .true.
  765. ! Loop on coupling fields
  766. DO i = 1, cpl_field_nb
  767. ! on target model
  768. IF ( cpl_fields(i)%target_model == k ) THEN
  769. ! Measure first valid time when field received (after receiving)
  770. temp_t = max_clock_measure(i,first_valid_comm(k)-1,4)
  771. ! If later than reference
  772. IF ( temp_t > r_min_time .and. temp_t < r_test_impossible ) &
  773. ! Set it as reference
  774. r_min_time = temp_t
  775. ! Measure last valid time when field received (after receiving)
  776. temp_t = max_clock_measure(i,valid_comm_nb(k),4)
  777. ! If later than reference
  778. IF ( temp_t > r_max_time .and. temp_t < r_test_impossible ) &
  779. ! Set it as reference
  780. r_max_time = temp_t
  781. l_put = .false.
  782. ENDIF
  783. ENDDO
  784. ! IF NO RECEIVED FIELD ON MODEL DO THE SAME THAN PREVIOUSLY BUT WITH SENT FIELDS
  785. IF ( l_put ) THEN
  786. ! Loop on coupling fields
  787. DO i = 1, cpl_field_nb
  788. ! on target model
  789. IF ( cpl_fields(i)%source_model == k ) THEN
  790. ! Measure first valid time when field received (after receiving)
  791. temp_t = max_clock_measure(i,first_valid_comm(k)-1,2)
  792. ! If later than reference
  793. IF ( temp_t > r_min_time .and. temp_t < r_test_impossible ) &
  794. ! Set it as reference
  795. r_min_time = temp_t
  796. ! Measure last valid time when field received (after receiving)
  797. temp_t = max_clock_measure(i,valid_comm_nb(k),2)
  798. ! If later than reference
  799. IF ( temp_t > r_max_time .and. temp_t < r_test_impossible ) &
  800. ! Set it as reference
  801. r_max_time = temp_t
  802. ENDIF
  803. ENDDO
  804. ENDIF
  805. !
  806. ! CALCULATION TIME defined as total time minus OASIS communication time
  807. calc_time(k) = r_max_time - r_min_time - noncalc_time(k)
  808. ! End loop on models
  809. ENDDO
  810. !
  811. WRITE(6,*) ' '
  812. WRITE(6,*), ' Load balance analysis '
  813. WRITE(6,*) ' '
  814. WRITE(6,*), ' Component - Calculations - Waiting time (s) - # cpl step :'
  815. !
  816. ! WRITE INFO ON DAT FILE FOR GNUPLOT AND STANDARD OUTPUT
  817. !
  818. WRITE(6,*) ' '
  819. OPEN (10, file="info.dat")
  820. DO i = 1, nb_models
  821. WRITE(10,'(I2, 2X, F10.3, 2X, F10.3, 2X, A6)'), &
  822. i, calc_time(i), noncalc_time(i), model_name(i)
  823. WRITE(6,'(2X, A6, 16X, F10.2, 12X, F10.2, 10X, I4)'), &
  824. model_name(i), calc_time(i), noncalc_time(i), valid_comm_nb(i)-first_valid_comm(i)+1
  825. ENDDO
  826. CLOSE (10)
  827. WRITE (6,*) ' '
  828. !
  829. WRITE(6,*), ' Additional informations'
  830. WRITE(6,*), ' Component - OASIS mean interpolation time - Jitter (s): '
  831. DO i = 1, nb_models
  832. WRITE(6,'(2X, A6, 12X, F10.2, 18X, F10.2 )'), &
  833. model_name(i), r_interp_time(i), r_jitter_time(i)
  834. END DO
  835. !
  836. WRITE (6,*) ' '
  837. WRITE (6,*) ' lucia completed successfully '
  838. WRITE (6,*) ' '
  839. end program lucia_analysis