main-lucia.F90 37 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960
  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=20) :: 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. ! Read model names
  235. IF ( c_field_code(1:3) == "MD " ) THEN
  236. IF ( TRIM(model_name(i)) == "none" ) model_name(i) = TRIM(c_dummy)
  237. cycle
  238. ENDIF
  239. IF ( c_field_code(1:3) == "NP " ) cycle
  240. ! Read field names as declared in namcouple
  241. IF ( c_field_code(1:3) == "SN " .or. c_field_code(1:3) == "RC " ) THEN
  242. BACKSPACE(10)
  243. READ(10, '(A9,A3,A5,A)', iostat=i_err) &
  244. & c_verif, &
  245. & c_field_code, &
  246. & c_dummy, &
  247. & c_field_name
  248. IF ( j == 0 ) THEN
  249. read(c_dummy(1:4),'(i4)') k
  250. field_name(i,k) = TRIM(c_field_name)
  251. ENDIF
  252. cycle
  253. ENDIF
  254. BACKSPACE(10)
  255. READ(10, '(A20,A3,A16,F16.5)', iostat=i_err) &
  256. & c_verif, &
  257. & c_field_code, &
  258. & c_comm_type, &
  259. & r_clock
  260. ! Skip if interpolation time measurement
  261. IF ( INDEX ( TRIM(c_comm_type),'rpo' ) /= 0 ) cycle
  262. !
  263. ! PROCESS INFORMATION FROM STANDARD TIMING LINE
  264. !
  265. ! When coupling field list is empty (beginning)
  266. IF ( i_cpl_field(i) == 0 ) THEN
  267. ! Fill list with first field found
  268. i_cpl_field(i) = 1
  269. READ(c_field_code,'(i3)') field_code(i, i_cpl_field(i))
  270. ! Start counting coupling steps
  271. comm_nb(i,i_cpl_field(i)) = 1
  272. ! if ( i == 2 ) write(6,*) ' field ', TRIM(field_code(i, 1)), comm_nb(i,1)
  273. ! Identify if it is a put or a get communication
  274. IF ( INDEX ( TRIM(c_comm_type), c_ident_put ) /= 0 ) THEN
  275. ! This communication is a put
  276. comm_type(i, i_cpl_field(i)) = 0
  277. start_time(i,i_cpl_field(i)) = r_clock
  278. ELSE
  279. ! This communication is a get
  280. comm_type(i, i_cpl_field(i)) = 1
  281. start_time(i,i_cpl_field(i)) = r_clock
  282. ENDIF
  283. ! When field list is not empty (loop)
  284. ELSE
  285. ! Coupling field index initialized
  286. mi = 1
  287. newf = 0
  288. ! Check model field number already identified
  289. DO WHILE ( mi <= i_cpl_field(i) )
  290. read(c_field_code,'(i3)') tmp_field_code
  291. IF ( field_code(i, mi) == tmp_field_code ) &
  292. newf = mi
  293. mi = mi + 1
  294. END DO
  295. ! Another field found because not identified in the list
  296. IF ( newf == 0 ) THEN
  297. ! Fill list with new field found (same than above)
  298. i_cpl_field(i) = i_cpl_field(i) + 1
  299. READ(c_field_code,'(i3)') field_code(i, i_cpl_field(i))
  300. comm_nb(i,i_cpl_field(i)) = 1
  301. ! Identify if it is a put or a get communication
  302. IF ( INDEX ( TRIM(c_comm_type), c_ident_put ) /= 0 ) THEN
  303. ! This communication is a put
  304. comm_type(i, i_cpl_field(i)) = 0
  305. start_time(i,i_cpl_field(i)) = r_clock
  306. ELSE
  307. comm_type(i, i_cpl_field(i)) = 1
  308. start_time(i,i_cpl_field(i)) = r_clock
  309. ENDIF
  310. ! Just another coupling step for an already identified field
  311. ELSE
  312. comm_nb(i,newf) = comm_nb(i,newf) + 1
  313. END IF
  314. END IF
  315. ! End loop on read lines
  316. END DO
  317. CLOSE(10)
  318. ! End loop on log files
  319. END DO
  320. write(6,*) ' '
  321. !
  322. ! write(6,*) ' nbFields ', model_name(i) , i_cpl_field(i)
  323. ! do k = 1, i_cpl_field(i)
  324. ! write(6,*) ' Field ', field_code(i, k), comm_type(i,k)
  325. ! ENDDO
  326. !
  327. ! End loop on models
  328. END DO
  329. !
  330. ! Coupling fields counterd twice (as sent and received field)
  331. cpl_field_nb = SUM(i_cpl_field(:))/2
  332. ALLOCATE ( cpl_fields ( cpl_field_nb ) )
  333. !
  334. ! write(6,*) ' nb fields ', cpl_field_nb
  335. ! call flush(6)
  336. !
  337. !
  338. DO i = 1, nb_models
  339. ! Count total send/received fields (divide by proc number)
  340. comm_nb(i,:) = comm_nb(i,:) / i_file_count(i)
  341. END DO
  342. !
  343. ! 3. FIND EXCHANGE ORDER
  344. !
  345. j = 1
  346. ! loop on coupling fields
  347. DO WHILE ( j <= cpl_field_nb )
  348. ! Find the earliest exchange
  349. i_first_exchg = MINLOC(start_time(:,:))
  350. ! Index of model doing the first exchange
  351. mi = i_first_exchg(1)
  352. ! Index of first field exchanged
  353. i = i_first_exchg(2)
  354. ! only if it is a send field
  355. IF ( comm_type(mi,i) == 0 ) THEN
  356. ! Find the exchange number in OASIS sequence (namcouple)
  357. cpl_fields(j)%namID = field_code ( mi, i )
  358. ! Set its source model
  359. cpl_fields(j)%source_model = mi
  360. ! Set how many times this coupling field has been sent
  361. cpl_fields(j)%source_comm_nb = comm_nb( mi, i )
  362. !
  363. DO k = 1, nb_models
  364. IF ( k == mi ) cycle
  365. IF ( ANY ( field_code ( k, 1:i_cpl_field(k) ) == cpl_fields(j)%namID)) THEN
  366. ! Set its target model
  367. cpl_fields(j)%target_model = k
  368. DO l = 1, i_cpl_field(k)
  369. IF ( field_code(k,l) == cpl_fields(j)%namID ) &
  370. ! Set how many times this coupling field has been received
  371. cpl_fields(j)%target_comm_nb = comm_nb( k, l )
  372. END DO
  373. END IF
  374. END DO
  375. j = j + 1
  376. END IF
  377. start_time(mi,i) = r_impossible_value
  378. END DO
  379. !
  380. write (6,*) ' '
  381. write (6,*) ' "Lucia" analysis '
  382. write (6,*) ' '
  383. write (6,*) ' Exchanged fields (based on first exchange): '
  384. !
  385. write (6,*) ' From model : to model '
  386. DO i = 1, cpl_field_nb
  387. write (6,*) ' ', TRIM(model_name(cpl_fields(i)%source_model)), &
  388. ' ( ', TRIM(field_name(cpl_fields(i)%source_model,cpl_fields(i)%namID)), &
  389. ' ) ', TRIM(model_name(cpl_fields(i)%target_model)), &
  390. ' ( ', TRIM(field_name(cpl_fields(i)%target_model,cpl_fields(i)%namID)) , ' )'
  391. END DO
  392. ! write (6,*) ' '
  393. ! call flush(6)
  394. !
  395. ! 4. CHECK COMMUNICATION NUMBER CONCORDANCE
  396. !
  397. do i = 1, cpl_field_nb
  398. IF ( cpl_fields(i)%target_comm_nb /= cpl_fields(i)%source_comm_nb ) THEN
  399. write(6,*) ' WARNING - Coupler exchanges: ' , &
  400. TRIM(field_name(cpl_fields(i)%source_model,cpl_fields(i)%namID)) , &
  401. ' sent ', cpl_fields(i)%source_comm_nb, &
  402. ' but ', TRIM(field_name(cpl_fields(i)%target_model,cpl_fields(i)%namID)) , &
  403. ' received ', cpl_fields(i)%target_comm_nb
  404. !
  405. ! In case of unbalanced exchange number (abnormal stop),
  406. ! restrain communication number according to the last valid exchange number
  407. !
  408. cpl_fields(i)%source_comm_nb = MIN ( cpl_fields(i)%target_comm_nb, cpl_fields(i)%source_comm_nb)
  409. cpl_fields(i)%target_comm_nb = MIN ( cpl_fields(i)%target_comm_nb, cpl_fields(i)%source_comm_nb)
  410. ENDIF
  411. end do
  412. !
  413. ! Find valid number of coupling
  414. !
  415. do j = 1, cpl_field_nb
  416. ! OASIS sends = OASIS receives. Count only before event (/2)
  417. cpl_fields(j)%target_comm_nb = MIN ( cpl_fields(j)%source_comm_nb , cpl_fields(j)%target_comm_nb ) / 2
  418. ! Same number of "received" and "send" exchange
  419. cpl_fields(j)%source_comm_nb = cpl_fields(j)%target_comm_nb
  420. end do
  421. ! Substract 1 to number of coupling tstep
  422. ! (last exchange ignored to avoid side effect of termination phase)
  423. max_comm_nb = MAXVAL ( cpl_fields(:)%source_comm_nb ) - 1
  424. cpl_fields(:)%source_comm_nb = cpl_fields(:)%source_comm_nb - 1
  425. cpl_fields(:)%target_comm_nb = cpl_fields(:)%source_comm_nb
  426. ! Set the maximum number of coupling tstep per model
  427. valid_comm_nb(:) = 0
  428. do i = 1, nb_models
  429. do j = 1, cpl_field_nb
  430. IF ( cpl_fields(j)%source_model == i .or. cpl_fields(j)%target_model == i ) &
  431. valid_comm_nb(i) = MAX(valid_comm_nb(i),cpl_fields(j)%source_comm_nb)
  432. end do
  433. end do
  434. !
  435. ! 5. Allocate Timing Arrays
  436. ! - to fill with minimum or maximum clock time among log files
  437. ! before and after each coupling communications (put and get)
  438. ! and for each coupling field
  439. !
  440. ALLOCATE ( min_clock_measure ( cpl_field_nb, max_comm_nb , 4 ) )
  441. ALLOCATE ( max_clock_measure ( cpl_field_nb, max_comm_nb , 4 ) )
  442. ! initialize min/max counters
  443. min_clock_measure = r_impossible_value
  444. max_clock_measure = r_impossible_value * (-1.)
  445. !
  446. ! - to store calculation / non calculation time
  447. ! for each log file of the same model
  448. !
  449. ! calc_noncalc_measure ( : , 1 ) : total 'calculation' time
  450. ! calc_noncalc_measure ( : , 2 ) : total time spent during send operation
  451. ! calc_noncalc_measure ( : , 3 ) : total time spent during receive operation
  452. !
  453. nb_tot_log_files = SUM ( i_file_count(:) )
  454. ALLOCATE ( calc_noncalc_measure ( nb_tot_log_files, max_comm_nb, 3 ) )
  455. ALLOCATE ( r_interp_measure ( nb_tot_log_files ) )
  456. ! initialize measures total
  457. calc_noncalc_measure (:,:,:) = 0
  458. !
  459. ! 6. READ AGAIN OASIS-LUCIA LOG FILES CONTAINT
  460. ! AND FILL ARRAYS WITH ALL CLOCK TIME MEASURES
  461. !
  462. log_nb = 0
  463. r_max_time = r_impossible_value * (-1.)
  464. r_min_time = r_impossible_value
  465. ! Loop on model number
  466. DO i = 1, nb_models
  467. ! Loop on log file number
  468. DO j = 0, nb_mpi(i), i_stride(i)
  469. ! Count number of log file
  470. log_nb = log_nb + 1
  471. write(log_file_name,'("lucia.",a2,".",i6.6)'),model_code(i),j
  472. OPEN (unit=10, &
  473. file=TRIM(log_file_name), &
  474. action="read", &
  475. status="OLD", &
  476. form="formatted", &
  477. iostat=i_err)
  478. IF ( i_err .ne. 0 ) then
  479. write(6,*) 'Error opening ASCII file ', TRIM(log_file_name)
  480. STOP
  481. END IF
  482. REWIND(10)
  483. l_exch_still_valid = .true.
  484. l_exch_not_yet_valid = .true.
  485. c_test_name="not"
  486. mi = 0
  487. r_interp_measure(log_nb)=0
  488. l_add_interp_time=.false.
  489. i_err=0
  490. ! For each line of the log file
  491. DO WHILE ( i_err /= -1 .and. l_exch_still_valid )
  492. READ(10, '(A20,A3,A16,F16.5)', iostat=i_err) &
  493. & c_verif, &
  494. & c_field_code, &
  495. & c_comm_type, &
  496. & r_clock
  497. IF ( i_err == -1 ) CYCLE
  498. ! Substract first clock measure to store anomaly instead of raw value
  499. ! (to avoid too big values when additionning)
  500. IF ( c_verif(10:12) == "IT " ) THEN
  501. BACKSPACE(10)
  502. READ(10, '(A20,A3,A7,F16.5)', iostat=i_err) &
  503. & c_verif, &
  504. & c_field_code, &
  505. & c_comm_type, &
  506. & r_clock
  507. r_reference = r_clock
  508. CYCLE
  509. ENDIF
  510. ! Skip model names
  511. IF ( c_verif(10:12) == "MD " ) cycle
  512. IF ( c_verif(10:12) == "NP " ) cycle
  513. ! Skip field names
  514. IF ( c_verif(10:12) == "SN " .or. c_verif(10:12) == "RC " ) cycle
  515. r_clock = r_clock - r_reference
  516. ! Special treatment for interpolation time :cumulated
  517. IF ( INDEX ( TRIM(c_comm_type), 'interpo' ) /= 0 ) then
  518. IF ( l_add_interp_time ) then
  519. r_interp_measure(log_nb) = r_interp_measure(log_nb) + r_clock
  520. l_add_interp_time=.false.
  521. ELSE
  522. r_interp_measure(log_nb) = r_interp_measure(log_nb) - r_clock
  523. l_add_interp_time=.true.
  524. ENDIF
  525. CYCLE
  526. ENDIF
  527. !
  528. ! PROCESS INFORMATION FROM STANDARD TIMING LINE
  529. !
  530. ! Get the name of the first field exchanged by this model
  531. IF ( TRIM(c_test_name) == "not" ) c_test_name=TRIM(c_field_code)
  532. ! write(6,*) 'c_comm_type ', c_comm_type
  533. ! write(6,*) 'c_test_name ', c_test_name
  534. ! write(6,*) 'TRIM(c_field_code) ', TRIM(c_field_code)
  535. !
  536. ! Find field name as declared in namcouple
  537. !
  538. k = 1
  539. DO WHILE ( k <= cpl_field_nb )
  540. READ(c_field_code,'(i3)') tmp_field_code
  541. IF ( cpl_fields(k)%namID == tmp_field_code ) &
  542. i_cpl = k
  543. k = k + 1
  544. END DO
  545. ! write(6,*) 'field number ', i_cpl
  546. !
  547. ! Determine if the exchange is a put or a get
  548. ! if the timing is set before or after the exchange
  549. l_put = .false.
  550. l_before = .false.
  551. !
  552. ! and attribute the corresponding index:
  553. ! 1: Before put
  554. ! 2: After put
  555. ! 3: Before get
  556. ! 4: After get
  557. IF ( INDEX ( TRIM(c_comm_type), c_ident_put ) /= 0 ) &
  558. l_put = .true.
  559. IF ( INDEX ( TRIM(c_comm_type), c_ident_before ) /= 0 ) &
  560. l_before = .true.
  561. IF ( l_before ) THEN
  562. IF ( l_put ) THEN
  563. clk_i = before_send
  564. ELSE
  565. clk_i = before_recv
  566. ENDIF
  567. ELSE
  568. IF ( l_put ) THEN
  569. clk_i = after_send
  570. ELSE
  571. clk_i = after_recv
  572. ENDIF
  573. ENDIF
  574. ! write(6,*) 'index number ', clk_i
  575. !
  576. ! Determine exchange validity
  577. !
  578. ! Measures start (coupler) the first time than a field is received
  579. ! This excludes restart reading sequence side effect if any
  580. !
  581. !
  582. IF ( l_exch_not_yet_valid .AND. cpl_fields(i_cpl)%source_comm_nb == valid_comm_nb(i) ) THEN
  583. l_exch_not_yet_valid = .false.
  584. ! Get the name of the first field exchanged by this model
  585. c_test_name = TRIM(c_field_code)
  586. ! and at what time it is
  587. r_min_time = MIN ( r_clock, r_min_time )
  588. END IF
  589. ! If before exchange of the first coupling field
  590. ! on a not yet valid exchange
  591. IF ( TRIM(c_field_code) == TRIM(c_test_name) .and. l_before &
  592. .and. .not. l_exch_not_yet_valid ) THEN
  593. ! Increase exchange number
  594. mi = mi + 1
  595. ! Before the last valid exchange
  596. IF ( mi <= valid_comm_nb(i) ) THEN
  597. ! calc/nocalc current index initialization
  598. calc_noncalc_measure ( log_nb, mi, 1 ) = &
  599. calc_noncalc_measure ( log_nb, mi, 1 ) - r_clock
  600. ENDIF
  601. ! After the first exchange
  602. IF ( mi > 1 ) THEN
  603. ! calc/nocalc previous index finalization
  604. calc_noncalc_measure ( log_nb, mi-1, 1 ) = &
  605. calc_noncalc_measure ( log_nb, mi-1, 1 ) + r_clock
  606. ENDIF
  607. ! Increase time counter to find timing of last exchange
  608. r_max_time = MAX ( r_clock, r_max_time )
  609. ! write(6,*) 'still valid ', l_exch_still_valid
  610. END IF
  611. ! Reach maximum number of valid exchanges
  612. IF ( mi > valid_comm_nb(i) ) &
  613. l_exch_still_valid = .false.
  614. ! Do not fill timer arrays if exchange not yet or no more valid
  615. IF ( l_exch_not_yet_valid .or. .not. l_exch_still_valid ) CYCLE
  616. ! write(6,*) 'not cycled ', TRIM(c_field_code)
  617. ! Fill mix/max array compared to previous log file measures
  618. min_clock_measure(i_cpl ,mi ,clk_i) = &
  619. MIN ( min_clock_measure(i_cpl ,mi ,clk_i), r_clock )
  620. max_clock_measure(i_cpl ,mi ,clk_i) = &
  621. MAX ( max_clock_measure(i_cpl ,mi ,clk_i), r_clock )
  622. ! Fill calc/noncalc array for each log file
  623. ! Sending time
  624. IF ( clk_i == after_send ) THEN
  625. calc_noncalc_measure ( log_nb, mi, 2 ) = &
  626. calc_noncalc_measure ( log_nb, mi, 2 ) + r_clock
  627. ELSE IF ( clk_i == before_send ) THEN
  628. calc_noncalc_measure ( log_nb, mi, 2 ) = &
  629. calc_noncalc_measure ( log_nb, mi, 2 ) - r_clock
  630. ! Receiving time
  631. ELSE IF ( clk_i == after_recv ) THEN
  632. calc_noncalc_measure ( log_nb, mi, 3 ) = &
  633. calc_noncalc_measure ( log_nb, mi, 3 ) + r_clock
  634. ELSE IF ( clk_i == before_recv ) THEN
  635. calc_noncalc_measure ( log_nb, mi, 3 ) = &
  636. calc_noncalc_measure ( log_nb, mi, 3 ) - r_clock
  637. ENDIF
  638. ! Calculation time
  639. IF ( MOD ( clk_i , after_send_or_recv ) == 1 ) THEN
  640. calc_noncalc_measure ( log_nb, mi, 1 ) = &
  641. calc_noncalc_measure ( log_nb, mi, 1 ) + r_clock
  642. ELSE
  643. calc_noncalc_measure ( log_nb, mi, 1 ) = &
  644. calc_noncalc_measure ( log_nb, mi, 1 ) - r_clock
  645. ENDIF
  646. ! End loop on read lines
  647. END DO
  648. CLOSE(10)
  649. ! End loop on log files
  650. END DO
  651. ! End loop on models
  652. END DO
  653. !
  654. ! 7. ANALYSIS
  655. !
  656. calc_time (:) = 0 ; noncalc_time (:) = 0
  657. send_spread (:) = 0 ; receive_spread (:) = 0; calc_spread (:) = 0
  658. !
  659. ! 7.1 ANALYSIS ON MAXIMUM MEAN VALUES AMONG LOG FILES
  660. !
  661. k = 1
  662. ! Loop on models
  663. DO i = 1, nb_models
  664. ! write(6,*), ' Model : ', i
  665. ! For most frequently coupled fields
  666. IF ( valid_comm_nb(i) == max_comm_nb ) THEN
  667. ! Start analysis on third exchange to avoid side effect
  668. first_valid_comm(i) = 3
  669. ELSE
  670. ! only on second for the others
  671. first_valid_comm(i) = 2
  672. END IF
  673. ! Special treatment for models not involved in coupling (IO servers)
  674. IF ( valid_comm_nb(i) == 0 ) first_valid_comm(i) = 1
  675. ! Loop on valid coupling tsteps
  676. DO j = first_valid_comm(i), valid_comm_nb(i)
  677. ! Maximum values over log files are added for all valid coupling tsteps
  678. ! ... for time spent by models on calculations
  679. calc_time (i) = calc_time (i) + MAXVAL(calc_noncalc_measure (k:k+i_file_count(i)-1, j, 1))
  680. ! ... for time spent by models on OASIS exchanges (send and receive operations)
  681. noncalc_time (i) = noncalc_time (i) + &
  682. MAXVAL(calc_noncalc_measure (k:k+i_file_count(i)-1, j, 2)) + &
  683. MAXVAL(calc_noncalc_measure (k:k+i_file_count(i)-1, j, 3))
  684. ! Variance among log file is calculated for those 2 values
  685. r_mean = SUM ( calc_noncalc_measure (k:k+i_file_count(i)-1, j, 2) ) / i_file_count(i)
  686. send_spread (i) = send_spread (i) + &
  687. SQRT ( SUM ( ( calc_noncalc_measure (k:k+i_file_count(i)-1, j, 2) - &
  688. r_mean ) ** 2 ) )
  689. r_mean = SUM ( calc_noncalc_measure (k:k+i_file_count(i)-1, j, 3) ) / i_file_count(i)
  690. receive_spread (i) = receive_spread (i) + &
  691. SQRT ( SUM ( ( calc_noncalc_measure (k:k+i_file_count(i)-1, j, 3) - &
  692. r_mean ) ** 2 ) )
  693. r_mean = SUM ( calc_noncalc_measure (k:k+i_file_count(i)-1, j, 1) ) / i_file_count(i)
  694. calc_spread (i) = calc_spread (i) + &
  695. SQRT ( SUM ( ( calc_noncalc_measure (k:k+i_file_count(i)-1, j, 1) - &
  696. r_mean ) ** 2 ) )
  697. !
  698. END DO
  699. ! Time spent on OASIS interpolation is a mean value among log files
  700. r_interp_time(i) = SUM(r_interp_measure(k:k+i_file_count(i)-1))/i_file_count(i)
  701. ! Counter on log file index among total log file number
  702. k = k + i_file_count(i)
  703. END DO
  704. !
  705. ! WRITE INFO ON STANDARD OUTPUT
  706. !
  707. ! Old analysis, no more active
  708. !
  709. ! WRITE(6,*) ' '
  710. ! WRITE(6,*), ' Component - Computation - Waiting time (s) - # cpl step '
  711. ! DO i = 1, nb_models
  712. ! WRITE(6,'(2X, A6, 5X, F10.2, A7, F6.2, A3, 5X, F10.2, A7, F6.2, A4, I4)'), &
  713. ! model_name(i), &
  714. ! calc_time(i), &
  715. ! ' ( +/- ', calc_spread(i) , ' ) ', &
  716. ! noncalc_time(i), &
  717. ! ' ( +/- ', send_spread(i)+receive_spread(i), ' ) ', &
  718. ! valid_comm_nb(i)-first_valid_comm(i)+1
  719. ! END DO
  720. ! WRITE(6,*), ' '
  721. ! call flush(6)
  722. !
  723. ! 7.2 ANALYSIS ON BOUNDARY VALUES AMONG LOG FILES
  724. !
  725. !
  726. r_min_time = 0. ; r_max_time = 0.
  727. !
  728. calc_time(:) = 0.
  729. noncalc_time(:) = 0.
  730. calc_time(:) = 0.
  731. r_jitter_time(:) = 0.
  732. ! loop on models
  733. DO k = 1, nb_models
  734. ! loop on coupling fields
  735. DO i = 1, cpl_field_nb
  736. ! If sent field
  737. IF ( cpl_fields(i)%source_model == k ) THEN
  738. ! loop on coupling time steps
  739. ! WARNING valid_comm_nb depends on cpl_field_nb (if different model
  740. ! with diff cpl time step)
  741. DO j = first_valid_comm(k), valid_comm_nb(k)
  742. ! If a timing is available for this coupling field at this coupling time step
  743. IF ( max_clock_measure (i,j,2) < r_test_impossible .and. max_clock_measure (i,j,1) < r_test_impossible ) &
  744. ! add sending time to the total of non calculation time
  745. noncalc_time(k) = max_clock_measure (i,j,2) - max_clock_measure (i,j,1) + &
  746. noncalc_time(k)
  747. ! WARNING : sending time starts when slowest mpi process check on log files is before sending
  748. ! and stops when slowest mpi process check on log files is after sending
  749. IF ( max_clock_measure (i,j,1) < r_test_impossible .and. ABS(min_clock_measure (i,j,1)) < r_test_impossible ) &
  750. ! Measure before sending between slowest and fastest mpi process check on log files
  751. r_jitter_time(k) = max_clock_measure (i,j,1) - min_clock_measure (i,j,1) + &
  752. r_jitter_time(k)
  753. ENDDO
  754. ! If received field
  755. ELSE IF ( cpl_fields(i)%target_model == k ) THEN
  756. ! loop on coupling time steps
  757. ! WARNING valid_comm_nb depends on cpl_field_nb (if different model
  758. ! with diff cpl time step)
  759. DO j = first_valid_comm(k), valid_comm_nb(k)
  760. ! If a timing is available for this coupling field at this coupling time step
  761. IF ( max_clock_measure (i,j,4) < r_test_impossible .and. max_clock_measure (i,j,3) < r_test_impossible ) &
  762. ! add receiving time to the total of non calculation time
  763. noncalc_time(k) = max_clock_measure (i,j,4) - max_clock_measure (i,j,3) + &
  764. noncalc_time(k)
  765. ! WARNING : receiving time starts when slowest mpi process check on log files is before receiving
  766. ! and stops when slowest mpi process check on log files is after receiving
  767. IF ( max_clock_measure (i,j,3) < r_test_impossible .and. ABS(min_clock_measure (i,j,3)) < r_test_impossible ) &
  768. ! Measure before receiving between slowest and fastest mpi process check on log files
  769. r_jitter_time(k) = max_clock_measure (i,j,3) - min_clock_measure (i,j,3) + &
  770. r_jitter_time(k)
  771. ENDDO
  772. ENDIF
  773. ENDDO
  774. !
  775. r_min_time = r_impossible_value * (-1.)
  776. r_max_time = r_impossible_value * (-1.)
  777. ! CALCULATE TIME BOUNDS
  778. l_put = .true.
  779. ! Loop on coupling fields
  780. DO i = 1, cpl_field_nb
  781. ! on target model
  782. IF ( cpl_fields(i)%target_model == k ) THEN
  783. ! Measure first valid time when field received (after receiving)
  784. temp_t = max_clock_measure(i,first_valid_comm(k)-1,4)
  785. ! If later than reference
  786. IF ( temp_t > r_min_time .and. temp_t < r_test_impossible ) &
  787. ! Set it as reference
  788. r_min_time = temp_t
  789. ! Measure last valid time when field received (after receiving)
  790. temp_t = max_clock_measure(i,valid_comm_nb(k),4)
  791. ! If later than reference
  792. IF ( temp_t > r_max_time .and. temp_t < r_test_impossible ) &
  793. ! Set it as reference
  794. r_max_time = temp_t
  795. l_put = .false.
  796. ENDIF
  797. ENDDO
  798. ! IF NO RECEIVED FIELD ON MODEL DO THE SAME THAN PREVIOUSLY BUT WITH SENT FIELDS
  799. IF ( l_put ) THEN
  800. ! Loop on coupling fields
  801. DO i = 1, cpl_field_nb
  802. ! on target model
  803. IF ( cpl_fields(i)%source_model == k ) THEN
  804. ! Measure first valid time when field received (after receiving)
  805. temp_t = max_clock_measure(i,first_valid_comm(k)-1,2)
  806. ! If later than reference
  807. IF ( temp_t > r_min_time .and. temp_t < r_test_impossible ) &
  808. ! Set it as reference
  809. r_min_time = temp_t
  810. ! Measure last valid time when field received (after receiving)
  811. temp_t = max_clock_measure(i,valid_comm_nb(k),2)
  812. ! If later than reference
  813. IF ( temp_t > r_max_time .and. temp_t < r_test_impossible ) &
  814. ! Set it as reference
  815. r_max_time = temp_t
  816. ENDIF
  817. ENDDO
  818. ENDIF
  819. !
  820. ! CALCULATION TIME defined as total time minus OASIS communication time
  821. calc_time(k) = r_max_time - r_min_time - noncalc_time(k)
  822. ! End loop on models
  823. ENDDO
  824. !
  825. WRITE(6,*) ' '
  826. WRITE(6,*), ' Load balance analysis '
  827. WRITE(6,*) ' '
  828. WRITE(6,*), ' Component - Calculations - Waiting time (s) - # cpl step :'
  829. !
  830. ! WRITE INFO ON DAT FILE FOR GNUPLOT AND STANDARD OUTPUT
  831. !
  832. WRITE(6,*) ' '
  833. OPEN (10, file="info.dat")
  834. DO i = 1, nb_models
  835. WRITE(10,'(I2, 2X, F10.3, 2X, F10.3, 2X, A6)'), &
  836. i, calc_time(i), noncalc_time(i), model_name(i)
  837. WRITE(6,'(2X, A6, 16X, F10.2, 12X, F10.2, 10X, I4)'), &
  838. model_name(i), calc_time(i), noncalc_time(i), valid_comm_nb(i)-first_valid_comm(i)+1
  839. ENDDO
  840. CLOSE (10)
  841. WRITE (6,*) ' '
  842. !
  843. WRITE(6,*), ' Additional informations'
  844. WRITE(6,*), ' Component - OASIS mean interpolation time - Jitter (s): '
  845. DO i = 1, nb_models
  846. WRITE(6,'(2X, A6, 12X, F10.2, 18X, F10.2 )'), &
  847. model_name(i), r_interp_time(i), r_jitter_time(i)
  848. END DO
  849. !
  850. WRITE (6,*) ' '
  851. WRITE (6,*) ' lucia completed successfully '
  852. WRITE (6,*) ' '
  853. end program lucia_analysis