Changeset 1327 for LMDZ4


Ignore:
Timestamp:
Mar 16, 2010, 11:23:17 AM (14 years ago)
Author:
yann meurdesoif
Message:

parallelisation COSP
YM

Location:
LMDZ4/trunk
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk/bld.cfg

    r1288 r1327  
    2222%LD_FLAGS          %BASE_LD %PARA_LD
    2323
    24 src::dyn    %SRC_PATH/%DYN
    25 src::phys   %SRC_PATH/%PHYS
     24src::dyn     %SRC_PATH/%DYN
     25src::phys    %SRC_PATH/%PHYS
    2626src::grid    %SRC_PATH/grid
    2727src::filtrez %SRC_PATH/filtrez
    2828src::bibio   %SRC_PATH/bibio
    29 src::cosp   %SRC_PATH/%COSP
     29src::cosp    %COSP
    3030
    3131bld::lib::dyn      %DYN
     
    3434bld::lib::filtrez   filtrez
    3535bld::lib::bibio     bibio
    36 bld::lib::cosp      %COSP
     36bld::lib::cosp      cosp
    3737
    3838
    3939bld::outfile_ext::exe    %SUFF_NAME.e
    40 bld::target              lib%{DYN}.a lib%{PHYS}.a libgrid.a libfiltrez.a libbibio.a
     40bld::target              lib%{DYN}.a lib%{PHYS}.a libgrid.a libfiltrez.a libbibio.a libcosp.a
    4141bld::target              %EXEC%SUFF_NAME.e
    42 bld::exe_dep             %{DYN} %{PHYS} grid filtrez bibio %{COSP}
     42bld::exe_dep             %{DYN} %{PHYS} grid filtrez bibio cosp
    4343
    4444
  • LMDZ4/trunk/libf/cosp/cosp.F90

    r1279 r1327  
    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.
  • LMDZ4/trunk/libf/cosp/ini_histdayCOSP.h

    r1279 r1327  
    55! sorties par jour
    66!
     7!$OMP MASTER
    78        zstoday = ecrit_day
    89        zout = freq_COSP
     
    191192
    192193        CALL histend(nid_day_cosp)
     194!$OMP END MASTER
     195!$OMP BARRIER
  • LMDZ4/trunk/libf/cosp/ini_histhfCOSP.h

    r1279 r1327  
    55! sorties par jour
    66!
     7!$OMP MASTER
    78        zstohf = ecrit_hf
    89        zout = freq_COSP
     
    191192
    192193        CALL histend(nid_hf_cosp)
     194!$OMP END MASTER
     195!$OMP BARRIER
  • LMDZ4/trunk/libf/cosp/ini_histmthCOSP.h

    r1279 r1327  
    55! sorties par jour
    66!
     7!$OMP MASTER
    78        zstomth = ecrit_mth
    89        zout = freq_COSP
     
    189190
    190191        CALL histend(nid_mth_cosp)
     192!$OMP END MASTER
     193!$OMP BARRIER
  • LMDZ4/trunk/libf/cosp/phys_cosp.F90

    r1279 r1327  
    7070  USE MOD_COSP
    7171  USE mod_phys_lmdz_para
     72  USE mod_grid_phy_lmdz
    7273  use ioipsl
    7374  use iophy
     
    7677
    7778  ! Local variables
    78   character(len=64)  :: cosp_input_nl='cosp_input_nl.txt'
    79   character(len=64)  :: cosp_output_nl='cosp_output_nl.txt'
     79  character(len=64),PARAMETER  :: cosp_input_nl='cosp_input_nl.txt'
     80  character(len=64),PARAMETER  :: cosp_output_nl='cosp_output_nl.txt'
    8081  character(len=512), save :: finput ! Input file name
    8182  character(len=512), save :: cmor_nl
     
    8485  integer,parameter :: Ncollmdz=20
    8586  integer, save :: Npoints      ! Number of gridpoints
     87!$OMP THREADPRIVATE(Npoints)
    8688  integer, save :: Nlevels      ! Number of levels
    8789  Integer :: Nptslmdz,Nlevlmdz ! Nb de points issus de physiq.F
     
    9092  integer :: i
    9193  type(cosp_config),save :: cfg   ! Configuration options
     94!$OMP THREADPRIVATE(cfg)
    9295  type(cosp_gridbox) :: gbx ! Gridbox information. Input for COSP
    9396  type(cosp_subgrid) :: sgx     ! Subgrid outputs
     
    103106  integer :: Nlon,Nlat,geomode
    104107  real,save :: radar_freq,k2,ZenAng,co2,ch4,n2o,co,emsfc_lw
     108!$OMP THREADPRIVATE(emsfc_lw)
    105109  integer,dimension(RTTOV_MAX_CHANNELS),save :: Channels
    106110  real,dimension(RTTOV_MAX_CHANNELS),save :: Surfem
     
    115119  integer :: nhori,nvert,nvertp,nvertisccp,nvertm,nvertcol
    116120  integer, save :: nid_day_cosp,nid_mth_cosp,nid_hf_cosp
     121!$OMP THREADPRIVATE(nid_day_cosp,nid_mth_cosp,nid_hf_cosp)
    117122  logical, save :: debut_cosp=.true.
     123!$OMP THREADPRIVATE(debut_cosp)
    118124  integer :: itau_wcosp
    119   character(len=10),dimension(Ncollmdz) :: chcol=(/'c01','c02','c03','c04','c05','c06','c07','c08','c09','c10', &
     125  character(len=10),dimension(Ncollmdz),parameter :: chcol=(/'c01','c02','c03','c04','c05','c06','c07','c08','c09','c10', &
    120126                                                   'c11','c12','c13','c14','c15','c16','c17','c18','c19','c20'/)
    121127  real,dimension(Ncollmdz) :: column_ax
    122128  integer, save :: Nlevout
     129!$OMP THREADPRIVATE(Nlevout)
    123130
    124131  include "dimensions.h"
     
    139146!
    140147   namelist/COSP_INPUT/cmor_nl,overlap,isccp_topheight,isccp_topheight_direction, &
    141               npoints,npoints_it,ncolumns,nlevels,use_vgrid,nlr,csat_vgrid,finput, &
     148              npoints_it,ncolumns,nlevels,use_vgrid,nlr,csat_vgrid,finput, &
    142149              radar_freq,surface_radar,use_mie_tables, &
    143150              use_gas_abs,do_ray,melt_lay,k2,Nprmts_max_hydro,Naero,Nprmts_max_aero, &
     
    154161
    155162 if (debut_cosp) then
     163  NPoints=Nptslmdz
    156164! Lecture du namelist input
    157   open(10,file=cosp_input_nl,status='old')
    158   read(10,nml=cosp_input)
    159   close(10)
     165  CALL read_cosp_input
     166
    160167! Clefs Outputs
    161168  call read_cosp_output_nl(cosp_output_nl,cfg)
    162169
    163     if ( (Ncollmdz.ne.Ncolumns).or.(Nptslmdz.ne.Npoints).or.(Nlevlmdz.ne.Nlevels) ) then
     170    if ( (Ncollmdz.ne.Ncolumns).or. (Nlevlmdz.ne.Nlevels) ) then
    164171       print*,'Nb points Horiz, Vert, Sub-col passes par physiq.F = ', &
    165172               Nptslmdz, Nlevlmdz, Ncollmdz
     
    169176       call abort
    170177    endif
    171 
     178   
    172179    if (overlaplmdz.ne.overlap) then
    173180       print*,'Attention overlaplmdz different de overlap lu dans namelist '
     
    194201        print *, 'Allocating memory for gridbox type...'
    195202
    196         call construct_cosp_gridbox(float(itap),radar_freq,surface_radar,use_mie_tables,use_gas_abs,do_ray,melt_lay,k2, &
     203        call construct_cosp_gridbox(dble(itap),radar_freq,surface_radar,use_mie_tables,use_gas_abs,do_ray,melt_lay,k2, &
    197204                                    Npoints,Nlevels,Ncolumns,N_HYDRO,Nprmts_max_hydro,Naero,Nprmts_max_aero,Npoints_it, &
    198205                                    lidar_ice_type,isccp_topheight,isccp_topheight_direction,overlap,emsfc_lw, &
     
    316323   
    317324        do ii=1,Ncolumns
    318           column_ax(ii) = float(ii)
     325          column_ax(ii) = real(ii)
    319326        enddo
    320327
     
    462469!  call system_clock(t1,count_rate,count_max)
    463470!  print *,(t1-t0)*1.0/count_rate
     471 
     472  CONTAINS
     473 
     474  SUBROUTINE read_cosp_input
    464475   
     476    IF (is_master) THEN
     477      OPEN(10,file=cosp_input_nl,status='old')
     478      READ(10,nml=cosp_input)
     479      CLOSE(10)
     480    ENDIF
     481    CALL bcast(cmor_nl)
     482    CALL bcast(overlap)
     483    CALL bcast(isccp_topheight)
     484    CALL bcast(isccp_topheight_direction)
     485    CALL bcast(npoints_it)
     486    CALL bcast(ncolumns)
     487    CALL bcast(nlevels)
     488    CALL bcast(use_vgrid)
     489    CALL bcast(nlr)
     490    CALL bcast(csat_vgrid)
     491    CALL bcast(finput)
     492    CALL bcast(radar_freq)
     493    CALL bcast(surface_radar)
     494    CALL bcast(use_mie_tables)
     495    CALL bcast(use_gas_abs)
     496    CALL bcast(do_ray)
     497    CALL bcast(melt_lay)
     498    CALL bcast(k2)
     499    CALL bcast(Nprmts_max_hydro)
     500    CALL bcast(Naero)
     501    CALL bcast(Nprmts_max_aero)
     502    CALL bcast(lidar_ice_type)
     503    CALL bcast(use_precipitation_fluxes)
     504    CALL bcast(use_reff)
     505    CALL bcast(platform)
     506    CALL bcast(satellite)
     507    CALL bcast(Instrument)
     508    CALL bcast(Nchannels)
     509    CALL bcast(Channels)
     510    CALL bcast(Surfem)
     511    CALL bcast(ZenAng)
     512    CALL bcast(co2)
     513    CALL bcast(ch4)
     514    CALL bcast(n2o)
     515    CALL bcast(co)
     516!$OMP BARRIER 
     517  END SUBROUTINE read_cosp_input
     518
    465519end subroutine phys_cosp
  • LMDZ4/trunk/libf/cosp/radar_simulator_types.F90

    r1279 r1327  
    4242  end type mie
    4343
    44   real*8, dimension(:), allocatable :: &
     44  real*8, dimension(:), save, allocatable :: &
    4545    mt_ttl, &                   ! liquid temperatures (C)
    4646    mt_tti, &                   ! ice temperatures (C)
    4747    mt_qext, mt_qbsca           ! extincion/backscatter efficiency
     48!$OMP THREADPRIVATE(mt_ttl,mt_tti,mt_qext, mt_qbsca)
    4849
    49   integer*4 :: &
     50  integer*4,save :: &
    5051    cnt_liq, &                  ! liquid temperature count
    5152    cnt_ice                     ! ice temperature count
     53!$OMP THREADPRIVATE(cnt_liq,cnt_ice)
    5254
    5355  end module radar_simulator_types
  • LMDZ4/trunk/libf/cosp/read_cosp_output_nl.F90

    r1279 r1327  
    55  USE MOD_COSP_CONSTANTS
    66  USE MOD_COSP_TYPES
     7  USE mod_phys_lmdz_para
    78  character(len=*),intent(in) :: cosp_nl
    89  type(cosp_config),intent(out) :: cfg
     
    1617             Llongitude,Llatitude,Lparasol_refl,LclMISR,Lmeantbisccp,Lmeantbclrisccp, &
    1718             Lfrac_out,Lbeta_mol532,Ltbrttov
     19
    1820  namelist/COSP_OUTPUT/Lradar_sim,Llidar_sim,Lisccp_sim,Lmisr_sim,Lrttov_sim, &
    1921             Lalbisccp,Latb532,Lboxptopisccp,Lboxtauisccp,Lcfad_dbze94, &
     
    2628    cfg%out_list(i)=''
    2729  enddo
    28   open(10,file=cosp_nl,status='old')
    29   read(10,nml=cosp_output)
    30   close(10)
     30 
     31  IF (is_master) THEN
     32    open(10,file=cosp_nl,status='old')
     33    read(10,nml=cosp_output)
     34    close(10)
     35  ENDIF
     36 
     37  CALL bcast(Lradar_sim)
     38  CALL bcast(Llidar_sim)
     39  CALL bcast(Lisccp_sim)
     40  CALL bcast(Lmisr_sim)
     41  CALL bcast(Lrttov_sim)
     42  CALL bcast(Lalbisccp)
     43  CALL bcast(Latb532)
     44  CALL bcast(Lboxptopisccp)
     45  CALL bcast(Lboxtauisccp)
     46  CALL bcast(Lcfad_dbze94)
     47  CALL bcast(Lcfad_lidarsr532)
     48  CALL bcast(Lclcalipso2)
     49  CALL bcast(Lclcalipso)
     50  CALL bcast(Lclhcalipso)
     51  CALL bcast(Lclisccp2)
     52  CALL bcast(Lcllcalipso)
     53  CALL bcast(Lclmcalipso)
     54  CALL bcast(Lcltcalipso)
     55  CALL bcast(Lcltlidarradar)
     56  CALL bcast(Lctpisccp)
     57  CALL bcast(Ldbze94)
     58  CALL bcast(Ltauisccp)
     59  CALL bcast(Ltclisccp)
     60  CALL bcast(Llongitude)
     61  CALL bcast(Llatitude)
     62  CALL bcast(Lparasol_refl)
     63  CALL bcast(LclMISR)
     64  CALL bcast(Lmeantbisccp)
     65  CALL bcast(Lmeantbclrisccp)
     66  CALL bcast(Lfrac_out)
     67  CALL bcast(Lbeta_mol532)
     68  CALL bcast(Ltbrttov)
     69!$OMP BARRIER
    3170
    3271!  print*,' Cles sorties cosp :'
  • LMDZ4/trunk/libf/cosp/scops.F

    r1279 r1327  
    3939! *****************************COPYRIGHT*******************************
    4040
     41      USE mod_phys_lmdz_para
     42      USE mod_grid_phy_lmdz
     43
    4144      implicit none
    4245
     
    175178          ELSE
    176179              DO ibox=1,ncol
    177                 include 'congvec.h'
     180!                include 'congvec_para.h'
     181                 include 'congvec.h'
    178182                ! select random pixels from the non-convective
    179183                ! part the gridbox ( some will be converted into
  • LMDZ4/trunk/libf/phylmd/mod_phys_lmdz_para.F90

    r1001 r1327  
    1010  LOGICAL,SAVE :: is_sequential
    1111  LOGICAL,SAVE :: is_parallel
     12  LOGICAL,SAVE :: is_master
    1213 
    13 !$OMP THREADPRIVATE(klon_loc)
     14!$OMP THREADPRIVATE(klon_loc,is_master)
    1415 
    1516CONTAINS
     
    2627    CALL Init_phys_lmdz_omp_data(klon_mpi)
    2728    klon_loc=klon_omp
     29    IF (is_mpi_root .AND. is_omp_root) THEN
     30       is_master=.TRUE.
     31     ELSE
     32       is_master=.FALSE.
     33     ENDIF
    2834    CALL Test_transfert
    2935!$OMP END PARALLEL   
     
    3541       is_parallel=.FALSE.
    3642     ENDIF
    37      
     43      
    3844  END SUBROUTINE Init_phys_lmdz_para
    3945
  • LMDZ4/trunk/makelmdz_fcm

    r1288 r1327  
    3333LIBOGCM=$LMDGCM/libo
    3434LIBFGCM=$LMDGCM/libf
     35COSP_PATH=$LMDGCM/.void_dir
    3536
    3637########################################################################
     
    168169rm -f .void_file
    169170echo > .void_file
     171rm -rf .void_dir
     172mkdir .void_dir
    170173rm -f arch.path
    171174ln -s arch/arch-${arch}.path ./arch.path
     
    248251then
    249252   CPP_KEY="$CPP_KEY CPP_COSP"
    250    INCLUDE="$INCLUDE -I$(LIBFGCM)/cosp"
     253   COSP_PATH="$LIBFGCM/cosp"
    251254#   LIB="${LIB} -l${LIBPREFIX}cosp"
    252255fi
     
    380383echo "%DYN           $DYN"           >> $config_fcm
    381384echo "%PHYS          phy${physique}" >> $config_fcm
    382 if [[ $cosp == "true" ]]
    383 then
    384 echo "%COSP          cosp"           >> $config_fcm
    385 fi
     385echo "%COSP          $COSP_PATH"     >> $config_fcm
    386386echo "%CPP_KEY       $CPP_KEY"       >> $config_fcm
    387387echo "%EXEC          $code"          >> $config_fcm
Note: See TracChangeset for help on using the changeset viewer.