Ignore:
Timestamp:
Feb 23, 2010, 9:12:08 PM (14 years ago)
Author:
yann meurdesoif
Message:

YM : Parallelisation COSP MPI+OpenMP

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/cosp/cosp.F90

    r1279 r1318  
    2626  USE MOD_COSP_TYPES
    2727  USE MOD_COSP_SIMULATOR
     28  USE mod_phys_lmdz_para
     29  USE mod_grid_phy_lmdz
    2830  IMPLICIT NONE
    2931
     
    6163  real :: minv,maxv
    6264  real :: maxp,minp
    63   integer,dimension(:),allocatable :: & ! Dimensions nPoints
     65  integer,dimension(:),save,  allocatable :: & ! Dimensions nPoints
    6466                  seed    !  It is recommended that the seed is set to a different value for each model
    6567                          !  gridbox it is called on, as it is possible that the choice of the same
    6668                          !  seed value every time may introduce some statistical bias in the results,
    6769                          !  particularly for low values of NCOL.
     70!$OMP THREADPRIVATE(seed)
     71  real,dimension(:),allocatable :: rseed    !  It is recommended that the seed is set to a different value for each model
    6872  ! Types used in one iteration
    6973  type(cosp_gridbox) :: gbx_it
     
    7680  type(cosp_radarstats) :: stradar_it
    7781  type(cosp_lidarstats) :: stlidar_it
     82 
     83  logical,save :: first_cosp=.TRUE.
     84!$OMP THREADPRIVATE(first_cosp)
    7885 
    7986  !++++++++++ Dimensions ++++++++++++
     
    162169  endif
    163170
    164  
     171  if (first_cosp) then 
    165172   ! We base the seed in the decimal part of the surface pressure.
    166    allocate(seed(Npoints))
    167    seed = int(gbx%psfc) ! This is to avoid division by zero when Npoints = 1   
     173     allocate(seed(Npoints))
     174
     175     allocate(rseed(klon_glo))
     176     CALL gather(gbx%psfc,rseed)
     177     call bcast(rseed)
     178!   seed = int(gbx%psfc) ! This is to avoid division by zero when Npoints = 1   
    168179      ! Roj Oct/2008 ... Note: seed value of 0 caused me some problems + I want to
    169180      ! randomize for each call to COSP even when Npoints ==1
    170    minp = minval(gbx%psfc)
    171    maxp = maxval(gbx%psfc)
    172    if (Npoints .gt. 1) seed=int((gbx%psfc-minp)/(maxp-minp)*100000) + 1
    173 
    174  
     181     minp = minval(rseed)
     182     maxp = maxval(rseed)
     183   
     184     if (Npoints .gt. 1) THEN
     185       seed=int((gbx%psfc-minp)/(maxp-minp)*100000) + 1
     186     else
     187       seed=int(gbx%psfc-minp)
     188     endif
     189
     190     deallocate(rseed)
     191     first_cosp=.false.
     192   endif
     193   
    175194   if (gbx%Npoints_it >= gbx%Npoints) then ! One iteration gbx%Npoints
    176195        call cosp_iter(overlap,seed,cfg,vgrid,gbx,sgx,sgradar,sglidar,isccp,misr,stradar,stlidar)
     
    273292        call free_cosp_lidarstats(stlidar_it)
    274293   endif
    275    deallocate(seed)
    276294
    277295   
     
    305323  integer :: i,j,k
    306324  real,dimension(:,:),pointer :: column_frac_out ! Array with one column of frac_out
    307   integer :: scops_debug=0    !  set to non-zero value to print out inputs for debugging in SCOPS
     325  integer,parameter :: scops_debug=0    !  set to non-zero value to print out inputs for debugging in SCOPS
     326 
    308327  real,dimension(:, :),allocatable :: cca_scops,ls_p_rate,cv_p_rate, &
    309328                     tca_scops ! Cloud cover in each model level (HORIZONTAL gridbox fraction) of total cloud.
Note: See TracChangeset for help on using the changeset viewer.