source: palm/trunk/SOURCE/cpulog_mod.f90 @ 2716

Last change on this file since 2716 was 2716, checked in by kanani, 6 years ago

Correction of "Former revisions" section

  • Property svn:keywords set to Id
File size: 22.0 KB
Line 
1!> @file cpulog_mod.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2017 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: cpulog_mod.f90 2716 2017-12-29 16:35:59Z kanani $
27! Corrected "Former revisions" section
28!
29! 2696 2017-12-14 17:12:51Z kanani
30! Change in file header (GPL part)
31!
32! 2266 2017-06-09 09:27:21Z raasch
33! bugfix: cpu-time per grid point is now calculated using ngp_3d in order to
34! avoid integer overflow,
35! some re-formatting
36!
37! 2119 2017-01-17 16:51:50Z raasch
38!
39! 2118 2017-01-17 16:38:49Z raasch
40! OpenACC relevant code removed
41!
42! 2000 2016-08-20 18:09:15Z knoop
43! Forced header and separation lines into 80 columns
44!
45! 1931 2016-06-10 12:06:59Z suehring
46! Adjustment in character length and format statement
47!
48! 1850 2016-04-08 13:29:27Z maronga
49! Module renamed
50!
51!
52! 1808 2016-04-05 19:44:00Z raasch
53! cpu measurements are done with standard FORTRAN routine on every machine
54!
55! 1682 2015-10-07 23:56:08Z knoop
56! Code annotations made doxygen readable
57!
58! 1402 2014-05-09 14:25:13Z raasch
59! location messages added
60!
61! 1369 2014-04-24 05:57:38Z raasch
62! routine description added
63!
64! 1353 2014-04-08 15:21:23Z heinze
65! REAL constants provided with KIND-attribute
66!
67! 1322 2014-03-20 16:38:49Z raasch
68! REAL functions provided with KIND-attribute
69!
70! 1320 2014-03-20 08:40:49Z raasch
71! ONLY-attribute added to USE-statements,
72! kind-parameters added to all INTEGER and REAL declaration statements,
73! kinds are defined in new module kinds,
74! revision history before 2012 removed,
75! comment fields (!:) to be used for variable explanations added to
76! all variable declaration statements
77!
78! 1318 2014-03-17 13:35:16Z raasch
79! former files/routines cpu_log and cpu_statistics combined to one module,
80! which also includes the former data module cpulog from the modules-file
81!
82! 1036 2012-10-22 13:43:42Z raasch
83! code put under GPL (PALM 3.9)
84!
85! Revision 1.1  1997/07/24 11:12:29  raasch
86! Initial revision
87!
88!
89! Description:
90! ------------
91!> CPU-time measurements for any program part whatever. Results of the
92!> measurements are output at the end of the run in local file CPU_MEASURES.
93!>
94!> To measure the CPU-time (better to say the wallclock time) of a specific code
95!> segment, two calls of cpu_log have to be used as brackets in front and at the
96!> end of the segment:
97!>
98!>     CALL cpu_log( log_point(n), 'any identifier', 'start' )
99!>       ... code segment ...
100!>     CALL cpu_log( log_point(n), 'any identifier', 'stop' )
101!>
102!> Parts of the code segment can be excluded from the measurement by additional
103!> call of cpu_log:
104!>
105!>       ... first segment to be measured
106!>     CALL cpu_log( log_point(n), 'any identifier', 'pause' )
107!>       ... oart of segment to be excluded from measurement
108!>     CALL cpu_log( log_point(n), 'any identifier', 'continue' )
109!>       ... second segment to be mesasured
110!>
111!> n is an INTEGER within the interval [1,100] defining the id of the specific
112!> code segment, 'any identifier' is a string describing the code segment to be
113!> measured. It can be freely chosen and results will appear under this name in
114!> file CPU_MEASURES. ids can only be used once. If you like to do a
115!> measurement of a new part of the code, please look for an id which is unused
116!> ao far.
117!>
118!> d3par-parameter cpu_log_barrierwait can be used to set an MPI barrier at the
119!> beginning of the measurement (modus 'start' or 'continue'), to avoid that
120!> idle times (due to MPI calls in the code segment, which are
121!> waiting for other processes to be finished) affect the measurements.
122!> If barriers shall not be used at all, a fourth, optional parameter has to be
123!> given:
124!>
125!>     CALL cpu_log( ..., ..., 'start', cpu_log_nowait )
126!>
127!> Variable log_point should be used for non-overlapping code segments, and they
128!> should sum up to the total cpu-time required by the complete run.
129!> Variable log_point_s can be used for any other special (s) measurements.
130!------------------------------------------------------------------------------!
131 MODULE cpulog
132 
133
134    USE control_parameters,                                                    &
135        ONLY: message_string, nr_timesteps_this_run, run_description_header,   &
136              synchronous_exchange
137               
138    USE indices,                                                               &
139        ONLY: ngp_3d, nx, ny, nz
140       
141    USE kinds
142   
143    USE pegrid
144
145    IMPLICIT NONE
146
147    PRIVATE
148    PUBLIC   cpu_log, cpu_log_barrierwait, cpu_log_nowait, cpu_statistics,     &
149             initial_wallclock_time, log_point, log_point_s
150
151    INTERFACE cpu_log
152       MODULE PROCEDURE cpu_log
153    END INTERFACE cpu_log
154
155    INTERFACE cpu_statistics
156       MODULE PROCEDURE cpu_statistics
157    END INTERFACE cpu_statistics
158
159    INTEGER(iwp), PARAMETER ::  cpu_log_continue = 0  !<
160    INTEGER(iwp), PARAMETER ::  cpu_log_pause = 1     !<
161    INTEGER(iwp), PARAMETER ::  cpu_log_start = 2     !<
162    INTEGER(iwp), PARAMETER ::  cpu_log_stop = 3      !<
163
164    LOGICAL            ::  cpu_log_barrierwait = .FALSE.  !<
165    LOGICAL, PARAMETER ::  cpu_log_nowait = .FALSE.       !<
166
167    REAL(wp) ::  initial_wallclock_time  !<
168
169    TYPE logpoint
170       REAL(wp)           ::  isum       !<
171       REAL(wp)           ::  ivect      !<
172       REAL(wp)           ::  mean       !<
173       REAL(wp)           ::  mtime      !<
174       REAL(wp)           ::  mtimevec   !<
175       REAL(wp)           ::  sum        !<
176       REAL(wp)           ::  vector     !<
177       INTEGER(iwp)       ::  counts     !<
178       CHARACTER (LEN=25) ::  place      !<
179    END TYPE logpoint
180
181    TYPE(logpoint), DIMENSION(100) ::  log_point = logpoint( 0.0_wp, 0.0_wp,   &
182                                       0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, &
183                                       0, ' ' ),                               &
184                                       log_point_s = logpoint( 0.0_wp, 0.0_wp, &
185                                       0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, &
186                                       0, ' ' )
187
188    SAVE
189
190 CONTAINS
191
192!------------------------------------------------------------------------------!
193! Description:
194! ------------
195!> @todo Missing subroutine description.
196!------------------------------------------------------------------------------!
197    SUBROUTINE cpu_log( log_event, place, modus, barrierwait )
198
199       IMPLICIT NONE
200
201       CHARACTER (LEN=*) ::  modus              !<
202       CHARACTER (LEN=*) ::  place              !<
203       
204       LOGICAL           ::  wait_allowed       !<
205       LOGICAL, OPTIONAL ::  barrierwait        !<
206       LOGICAL, SAVE     ::  first = .TRUE.     !<
207       
208       REAL(wp)          ::  mtime = 0.0_wp     !<
209       REAL(wp)          ::  mtimevec = 0.0_wp  !<
210       TYPE(logpoint)    ::  log_event          !<
211
212       INTEGER(idp)     ::  count        !<
213       INTEGER(idp)     ::  count_rate   !<
214
215
216!
217!--    Initialize and check, respectively, point of measurement
218       IF ( log_event%place == ' ' )  THEN
219          log_event%place = place
220       ELSEIF ( log_event%place /= place )  THEN
221          WRITE( message_string, * ) 'wrong argument & expected: ',            &
222                            TRIM(log_event%place), '  given: ',  TRIM( place )
223          CALL message( 'cpu_log', 'PA0174', 1, 2, 0, 6, 0 )
224       ENDIF
225
226!
227!--    Determine, if barriers are allowed to set
228       IF ( PRESENT( barrierwait ) )  THEN
229          wait_allowed = barrierwait
230       ELSE
231          wait_allowed = .TRUE.
232       ENDIF
233
234!
235!--    MPI barrier, if requested, in order to avoid measuring wait times
236!--    caused by MPI routines waiting for other MPI routines of other
237!--    PEs that have not yet finished
238#if defined( __parallel )
239       IF ( cpu_log_barrierwait  .AND.  wait_allowed  .AND.                    &
240            ( modus == 'start'  .OR.  modus == 'continue' ) )  THEN
241          CALL MPI_BARRIER( comm2d, ierr )
242       ENDIF
243#endif
244
245!
246!--    Take current time
247       CALL SYSTEM_CLOCK( count, count_rate )
248       mtime = REAL( count, KIND=wp ) / REAL( count_rate, KIND=wp )
249
250!
251!--    Start, stop or pause measurement
252       IF ( modus == 'start'  .OR.  modus == 'continue' )  THEN
253          log_event%mtime    = mtime
254          log_event%mtimevec = mtimevec
255       ELSEIF ( modus == 'pause' )  THEN
256          IF ( ( mtime - log_event%mtime ) < 0.0  .AND.  first )  THEN
257             WRITE( message_string, * ) 'negative time interval occured',      &
258                         ' &PE',myid,' L=PAUSE "',TRIM(log_event%place),       &
259                         '" new=', mtime,' last=',log_event%mtime
260             CALL message( 'cpu_log', 'PA0176', 0, 1, -1, 6, 0 )
261             first = .FALSE.
262          ENDIF
263          log_event%isum     = log_event%isum + mtime - log_event%mtime
264          log_event%ivect    = log_event%ivect  + mtimevec - log_event%mtimevec
265       ELSEIF ( modus == 'stop' )  THEN
266          IF ( ( mtime - log_event%mtime + log_event%isum ) < 0.0  .AND.       &
267               first )  THEN
268             WRITE( message_string, * ) 'negative time interval occured',      &
269                       ' &PE',myid,' L=STOP "',TRIM(log_event%place),'" new=', &
270                       mtime,' last=',log_event%mtime,' isum=',log_event%isum
271             CALL message( 'cpu_log', 'PA0177', 0, 1, -1, 6, 0 )
272             first = .FALSE.
273          ENDIF
274          log_event%mtime    = mtime    - log_event%mtime    + log_event%isum
275          log_event%mtimevec = mtimevec - log_event%mtimevec + log_event%ivect
276          log_event%sum      = log_event%sum  + log_event%mtime
277          IF ( log_event%sum < 0.0  .AND.  first )  THEN
278             WRITE( message_string, * ) 'negative time interval occured',      &
279                       ' &PE',myid,' L=STOP "',TRIM(log_event%place),'" sum=', &
280                       log_event%sum,' mtime=',log_event%mtime
281             CALL message( 'cpu_log', 'PA0178', 0, 1, -1, 6, 0 )
282             first = .FALSE.
283          ENDIF
284          log_event%vector   = log_event%vector + log_event%mtimevec
285          log_event%counts   = log_event%counts + 1
286          log_event%isum     = 0.0_wp
287          log_event%ivect    = 0.0_wp
288       ELSE
289          message_string = 'unknown modus of time measurement: ' //            &
290                           TRIM( modus )
291          CALL message( 'cpu_log', 'PA0179', 0, 1, -1, 6, 0 )
292       ENDIF
293
294    END SUBROUTINE cpu_log
295
296
297!------------------------------------------------------------------------------!
298! Description:
299! ------------
300!> Analysis and output of the cpu-times measured. All PE results are collected
301!> on PE0 in order to calculate the mean cpu-time over all PEs and other
302!> statistics. The output is sorted according to the amount of cpu-time consumed
303!> and output on PE0.
304!------------------------------------------------------------------------------!
305 
306    SUBROUTINE cpu_statistics
307
308       IMPLICIT NONE
309
310       INTEGER(iwp)    ::  i               !<
311       INTEGER(iwp)    ::  ii(1)           !<
312       INTEGER(iwp)    ::  iii             !<
313       INTEGER(iwp)    ::  sender          !<
314       REAL(wp)       ::  average_cputime  !<
315       REAL(wp), SAVE ::  norm = 1.0_wp    !<
316       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  pe_max        !<
317       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  pe_min        !<
318       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  pe_rms        !<
319       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  sum           !<
320       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pe_log_points !<
321
322
323       CALL location_message( 'calculating cpu statistics', .FALSE. )
324
325!
326!--    Compute cpu-times in seconds
327       log_point%mtime  = log_point%mtime  / norm
328       log_point%sum    = log_point%sum    / norm
329       log_point%vector = log_point%vector / norm
330       WHERE ( log_point%counts /= 0 )
331          log_point%mean = log_point%sum / log_point%counts
332       END WHERE
333
334
335!
336!--    Collect cpu-times from all PEs and calculate statistics
337       IF ( myid == 0 )  THEN
338!
339!--       Allocate and initialize temporary arrays needed for statistics
340          ALLOCATE( pe_max( SIZE( log_point ) ), pe_min( SIZE( log_point ) ),  &
341                    pe_rms( SIZE( log_point ) ),                               &
342                    pe_log_points( SIZE( log_point ), 0:numprocs-1 ) )
343          pe_min = log_point%sum
344          pe_max = log_point%sum    ! need to be set in case of 1 PE
345          pe_rms = 0.0_wp
346
347#if defined( __parallel )
348!
349!--       Receive data from all PEs
350          DO  i = 1, numprocs-1
351             CALL MPI_RECV( pe_max(1), SIZE( log_point ), MPI_REAL,            &
352                            i, i, comm2d, status, ierr )
353             sender = status(MPI_SOURCE)
354             pe_log_points(:,sender) = pe_max
355          ENDDO
356          pe_log_points(:,0) = log_point%sum   ! Results from PE0
357!
358!--       Calculate mean of all PEs, store it on log_point%sum
359!--       and find minimum and maximum
360          DO  iii = 1, SIZE( log_point )
361             DO  i = 1, numprocs-1
362                log_point(iii)%sum = log_point(iii)%sum + pe_log_points(iii,i)
363                pe_min(iii) = MIN( pe_min(iii), pe_log_points(iii,i) )
364                pe_max(iii) = MAX( pe_max(iii), pe_log_points(iii,i) )
365             ENDDO
366             log_point(iii)%sum = log_point(iii)%sum / numprocs
367!
368!--          Calculate rms
369             DO  i = 0, numprocs-1
370                pe_rms(iii) = pe_rms(iii) + (                                  &
371                                    pe_log_points(iii,i) - log_point(iii)%sum  &
372                                            )**2
373             ENDDO
374             pe_rms(iii) = SQRT( pe_rms(iii) / numprocs )
375          ENDDO
376       ELSE
377!
378!--       Send data to PE0 (pe_max is used as temporary storage to send
379!--       the data in order to avoid sending the data type log)
380          ALLOCATE( pe_max( SIZE( log_point ) ) )
381          pe_max = log_point%sum
382          CALL MPI_SEND( pe_max(1), SIZE( log_point ), MPI_REAL, 0, myid,      &
383                         comm2d, ierr )
384#endif
385
386       ENDIF
387
388!
389!--    Write cpu-times
390       IF ( myid == 0 )  THEN
391!
392!--       Re-store sums
393          ALLOCATE( sum( SIZE( log_point ) ) )
394          WHERE ( log_point%counts /= 0 )
395             sum = log_point%sum
396          ELSEWHERE
397             sum = -1.0_wp
398          ENDWHERE
399
400!
401!--       Get total time in order to calculate CPU-time per gridpoint and
402!--       timestep
403          IF ( nr_timesteps_this_run /= 0 )  THEN
404             average_cputime = log_point(1)%sum / REAL( ngp_3d(0), KIND=wp ) / &
405                               REAL( nr_timesteps_this_run, KIND=wp ) * 1E6_wp
406                               ! in micro-sec
407          ELSE
408             average_cputime = -1.0_wp
409          ENDIF
410
411!
412!--       Write cpu-times sorted by size
413          CALL check_open( 18 )
414#if defined( __parallel )
415          WRITE ( 18, 100 )  TRIM( run_description_header ),                   &
416                             numprocs * threads_per_task, pdims(1), pdims(2),  &
417                             threads_per_task, nx+1, ny+1, nz,                 &
418                             nr_timesteps_this_run, average_cputime
419
420          WRITE ( 18, 110 )
421#else
422          WRITE ( 18, 100 )  TRIM( run_description_header ),                   &
423                             numprocs * threads_per_task, 1, 1,                &
424                             threads_per_task, nx+1, ny+1, nz,                 &
425                             nr_timesteps_this_run, average_cputime
426
427          WRITE ( 18, 110 )
428#endif
429          DO
430             ii = MAXLOC( sum )
431             i = ii(1)
432             IF ( sum(i) /= -1.0_wp )  THEN
433                WRITE ( 18, 102 ) &
434              log_point(i)%place, log_point(i)%sum,                            &
435                   log_point(i)%sum / log_point(1)%sum * 100.0_wp,             &
436                   log_point(i)%counts, pe_min(i), pe_max(i), pe_rms(i)
437                sum(i) = -1.0_wp
438             ELSE
439                EXIT
440             ENDIF
441          ENDDO
442       ENDIF
443
444
445!
446!--    The same procedure again for the individual measurements.
447!
448!--    Compute cpu-times in seconds
449       log_point_s%mtime  = log_point_s%mtime  / norm
450       log_point_s%sum    = log_point_s%sum    / norm
451       log_point_s%vector = log_point_s%vector / norm
452       WHERE ( log_point_s%counts /= 0 )
453          log_point_s%mean = log_point_s%sum / log_point_s%counts
454       END WHERE
455
456!
457!--    Collect cpu-times from all PEs and calculate statistics
458#if defined( __parallel )
459!
460!--    Set barrier in order to avoid that PE0 receives log_point_s-data
461!--    while still busy with receiving log_point-data (see above)
462       CALL MPI_BARRIER( comm2d, ierr )
463#endif
464       IF ( myid == 0 )  THEN
465!
466!--       Initialize temporary arrays needed for statistics
467          pe_min = log_point_s%sum
468          pe_max = log_point_s%sum    ! need to be set in case of 1 PE
469          pe_rms = 0.0_wp
470
471#if defined( __parallel )
472!
473!--       Receive data from all PEs
474          DO  i = 1, numprocs-1
475             CALL MPI_RECV( pe_max(1), SIZE( log_point ), MPI_REAL, &
476                            MPI_ANY_SOURCE, MPI_ANY_TAG, comm2d, status, ierr )
477             sender = status(MPI_SOURCE)
478             pe_log_points(:,sender) = pe_max
479          ENDDO
480          pe_log_points(:,0) = log_point_s%sum   ! Results from PE0
481!
482!--       Calculate mean of all PEs, store it on log_point_s%sum
483!--       and find minimum and maximum
484          DO  iii = 1, SIZE( log_point )
485             DO  i = 1, numprocs-1
486                log_point_s(iii)%sum = log_point_s(iii)%sum +                  &
487                                       pe_log_points(iii,i)
488                pe_min(iii) = MIN( pe_min(iii), pe_log_points(iii,i) )
489                pe_max(iii) = MAX( pe_max(iii), pe_log_points(iii,i) )
490             ENDDO
491             log_point_s(iii)%sum = log_point_s(iii)%sum / numprocs
492!
493!--          Calculate rms
494             DO  i = 0, numprocs-1
495                pe_rms(iii) = pe_rms(iii) + (                                  &
496                                   pe_log_points(iii,i) - log_point_s(iii)%sum &
497                                            )**2
498             ENDDO
499             pe_rms(iii) = SQRT( pe_rms(iii) / numprocs )
500          ENDDO
501       ELSE
502!
503!--       Send data to PE0 (pe_max is used as temporary storage to send
504!--       the data in order to avoid sending the data type log)
505          pe_max = log_point_s%sum
506          CALL MPI_SEND( pe_max(1), SIZE( log_point ), MPI_REAL, 0, 0, comm2d, &
507                         ierr )
508#endif
509
510       ENDIF
511
512!
513!--    Write cpu-times
514       IF ( myid == 0 )  THEN
515!
516!--       Re-store sums
517          WHERE ( log_point_s%counts /= 0 )
518             sum = log_point_s%sum
519          ELSEWHERE
520             sum = -1.0_wp
521          ENDWHERE
522
523!
524!--       Write cpu-times sorted by size
525          WRITE ( 18, 101 )
526          DO
527             ii = MAXLOC( sum )
528             i = ii(1)
529             IF ( sum(i) /= -1.0_wp )  THEN
530                WRITE ( 18, 102 )                                              &
531                   log_point_s(i)%place, log_point_s(i)%sum,                   &
532                   log_point_s(i)%sum / log_point(1)%sum * 100.0_wp,           &
533                   log_point_s(i)%counts, pe_min(i), pe_max(i), pe_rms(i)
534                sum(i) = -1.0_wp
535             ELSE
536                EXIT
537             ENDIF
538          ENDDO
539
540!
541!--       Output of handling of MPI operations
542          IF ( collective_wait )  THEN
543             WRITE ( 18, 103 )
544          ELSE
545             WRITE ( 18, 104 )
546          ENDIF
547          IF ( cpu_log_barrierwait )  WRITE ( 18, 111 )
548          IF ( synchronous_exchange )  THEN
549             WRITE ( 18, 105 )
550          ELSE
551             WRITE ( 18, 106 )
552          ENDIF
553
554!
555!--       Empty lines in order to create a gap to the results of the model
556!--       continuation runs
557          WRITE ( 18, 107 )
558
559!
560!--       Unit 18 is not needed anymore
561          CALL close_file( 18 )
562
563       ENDIF
564
565       CALL location_message( 'finished', .TRUE. )
566
567   100 FORMAT (A/11('-')//'CPU measures for ',I5,' PEs (',I5,'(x) * ',I5,'(y', &
568               &') tasks *',I5,' threads):'//                                  &
569               'gridpoints (x/y/z): ',20X,I5,' * ',I5,' * ',I5/                &
570               'nr of timesteps: ',22X,I6/                                     &
571               'cpu time per grid point and timestep: ',5X,F8.5,' * 10**-6 s')
572
573   101 FORMAT (/'special measures:'/ &
574               &'-----------------------------------------------------------', &
575               &'------------------------')
576
577   102 FORMAT (A25,2X,F9.3,2X,F7.2,1X,I7,3(1X,F9.3))
578   103 FORMAT (/'Barriers are set in front of collective operations')
579   104 FORMAT (/'No barriers are set in front of collective operations')
580   105 FORMAT (/'Exchange of ghostpoints via MPI_SENDRCV')
581   106 FORMAT (/'Exchange of ghostpoints via MPI_ISEND/MPI_IRECV')
582   107 FORMAT (//)
583   110 FORMAT ('-------------------------------------------------------------',     &
584               &'---------'//&
585               &'place:                              mean        counts      min  ',&
586               &'     max       rms'/ &
587               &'                                sec.      %                sec. ', &
588               &'     sec.      sec.'/  &
589               &'-----------------------------------------------------------',      &
590               &'------------------------')
591   111 FORMAT (/'Barriers are set at beginning (start/continue) of measurements')
592
593    END SUBROUTINE cpu_statistics
594
595 END MODULE cpulog
Note: See TracBrowser for help on using the repository browser.