source: palm/tags/release-3.8/SOURCE/init_particles.f90 @ 1320

Last change on this file since 1320 was 668, checked in by suehring, 13 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 22.2 KB
Line 
1 SUBROUTINE init_particles
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7! Former revisions:
8! -----------------
9! $Id: init_particles.f90 668 2010-12-23 13:22:58Z raasch $
10!
11! 667 2010-12-23 12:06:00Z suehring/gryschka
12! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng for allocation
13! of arrays.
14!
15! 622 2010-12-10 08:08:13Z raasch
16! optional barriers included in order to speed up collective operations
17!
18! 336 2009-06-10 11:19:35Z raasch
19! Maximum number of tails is calculated from maximum number of particles and
20! skip_particles_for_tail,
21! output of messages replaced by message handling routine
22! Bugfix: arrays for tails are allocated with a minimum size of 10 tails if
23! there is no tail initially
24!
25! 150 2008-02-29 08:19:58Z raasch
26! Setting offset_ocean_* needed for calculating vertical indices within ocean
27! runs
28!
29! 117 2007-10-11 03:27:59Z raasch
30! Sorting of particles only in case of cloud droplets
31!
32! 106 2007-08-16 14:30:26Z raasch
33! variable iran replaced by iran_part
34!
35! 82 2007-04-16 15:40:52Z raasch
36! Preprocessor directives for old systems removed
37!
38! 70 2007-03-18 23:46:30Z raasch
39! displacements for mpi_particle_type changed, age_m initialized,
40! particles-package is now part of the default code
41!
42! 16 2007-02-15 13:16:47Z raasch
43! Bugfix: MPI_REAL in MPI_ALLREDUCE replaced by MPI_INTEGER
44!
45! r4 | raasch | 2007-02-13 12:33:16 +0100 (Tue, 13 Feb 2007)
46! RCS Log replace by Id keyword, revision history cleaned up
47!
48! Revision 1.24  2007/02/11 13:00:17  raasch
49! Bugfix: allocation of tail_mask and new_tail_id in case of restart-runs
50! Bugfix: __ was missing in a cpp-directive
51!
52! Revision 1.1  1999/11/25 16:22:38  raasch
53! Initial revision
54!
55!
56! Description:
57! ------------
58! This routine initializes a set of particles and their attributes (position,
59! radius, ..). Advection of these particles is carried out by advec_particles,
60! plotting is done in data_output_dvrp.
61!------------------------------------------------------------------------------!
62
63    USE arrays_3d
64    USE control_parameters
65    USE dvrp_variables
66    USE grid_variables
67    USE indices
68    USE particle_attributes
69    USE pegrid
70    USE random_function_mod
71
72
73    IMPLICIT NONE
74
75    CHARACTER (LEN=10) ::  particle_binary_version, version_on_file
76
77    INTEGER ::  i, j, n, nn
78#if defined( __parallel )
79    INTEGER, DIMENSION(3) ::  blocklengths, displacements, types
80#endif
81    LOGICAL ::  uniform_particles_l
82    REAL    ::  factor, pos_x, pos_y, pos_z, value
83
84
85#if defined( __parallel )
86!
87!-- Define MPI derived datatype for FORTRAN datatype particle_type (see module
88!-- particle_attributes). Integer length is 4 byte, Real is 8 byte
89    blocklengths(1)  = 19;  blocklengths(2)  =   4;  blocklengths(3)  =   1
90    displacements(1) =  0;  displacements(2) = 152;  displacements(3) = 168
91
92    types(1) = MPI_REAL
93    types(2) = MPI_INTEGER
94    types(3) = MPI_UB
95    CALL MPI_TYPE_STRUCT( 3, blocklengths, displacements, types, &
96                          mpi_particle_type, ierr )
97    CALL MPI_TYPE_COMMIT( mpi_particle_type, ierr )
98#endif
99
100!
101!-- In case of oceans runs, the vertical index calculations need an offset,
102!-- because otherwise the k indices will become negative
103    IF ( ocean )  THEN
104       offset_ocean_nzt    = nzt
105       offset_ocean_nzt_m1 = nzt - 1
106    ENDIF
107
108
109!
110!-- Check the number of particle groups.
111    IF ( number_of_particle_groups > max_number_of_particle_groups )  THEN
112       WRITE( message_string, * ) 'max_number_of_particle_groups =',      &
113                                  max_number_of_particle_groups ,         &
114                                  '&number_of_particle_groups reset to ', &
115                                  max_number_of_particle_groups
116       CALL message( 'init_particles', 'PA0213', 0, 1, 0, 6, 0 )
117       number_of_particle_groups = max_number_of_particle_groups
118    ENDIF
119
120!
121!-- Set default start positions, if necessary
122    IF ( psl(1) == 9999999.9 )  psl(1) = -0.5 * dx
123    IF ( psr(1) == 9999999.9 )  psr(1) = ( nx + 0.5 ) * dx
124    IF ( pss(1) == 9999999.9 )  pss(1) = -0.5 * dy
125    IF ( psn(1) == 9999999.9 )  psn(1) = ( ny + 0.5 ) * dy
126    IF ( psb(1) == 9999999.9 )  psb(1) = zu(nz/2)
127    IF ( pst(1) == 9999999.9 )  pst(1) = psb(1)
128
129    IF ( pdx(1) == 9999999.9  .OR.  pdx(1) == 0.0 )  pdx(1) = dx
130    IF ( pdy(1) == 9999999.9  .OR.  pdy(1) == 0.0 )  pdy(1) = dy
131    IF ( pdz(1) == 9999999.9  .OR.  pdz(1) == 0.0 )  pdz(1) = zu(2) - zu(1)
132
133    DO  j = 2, number_of_particle_groups
134       IF ( psl(j) == 9999999.9 )  psl(j) = psl(j-1)
135       IF ( psr(j) == 9999999.9 )  psr(j) = psr(j-1)
136       IF ( pss(j) == 9999999.9 )  pss(j) = pss(j-1)
137       IF ( psn(j) == 9999999.9 )  psn(j) = psn(j-1)
138       IF ( psb(j) == 9999999.9 )  psb(j) = psb(j-1)
139       IF ( pst(j) == 9999999.9 )  pst(j) = pst(j-1)
140       IF ( pdx(j) == 9999999.9  .OR.  pdx(j) == 0.0 )  pdx(j) = pdx(j-1)
141       IF ( pdy(j) == 9999999.9  .OR.  pdy(j) == 0.0 )  pdy(j) = pdy(j-1)
142       IF ( pdz(j) == 9999999.9  .OR.  pdz(j) == 0.0 )  pdz(j) = pdz(j-1)
143    ENDDO
144
145!
146!-- For the first model run of a possible job chain initialize the
147!-- particles, otherwise read the particle data from file.
148    IF ( TRIM( initializing_actions ) == 'read_restart_data'  &
149         .AND.  read_particles_from_restartfile )  THEN
150
151!
152!--    Read particle data from previous model run.
153!--    First open the input unit.
154       IF ( myid_char == '' )  THEN
155          OPEN ( 90, FILE='PARTICLE_RESTART_DATA_IN'//myid_char, &
156                     FORM='UNFORMATTED' )
157       ELSE
158          OPEN ( 90, FILE='PARTICLE_RESTART_DATA_IN/'//myid_char, &
159                     FORM='UNFORMATTED' )
160       ENDIF
161
162!
163!--    First compare the version numbers
164       READ ( 90 )  version_on_file
165       particle_binary_version = '3.0'
166       IF ( TRIM( version_on_file ) /= TRIM( particle_binary_version ) )  THEN
167          message_string = 'version mismatch concerning data from prior ' // &
168                           'run &version on file    = "' //                  &
169                                         TRIM( version_on_file ) //          &
170                           '&version in program = "' //                      &
171                                         TRIM( particle_binary_version ) // '"'
172          CALL message( 'init_particles', 'PA0214', 1, 2, 0, 6, 0 )
173       ENDIF
174
175!
176!--    Read some particle parameters and the size of the particle arrays,
177!--    allocate them and read their contents.
178       READ ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,                  &
179                    maximum_number_of_particles, maximum_number_of_tailpoints, &
180                    maximum_number_of_tails, number_of_initial_particles,      &
181                    number_of_particles, number_of_particle_groups,            &
182                    number_of_tails, particle_groups, time_prel,               &
183                    time_write_particle_data, uniform_particles
184
185       IF ( number_of_initial_particles /= 0 )  THEN
186          ALLOCATE( initial_particles(1:number_of_initial_particles) )
187          READ ( 90 )  initial_particles
188       ENDIF
189
190       ALLOCATE( prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg),       &
191                 prt_start_index(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
192                 particle_mask(maximum_number_of_particles),         &
193                 particles(maximum_number_of_particles) )
194
195       READ ( 90 )  prt_count, prt_start_index
196       READ ( 90 )  particles
197
198       IF ( use_particle_tails )  THEN
199          ALLOCATE( particle_tail_coordinates(maximum_number_of_tailpoints,5, &
200                    maximum_number_of_tails),                                 &
201                    new_tail_id(maximum_number_of_tails),                     &
202                    tail_mask(maximum_number_of_tails) )
203          READ ( 90 )  particle_tail_coordinates
204       ENDIF
205
206       CLOSE ( 90 )
207
208    ELSE
209
210!
211!--    Allocate particle arrays and set attributes of the initial set of
212!--    particles, which can be also periodically released at later times.
213!--    Also allocate array for particle tail coordinates, if needed.
214       ALLOCATE( prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg),       &
215                 prt_start_index(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
216                 particle_mask(maximum_number_of_particles),         &
217                 particles(maximum_number_of_particles) )
218
219!
220!--    Initialize all particles with dummy values (otherwise errors may
221!--    occur within restart runs). The reason for this is still not clear
222!--    and may be presumably caused by errors in the respective user-interface.
223       particles = particle_type( 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
224                                  0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
225                                  0.0, 0, 0, 0, 0 )
226       particle_groups = particle_groups_type( 0.0, 0.0, 0.0, 0.0 )
227
228!
229!--    Set the default particle size used for dvrp plots
230       IF ( dvrp_psize == 9999999.9 )  dvrp_psize = 0.2 * dx
231
232!
233!--    Set values for the density ratio and radius for all particle
234!--    groups, if necessary
235       IF ( density_ratio(1) == 9999999.9 )  density_ratio(1) = 0.0
236       IF ( radius(1)        == 9999999.9 )  radius(1) = 0.0
237       DO  i = 2, number_of_particle_groups
238          IF ( density_ratio(i) == 9999999.9 )  THEN
239             density_ratio(i) = density_ratio(i-1)
240          ENDIF
241          IF ( radius(i) == 9999999.9 )  radius(i) = radius(i-1)
242       ENDDO
243
244       DO  i = 1, number_of_particle_groups
245          IF ( density_ratio(i) /= 0.0  .AND.  radius(i) == 0 )  THEN
246             WRITE( message_string, * ) 'particle group #', i, 'has a', &
247                                        'density ratio /= 0 but radius = 0'
248             CALL message( 'init_particles', 'PA0215', 1, 2, 0, 6, 0 )
249          ENDIF
250          particle_groups(i)%density_ratio = density_ratio(i)
251          particle_groups(i)%radius        = radius(i)
252       ENDDO
253
254!
255!--    Calculate particle positions and store particle attributes, if
256!--    particle is situated on this PE
257       n = 0
258
259       DO  i = 1, number_of_particle_groups
260
261          pos_z = psb(i)
262
263          DO WHILE ( pos_z <= pst(i) )
264
265             pos_y = pss(i)
266
267             DO WHILE ( pos_y <= psn(i) )
268
269                IF ( pos_y >= ( nys - 0.5 ) * dy  .AND.  &
270                     pos_y <  ( nyn + 0.5 ) * dy )  THEN
271
272                   pos_x = psl(i)
273
274                   DO WHILE ( pos_x <= psr(i) )
275
276                      IF ( pos_x >= ( nxl - 0.5 ) * dx  .AND.  &
277                           pos_x <  ( nxr + 0.5 ) * dx )  THEN
278
279                         DO  j = 1, particles_per_point
280
281                            n = n + 1
282                            IF ( n > maximum_number_of_particles )  THEN
283                               WRITE( message_string, * ) 'number of initial', &
284                                      'particles (', n, ') exceeds',           &
285                                      '&maximum_number_of_particles (',        &
286                                      maximum_number_of_particles, ') on PE ', &
287                                             myid
288                               CALL message( 'init_particles', 'PA0216', &
289                                                                 2, 2, -1, 6, 1 )
290                            ENDIF
291                            particles(n)%x             = pos_x
292                            particles(n)%y             = pos_y
293                            particles(n)%z             = pos_z
294                            particles(n)%age           = 0.0
295                            particles(n)%age_m         = 0.0
296                            particles(n)%dt_sum        = 0.0
297                            particles(n)%dvrp_psize    = dvrp_psize
298                            particles(n)%e_m           = 0.0
299                            particles(n)%speed_x       = 0.0
300                            particles(n)%speed_x_sgs   = 0.0
301                            particles(n)%speed_y       = 0.0
302                            particles(n)%speed_y_sgs   = 0.0
303                            particles(n)%speed_z       = 0.0
304                            particles(n)%speed_z_sgs   = 0.0
305                            particles(n)%origin_x      = pos_x
306                            particles(n)%origin_y      = pos_y
307                            particles(n)%origin_z      = pos_z
308                            particles(n)%radius      = particle_groups(i)%radius
309                            particles(n)%weight_factor =initial_weighting_factor
310                            particles(n)%color         = 1
311                            particles(n)%group         = i
312                            particles(n)%tailpoints    = 0
313                            IF ( use_particle_tails  .AND. &
314                                 MOD( n, skip_particles_for_tail ) == 0 )  THEN
315                               number_of_tails         = number_of_tails + 1
316!
317!--                            This is a temporary provisional setting (see
318!--                            further below!)
319                               particles(n)%tail_id    = number_of_tails
320                            ELSE
321                               particles(n)%tail_id    = 0
322                            ENDIF
323
324                         ENDDO
325
326                      ENDIF
327
328                      pos_x = pos_x + pdx(i)
329
330                   ENDDO
331
332                ENDIF
333
334                pos_y = pos_y + pdy(i)
335
336             ENDDO
337
338             pos_z = pos_z + pdz(i)
339
340          ENDDO
341
342       ENDDO
343
344       number_of_initial_particles = n
345       number_of_particles         = n
346
347!
348!--    Calculate the number of particles and tails of the total domain
349#if defined( __parallel )
350       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
351       CALL MPI_ALLREDUCE( number_of_particles, total_number_of_particles, 1, &
352                           MPI_INTEGER, MPI_SUM, comm2d, ierr )
353       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
354       CALL MPI_ALLREDUCE( number_of_tails, total_number_of_tails, 1, &
355                           MPI_INTEGER, MPI_SUM, comm2d, ierr )
356#else
357       total_number_of_particles = number_of_particles
358       total_number_of_tails     = number_of_tails
359#endif
360
361!
362!--    Set a seed value for the random number generator to be exclusively
363!--    used for the particle code. The generated random numbers should be
364!--    different on the different PEs.
365       iran_part = iran_part + myid
366
367!
368!--    User modification of initial particles
369       CALL user_init_particles
370
371!
372!--    Store the initial set of particles for release at later times
373       IF ( number_of_initial_particles /= 0 )  THEN
374          ALLOCATE( initial_particles(1:number_of_initial_particles) )
375          initial_particles(1:number_of_initial_particles) = &
376                                        particles(1:number_of_initial_particles)
377       ENDIF
378
379!
380!--    Add random fluctuation to particle positions
381       IF ( random_start_position )  THEN
382
383          DO  n = 1, number_of_initial_particles
384             IF ( psl(particles(n)%group) /= psr(particles(n)%group) )  THEN
385                particles(n)%x = particles(n)%x + &
386                                 ( random_function( iran_part ) - 0.5 ) * &
387                                 pdx(particles(n)%group)
388                IF ( particles(n)%x  <=  ( nxl - 0.5 ) * dx )  THEN
389                   particles(n)%x = ( nxl - 0.4999999999 ) * dx
390                ELSEIF ( particles(n)%x  >=  ( nxr + 0.5 ) * dx )  THEN
391                   particles(n)%x = ( nxr + 0.4999999999 ) * dx
392                ENDIF
393             ENDIF
394             IF ( pss(particles(n)%group) /= psn(particles(n)%group) )  THEN
395                particles(n)%y = particles(n)%y + &
396                                 ( random_function( iran_part ) - 0.5 ) * &
397                                 pdy(particles(n)%group)
398                IF ( particles(n)%y  <=  ( nys - 0.5 ) * dy )  THEN
399                   particles(n)%y = ( nys - 0.4999999999 ) * dy
400                ELSEIF ( particles(n)%y  >=  ( nyn + 0.5 ) * dy )  THEN
401                   particles(n)%y = ( nyn + 0.4999999999 ) * dy
402                ENDIF
403             ENDIF
404             IF ( psb(particles(n)%group) /= pst(particles(n)%group) )  THEN
405                particles(n)%z = particles(n)%z + &
406                                 ( random_function( iran_part ) - 0.5 ) * &
407                                 pdz(particles(n)%group)
408             ENDIF
409          ENDDO
410       ENDIF
411
412!
413!--    Sort particles in the sequence the gridboxes are stored in the memory.
414!--    Only required if cloud droplets are used.
415       IF ( cloud_droplets )  CALL sort_particles
416
417!
418!--    Open file for statistical informations about particle conditions
419       IF ( write_particle_statistics )  THEN
420          CALL check_open( 80 )
421          WRITE ( 80, 8000 )  current_timestep_number, simulated_time, &
422                              number_of_initial_particles,             &
423                              maximum_number_of_particles
424          CALL close_file( 80 )
425       ENDIF
426
427!
428!--    Check if particles are really uniform in color and radius (dvrp_size)
429!--    (uniform_particles is preset TRUE)
430       IF ( uniform_particles )  THEN
431          IF ( number_of_initial_particles == 0 )  THEN
432             uniform_particles_l = .TRUE.
433          ELSE
434             n = number_of_initial_particles
435             IF ( MINVAL( particles(1:n)%dvrp_psize  ) ==     &
436                  MAXVAL( particles(1:n)%dvrp_psize  )  .AND. &
437                  MINVAL( particles(1:n)%color ) ==     &
438                  MAXVAL( particles(1:n)%color ) )  THEN
439                uniform_particles_l = .TRUE.
440             ELSE
441                uniform_particles_l = .FALSE.
442             ENDIF
443          ENDIF
444
445#if defined( __parallel )
446          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
447          CALL MPI_ALLREDUCE( uniform_particles_l, uniform_particles, 1, &
448                              MPI_LOGICAL, MPI_LAND, comm2d, ierr )
449#else
450          uniform_particles = uniform_particles_l
451#endif
452
453       ENDIF
454
455!
456!--    Particles will probably become none-uniform, if their size and color
457!--    will be determined by flow variables
458       IF ( particle_color /= 'none'  .OR.  particle_dvrpsize /= 'none' )  THEN
459          uniform_particles = .FALSE.
460       ENDIF
461
462!
463!--    Set the beginning of the particle tails and their age
464       IF ( use_particle_tails )  THEN
465!
466!--       Choose the maximum number of tails with respect to the maximum number
467!--       of particles and skip_particles_for_tail
468          maximum_number_of_tails = maximum_number_of_particles / &
469                                    skip_particles_for_tail
470
471!
472!--       Create a minimum number of tails in case that there is no tail
473!--       initially (otherwise, index errors will occur when adressing the
474!--       arrays below)
475          IF ( maximum_number_of_tails == 0 )  maximum_number_of_tails = 10
476
477          ALLOCATE( particle_tail_coordinates(maximum_number_of_tailpoints,5, &
478                    maximum_number_of_tails),                                 &
479                    new_tail_id(maximum_number_of_tails),                     &
480                    tail_mask(maximum_number_of_tails) )
481
482          particle_tail_coordinates  = 0.0
483          minimum_tailpoint_distance = minimum_tailpoint_distance**2
484          number_of_initial_tails    = number_of_tails
485
486          nn = 0
487          DO  n = 1, number_of_particles
488!
489!--          Only for those particles marked above with a provisional tail_id
490!--          tails will be created. Particles now get their final tail_id.
491             IF ( particles(n)%tail_id /= 0 )  THEN
492
493                nn = nn + 1
494                particles(n)%tail_id = nn
495
496                particle_tail_coordinates(1,1,nn) = particles(n)%x
497                particle_tail_coordinates(1,2,nn) = particles(n)%y
498                particle_tail_coordinates(1,3,nn) = particles(n)%z
499                particle_tail_coordinates(1,4,nn) = particles(n)%color
500                particles(n)%tailpoints = 1
501                IF ( minimum_tailpoint_distance /= 0.0 )  THEN
502                   particle_tail_coordinates(2,1,nn) = particles(n)%x
503                   particle_tail_coordinates(2,2,nn) = particles(n)%y
504                   particle_tail_coordinates(2,3,nn) = particles(n)%z
505                   particle_tail_coordinates(2,4,nn) = particles(n)%color
506                   particle_tail_coordinates(1:2,5,nn) = 0.0
507                   particles(n)%tailpoints = 2
508                ENDIF
509
510             ENDIF
511          ENDDO
512       ENDIF
513
514!
515!--    Plot initial positions of particles (only if particle advection is
516!--    switched on from the beginning of the simulation (t=0))
517       IF ( particle_advection_start == 0.0 )  CALL data_output_dvrp
518
519    ENDIF
520
521!
522!-- Check boundary condition and set internal variables
523    SELECT CASE ( bc_par_b )
524   
525       CASE ( 'absorb' )
526          ibc_par_b = 1
527
528       CASE ( 'reflect' )
529          ibc_par_b = 2
530         
531       CASE DEFAULT
532          WRITE( message_string, * )  'unknown boundary condition ',   &
533                                       'bc_par_b = "', TRIM( bc_par_b ), '"'
534          CALL message( 'init_particles', 'PA0217', 1, 2, 0, 6, 0 )
535         
536    END SELECT
537    SELECT CASE ( bc_par_t )
538   
539       CASE ( 'absorb' )
540          ibc_par_t = 1
541
542       CASE ( 'reflect' )
543          ibc_par_t = 2
544         
545       CASE DEFAULT
546          WRITE( message_string, * ) 'unknown boundary condition ',   &
547                                     'bc_par_t = "', TRIM( bc_par_t ), '"'
548          CALL message( 'init_particles', 'PA0218', 1, 2, 0, 6, 0 )
549         
550    END SELECT
551    SELECT CASE ( bc_par_lr )
552
553       CASE ( 'cyclic' )
554          ibc_par_lr = 0
555
556       CASE ( 'absorb' )
557          ibc_par_lr = 1
558
559       CASE ( 'reflect' )
560          ibc_par_lr = 2
561         
562       CASE DEFAULT
563          WRITE( message_string, * ) 'unknown boundary condition ',   &
564                                     'bc_par_lr = "', TRIM( bc_par_lr ), '"'
565          CALL message( 'init_particles', 'PA0219', 1, 2, 0, 6, 0 )
566         
567    END SELECT
568    SELECT CASE ( bc_par_ns )
569
570       CASE ( 'cyclic' )
571          ibc_par_ns = 0
572
573       CASE ( 'absorb' )
574          ibc_par_ns = 1
575
576       CASE ( 'reflect' )
577          ibc_par_ns = 2
578         
579       CASE DEFAULT
580          WRITE( message_string, * ) 'unknown boundary condition ',   &
581                                     'bc_par_ns = "', TRIM( bc_par_ns ), '"'
582          CALL message( 'init_particles', 'PA0220', 1, 2, 0, 6, 0 )
583         
584    END SELECT
585!
586!-- Formats
5878000 FORMAT (I6,1X,F7.2,4X,I6,71X,I6)
588
589 END SUBROUTINE init_particles
Note: See TracBrowser for help on using the repository browser.