Changeset 3895


Ignore:
Timestamp:
Jan 25, 2016, 10:47:14 AM (9 years ago)
Author:
ymipsl
Message:

Make LMDZ5 be compliant to generate initiale state and compute in openMP mode suing unstructured grid.

YM

Location:
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/climoz_mod.f90

    r3867 r3895  
    1515  USE mod_grid_phy_lmdz, ONLY :  grid_type, unstructured
    1616  USE regr_lat_time_climoz_m
     17  USE mod_phys_lmdz_para
    1718  USE XIOS
    1819  IMPLICIT NONE
     
    2324   
    2425      IF(read_climoz>=1) THEN
    25         CALL regr_lat_time_climoz(read_climoz,.FALSE.)
    26         CALL xios_set_field_attr( "tro3_reg",  enabled=.TRUE.)
    27         CALL xios_set_field_attr( "tro3_read", enabled=.TRUE.)
    28         IF (read_climoz==2) THEN
    29           CALL xios_set_field_attr( "tro3_daylight_reg",  enabled=.TRUE.)
    30           CALL xios_set_field_attr( "tro3_daylight_read", enabled=.TRUE.)
     26        IF (is_master) CALL regr_lat_time_climoz(read_climoz,.FALSE.)
     27        IF (is_omp_master) THEN
     28          CALL xios_set_field_attr( "tro3_reg",  enabled=.TRUE.)
     29          CALL xios_set_field_attr( "tro3_read", enabled=.TRUE.)
     30          IF (read_climoz==2) THEN
     31            CALL xios_set_field_attr( "tro3_daylight_reg",  enabled=.TRUE.)
     32            CALL xios_set_field_attr( "tro3_daylight_read", enabled=.TRUE.)
     33          ENDIF
    3134        ENDIF
    3235      ENDIF
     
    4043  SUBROUTINE get_ozone_var(name,press_in_edg,paprs,v3)
    4144  USE dimphy
     45  USE mod_phys_lmdz_para
    4246  USE xios
    4347  USE regr1_step_av_m, only: regr1_step_av
     
    4852    REAL, INTENT(OUT):: v3(:, :, :) ! (klon, klev, size(name))
    4953   
    50     REAL  :: v1(klon, size(press_in_edg) - 1, size(name))
     54    REAL  :: v1_mpi(klon_mpi, size(press_in_edg) - 1, size(v3,3))
     55    REAL  :: v1(klon, size(press_in_edg) - 1, size(v3,3))
    5156    INTEGER :: m,i
    5257   
    5358    DO m=1,size(name)
    54       CALL xios_recv_field(name(m),v1(:,:,m))
    55    
     59      IF (is_omp_master) CALL xios_recv_field(name(m),v1_mpi(:,:,m))
     60      CALL scatter_omp(v1_mpi,v1)
    5661      ! Regrid in pressure at each horizontal position:
    5762      DO i = 1, klon
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/conf_phys_m.F90

    r3831 r3895  
    204204    LOGICAL,SAVE      :: carbon_cycle_tr_omp
    205205    LOGICAL,SAVE      :: carbon_cycle_cpl_omp
    206 
     206    INTEGER,SAVE      :: read_climoz_omp
     207 
    207208    integer, intent(out):: read_climoz ! read ozone climatology, OpenMP shared
    208209    ! Allowed values are 0, 1 and 2
     
    18461847    !
    18471848    read_climoz = 0 ! default value
    1848     call getin('read_climoz', read_climoz)
     1849    call getin('read_climoz', read_climoz_omp)
    18491850
    18501851    carbon_cycle_tr_omp=.FALSE.
     
    20692070    callstats = callstats_omp
    20702071    ecrit_LES = ecrit_LES_omp
     2072    read_climoz = read_climoz_omp
    20712073    carbon_cycle_tr = carbon_cycle_tr_omp
    20722074    carbon_cycle_cpl = carbon_cycle_cpl_omp
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/create_etat0_limit_unstruct.f90

    r3867 r3895  
    3434        ENDDO
    3535       
    36         CALL xios_set_axis_attr("time_year",n_glo=ndays,value=value)
     36        IF (is_omp_master) CALL xios_set_axis_attr("time_year",n_glo=ndays,value=value)
    3737       
    3838        IF (iflag_phys<100) THEN
    3939
    4040          IF (create_etat0_limit) THEN
    41             CALL xios_set_fieldgroup_attr("etat0_limit_read",read_access=.TRUE.,enabled=.TRUE.)
    42             CALL xios_set_filegroup_attr("etat0_limit_read",enabled=.TRUE.)
     41            IF (is_omp_master) CALL xios_set_fieldgroup_attr("etat0_limit_read",read_access=.TRUE.,enabled=.TRUE.)
     42            IF (is_omp_master) CALL xios_set_filegroup_attr("etat0_limit_read",enabled=.TRUE.)
     43            IF (is_omp_master) CALL xios_set_file_attr("limit_write",enabled=.TRUE.)
    4344          ENDIF
    4445     
     
    5758  USE ioipsl, ONLY : getin
    5859  USE dimphy
     60  USE xios
    5961  IMPLICIT NONE
    6062      INTEGER :: iflag_phys
     
    6971              CALL create_etat0_unstruct
    7072              CALL create_limit_unstruct
     73              IF (is_omp_master) CALL xios_context_finalize()
     74!$OMP BARRIER
    7175              CALL abort_physic ('create_etat0_limit_unstruct','Initial state file are created, all is fine' ,1)
    7276          ENDIF
     
    7478          IF (create_etat0_limit) THEN
    7579            CALL iniaqua(klon,iflag_phys)
     80            IF (is_omp_master) CALL xios_context_finalize()
     81!$OMP BARRIER
    7682            CALL abort_physic ('create_etat0_limit_unstruct','Initial state file are created, all is fine' ,1)
    7783          ENDIF
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/create_etat0_unstruct.f90

    r3867 r3895  
    1616  USE phys_state_var_mod
    1717  USE indice_sol_mod
     18  USE mod_phys_lmdz_para
    1819  IMPLICIT NONE
    1920  INCLUDE 'dimsoil.h'
     
    2930    REAL,    DIMENSION(klon,nbsrf)           :: qsolsrf, snsrf
    3031    REAL,    DIMENSION(klon,nsoilmx,nbsrf)   :: tsoil
     32   
     33    REAL,    DIMENSION(klon_mpi)             :: tsol_mpi, qsol_mpi, zmasq_mpi, lic_mpi
     34
    3135    INTEGER :: ji,j,i
    3236 
    33     CALL xios_recv_field("ts",tsol)
    34     CALL xios_recv_field("qs",qsol)
    35     CALL xios_recv_field("mask",zmasq)
    36     CALL xios_recv_field("landice",lic)
    37 
     37    IF (is_omp_master) THEN
     38      CALL xios_recv_field("ts",tsol_mpi)
     39      CALL xios_recv_field("qs",qsol_mpi)
     40      CALL xios_recv_field("mask",zmasq_mpi)
     41      CALL xios_recv_field("landice",lic_mpi)
     42    ENDIF
     43    CALL scatter_omp(tsol_mpi,tsol)
     44    CALL scatter_omp(qsol_mpi,qsol)
     45    CALL scatter_omp(zmasq_mpi,zmasq)
     46    CALL scatter_omp(lic_mpi,lic)
     47   
    3848    rads(:)   = 0.0
    3949    rugmer(:) = 0.001
     
    7181    pctsrf(:,is_oce)=(1.-zmasq(:))
    7282    WHERE(pctsrf(:,is_oce)<EPSFRA) pctsrf(:,is_oce)=0.
     83
     84!! WARNING    DON'T FORGET FOR LATER
    7385!!ym  IF(couple) pctsrf(:,is_oce)=ocemask_fi(:)
    74 
    75     CALL xios_send_field("check_ts",tsol)
    76     CALL xios_send_field("check_qs",qsol)
    77     CALL xios_send_field("check_zmasq",zmasq)
    78     CALL xios_send_field("check_pctsrf1",pctsrf(:,1))
    79     CALL xios_send_field("check_pctsrf2",pctsrf(:,2))
    80     CALL xios_send_field("check_pctsrf3",pctsrf(:,3))
    81     CALL xios_send_field("check_pctsrf4",pctsrf(:,4))
     86!!
    8287   
    8388! Init: tsol, qsol, sn, evap, tsoil, rain_fall, snow_fall, solsw, sollw, frugs
     
    9196    END DO
    9297!albedo SB >>>
    93     falb_dir(:,is_ter,:)=0.08; falb_dir(:,is_lic,:)=0.6
    94     falb_dir(:,is_oce,:)=0.5;  falb_dir(:,is_sic,:)=0.6
     98!ym error : the sub surface dimension is the third not second
     99!    falb_dir(:,is_ter,:)=0.08; falb_dir(:,is_lic,:)=0.6
     100!    falb_dir(:,is_oce,:)=0.5;  falb_dir(:,is_sic,:)=0.6
     101    falb_dir(:,:,is_ter)=0.08; falb_dir(:,:,is_lic)=0.6
     102    falb_dir(:,:,is_oce)=0.5;  falb_dir(:,:,is_sic)=0.6
     103
     104!ym falb_dif has been forgotten, initialize with defaukt value found in phyetat0 or 0 ?
     105!ym probably the uninitialized value was 0 for standard (regular grid) case
     106    falb_dif(:,:,:)=0
     107
    95108!albedo SB <<<
    96109    fevap(:,:) = 0.
     
    112125
    113126    z0m(:,is_oce) = rugmer(:)
    114     z0m(:,is_ter) = MAX(1.0e-05,zstd(:)*zsig(:)/2.0)
    115     z0m(:,is_lic) = MAX(1.0e-05,zstd(:)*zsig(:)/2.0)
     127
     128!ym for now, no orography parametrization for gravity wave
     129!   z0m(:,is_ter) = MAX(1.0e-05,zstd(:)*zsig(:)/2.0)
     130!   z0m(:,is_lic) = MAX(1.0e-05,zstd(:)*zsig(:)/2.0)
     131    z0m(:,is_ter) = 1.0e-05
     132    z0m(:,is_lic) = 1.0e-05
     133
    116134    z0m(:,is_sic) = 0.001
    117135    z0h(:,:)=z0m(:,:)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/create_limit_unstruct.f90

    r3867 r3895  
    1414  USE indice_sol_mod
    1515  USE phys_state_var_mod
     16  USE mod_phys_lmdz_para
    1617  IMPLICIT NONE
    1718    INCLUDE "iniprint.h"
     
    2021    REAL,    DIMENSION(klon,lmdep)                 :: rugos
    2122    REAL,    DIMENSION(klon,lmdep)                 :: albedo
     23    REAL,    DIMENSION(klon_mpi,lmdep)             :: sic_mpi
     24    REAL,    DIMENSION(klon_mpi,lmdep)             :: sst_mpi
     25    REAL,    DIMENSION(klon_mpi,lmdep)             :: rugos_mpi
     26    REAL,    DIMENSION(klon_mpi,lmdep)             :: albedo_mpi
    2227    INTEGER                                        :: ndays
    2328    REAL                                           :: fi_ice(klon)
     
    2833    REAL, ALLOCATABLE                              :: pctsrf_t(:,:,:)
    2934    REAL, ALLOCATABLE                              :: phy_bil(:,:)
     35    REAL, ALLOCATABLE                              :: sst_year_mpi(:,:)
     36    REAL, ALLOCATABLE                              :: rugos_year_mpi(:,:)
     37    REAL, ALLOCATABLE                              :: albedo_year_mpi(:,:)
     38    REAL, ALLOCATABLE                              :: pctsrf_t_mpi(:,:,:)
     39    REAL, ALLOCATABLE                              :: phy_bil_mpi(:,:)
    3040    INTEGER :: l,k
    3141    INTEGER :: nbad
    3242   
    3343    ndays=ioget_year_len(annee_ref)
    34     CALL xios_recv_field("sic_limit",sic)
    35     CALL xios_recv_field("sst_limit",sst)
    36     CALL xios_recv_field("rugos_limit",rugos)
    37     CALL xios_recv_field("albedo_limit",albedo)
    38  
     44   
     45    IF (is_omp_master) THEN
     46      CALL xios_recv_field("sic_limit",sic_mpi)
     47      CALL xios_recv_field("sst_limit",sst_mpi)
     48      CALL xios_recv_field("rugos_limit",rugos_mpi)
     49      CALL xios_recv_field("albedo_limit",albedo_mpi)
     50    ENDIF
     51    CALL scatter_omp(sic_mpi,sic)
     52    CALL scatter_omp(sst_mpi,sst)
     53    CALL scatter_omp(rugos_mpi,rugos)
     54    CALL scatter_omp(albedo_mpi,albedo)
     55   
    3956    ALLOCATE(sic_year(klon,ndays))
    4057    ALLOCATE(sst_year(klon,ndays))
    4158    ALLOCATE(rugos_year(klon,ndays))
    4259    ALLOCATE(albedo_year(klon,ndays))
     60    ALLOCATE(pctsrf_t(klon,nbsrf,ndays))
     61    ALLOCATE(phy_bil(klon,ndays)); phy_bil=0.0
    4362
    4463! sic
     
    6281
    6382
    64     ALLOCATE(pctsrf_t(klon,nbsrf,ndays))
    6583    DO k=1,ndays
    6684      fi_ice=sic_year(:,k)
     
    99117    END DO
    100118   
    101     ALLOCATE(phy_bil(klon,ndays)); phy_bil=0.0
    102 
    103     CALL xios_send_field("foce_limout",pctsrf_t(:,is_oce,:))
    104     CALL xios_send_field("fsic_limout",pctsrf_t(:,is_sic,:))
    105     CALL xios_send_field("fter_limout",pctsrf_t(:,is_ter,:))
    106     CALL xios_send_field("flic_limout",pctsrf_t(:,is_lic,:))
    107     CALL xios_send_field("sst_limout", sst_year)
    108     CALL xios_send_field("bils_limout",phy_bil)
    109     CALL xios_send_field("alb_limout",albedo_year)
    110     CALL xios_send_field("rug_limout",rugos_year)
     119    ALLOCATE(sst_year_mpi(klon_mpi,ndays))
     120    ALLOCATE(rugos_year_mpi(klon_mpi,ndays))
     121    ALLOCATE(albedo_year_mpi(klon_mpi,ndays))
     122    ALLOCATE(pctsrf_t_mpi(klon_mpi,nbsrf,ndays))
     123    ALLOCATE(phy_bil_mpi(klon_mpi,ndays))
     124   
     125    CALL gather_omp(pctsrf_t   , pctsrf_t_mpi)
     126    CALL gather_omp(sst_year   , sst_year_mpi)
     127    CALL gather_omp(phy_bil    , phy_bil_mpi)
     128    CALL gather_omp(albedo_year, albedo_year_mpi)
     129    CALL gather_omp(rugos_year , rugos_year_mpi)
     130
     131    IF (is_omp_master) THEN
     132      CALL xios_send_field("foce_limout",pctsrf_t_mpi(:,is_oce,:))
     133      CALL xios_send_field("fsic_limout",pctsrf_t_mpi(:,is_sic,:))
     134      CALL xios_send_field("fter_limout",pctsrf_t_mpi(:,is_ter,:))
     135      CALL xios_send_field("flic_limout",pctsrf_t_mpi(:,is_lic,:))
     136      CALL xios_send_field("sst_limout", sst_year_mpi)
     137      CALL xios_send_field("bils_limout",phy_bil_mpi)
     138      CALL xios_send_field("alb_limout", albedo_year_mpi)
     139      CALL xios_send_field("rug_limout", rugos_year_mpi)
     140    ENDIF
    111141     
    112142  END SUBROUTINE create_limit_unstruct
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/limit_read_mod.F90

    r3871 r3895  
    3535  USE mod_grid_phy_lmdz
    3636  USE surface_data
     37  USE mod_phys_lmdz_para
    3738  USE XIOS
    3839  IMPLICIT NONE
     
    4243    IF ( type_ocean /= 'couple') THEN
    4344      IF (grid_type==unstructured) THEN
    44         CALL xios_set_file_attr("limit_read",enabled=.TRUE.,record_offset=first_day)
     45        IF (is_omp_master) CALL xios_set_file_attr("limit_read",enabled=.TRUE.,record_offset=first_day)
    4546      ENDIF 
    4647    ENDIF
     
    110111!****************************************************************************************
    111112
    112 IF (type_ocean == 'couple'.OR. &
     113    IF (type_ocean == 'couple'.OR. &
    113114         (type_ocean == 'slab' .AND. version_ocean == 'sicINT')) THEN
    114115       ! limit.nc has not yet been read. Do it now!
     
    243244      IF (grid_type==unstructured) THEN
    244245
    245 !$OMP MASTER  ! Only master thread
    246 
    247246
    248247        IF ( type_ocean /= 'couple') THEN
    249248
    250            CALL xios_recv_field("foce_limin",pct_mpi(:,is_oce))
    251            CALL xios_recv_field("fsic_limin",pct_mpi(:,is_sic))
     249           IF (is_omp_master) CALL xios_recv_field("foce_limin",pct_mpi(:,is_oce))
     250           IF (is_omp_master) CALL xios_recv_field("fsic_limin",pct_mpi(:,is_sic))
    252251  !         IF (read_continents .OR. itime == 1) THEN
    253              CALL xios_recv_field("fter_limin",pct_mpi(:,is_ter))
    254              CALL xios_recv_field("flic_limin",pct_mpi(:,is_lic))
     252           IF (is_omp_master) CALL xios_recv_field("fter_limin",pct_mpi(:,is_ter))
     253           IF (is_omp_master) CALL xios_recv_field("flic_limin",pct_mpi(:,is_lic))
    255254  !         ENDIF
    256255         ENDIF! type_ocean /= couple
    257256         
    258257         IF ( type_ocean /= 'couple') THEN                   
    259              CALL xios_recv_field("sst_limin",sst_mpi)
     258             IF (is_omp_master) CALL xios_recv_field("sst_limin",sst_mpi)
    260259         ENDIF
    261260       
    262261         IF (.NOT. ok_veget) THEN
    263            CALL xios_recv_field("alb_limin",alb_mpi)
    264            CALL xios_recv_field("rug_limin",rug_mpi)
     262           IF (is_omp_master) CALL xios_recv_field("alb_limin",alb_mpi)
     263           IF (is_omp_master) CALL xios_recv_field("rug_limin",rug_mpi)
    265264         ENDIF
    266265
     
    280279       END IF
    281280
    282 !$OMP END MASTER
    283281
    284282 
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/open_climoz_m.F90

    r3809 r3895  
    1818    use netcdf95, only: nf95_open, nf95_close, nf95_gw_var, nf95_inq_varid
    1919    use netcdf, only: nf90_nowrite
    20 
    21     use mod_phys_lmdz_mpi_data, only: is_mpi_root
    22     use mod_phys_lmdz_mpi_transfert, only: bcast_mpi ! broadcast
     20    use mod_phys_lmdz_para, only : is_master, bcast
    2321
    2422    integer, intent(out):: ncid ! of "climoz_LMDZ.nc", OpenMP shared
     
    4139
    4240    print *, "Call sequence information: open_climoz"
    43 
    44     if (is_mpi_root) then
     41    if (is_master) then
    4542       call nf95_open("climoz_LMDZ.nc", nf90_nowrite, ncid)
    4643
     
    5047       plev = plev * 100.
    5148       n_plev = size(plev)
    52     end if
    53 
    54     call bcast_mpi(n_plev)
    55     if (.not. is_mpi_root) allocate(plev(n_plev))
    56     call bcast_mpi(plev)
    57    
    58     ! Compute edges of pressure intervals:
    59     allocate(press_in_edg(n_plev + 1))
    60     if (is_mpi_root) then
     49     endif
     50     CALL bcast(n_plev)
     51     ALLOCATE(press_in_edg(n_plev + 1))
     52     if (is_master) THEN
    6153       press_in_edg(1) = 0.
    6254       ! We choose edges halfway in logarithm:
     
    6557       ! (infinity, but any value guaranteed to be greater than the
    6658       ! surface pressure would do)
    67     end if
    68     call bcast_mpi(press_in_edg)
    69     deallocate(plev) ! pointer
     59       deallocate(plev) ! pointer
     60     endif
     61     call bcast(press_in_edg)
    7062
    7163  end subroutine open_climoz
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phyaqua_mod.F90

    r3867 r3895  
    3232    USE mod_phys_lmdz_para, ONLY: is_master
    3333    USE mod_phys_lmdz_transfert_para, ONLY: bcast
     34    USE mod_grid_phy_lmdz
    3435    IMPLICIT NONE
    3536
     
    235236    CALL profil_sst(nlon, latitude, type_profil, phy_sst)
    236237
    237     CALL writelim_unstruct(klon, phy_nat, phy_alb, phy_sst, phy_bil, phy_rug, phy_ice, &
    238       phy_fter, phy_foce, phy_flic, phy_fsic)
    239 
     238    IF (grid_type==unstructured) THEN
     239      CALL writelim_unstruct(klon, phy_nat, phy_alb, phy_sst, phy_bil, phy_rug, phy_ice, &
     240                             phy_fter, phy_foce, phy_flic, phy_fsic)
     241    ELSE
     242     
     243       CALL writelim(klon, phy_nat, phy_alb, phy_sst, phy_bil, phy_rug, phy_ice, &
     244                     phy_fter, phy_foce, phy_flic, phy_fsic)
     245    ENDIF
    240246
    241247    ! ---------------------------------------------------------------------
     
    477483    REAL, INTENT (IN) :: phy_fsic(klon, 360)
    478484
    479     REAL :: phy_glo(klon_mpi, 360) ! temporary variable, to store phy_***(:)
     485    REAL :: phy_mpi(klon_mpi, 360) ! temporary variable, to store phy_***(:)
    480486      ! on the whole physics grid
    481487 
     
    483489    PRINT *, 'writelim: Ecriture du fichier limit'
    484490
    485     CALL gather_omp(phy_foce, phy_glo)
    486     IF (is_omp_master) CALL xios_send_field('foce_limout',phy_glo)
    487 
    488     CALL gather_omp(phy_fsic, phy_glo)
    489     IF (is_omp_master) CALL xios_send_field('fsic_limout',phy_glo)
     491    CALL gather_omp(phy_foce, phy_mpi)
     492    IF (is_omp_master) CALL xios_send_field('foce_limout',phy_mpi)
     493
     494    CALL gather_omp(phy_fsic, phy_mpi)
     495    IF (is_omp_master) CALL xios_send_field('fsic_limout',phy_mpi)
    490496     
    491     CALL gather_omp(phy_fter, phy_glo)
    492     IF (is_omp_master) CALL xios_send_field('fter_limout',phy_glo)
     497    CALL gather_omp(phy_fter, phy_mpi)
     498    IF (is_omp_master) CALL xios_send_field('fter_limout',phy_mpi)
    493499     
    494     CALL gather_omp(phy_flic, phy_glo)
    495     IF (is_omp_master) CALL xios_send_field('flic_limout',phy_glo)
    496 
    497     CALL gather_omp(phy_sst, phy_glo)
    498     IF (is_omp_master) CALL xios_send_field('sst_limout',phy_glo)
    499 
    500     CALL gather_omp(phy_bil, phy_glo)
    501     IF (is_omp_master) CALL xios_send_field('bils_limout',phy_glo)
    502 
    503     CALL gather_omp(phy_alb, phy_glo)
    504     IF (is_omp_master) CALL xios_send_field('alb_limout',phy_glo)
    505 
    506     CALL gather_omp(phy_rug, phy_glo)
    507     IF (is_omp_master) CALL xios_send_field('rug_limout',phy_glo)
     500    CALL gather_omp(phy_flic, phy_mpi)
     501    IF (is_omp_master) CALL xios_send_field('flic_limout',phy_mpi)
     502
     503    CALL gather_omp(phy_sst, phy_mpi)
     504    IF (is_omp_master) CALL xios_send_field('sst_limout',phy_mpi)
     505
     506    CALL gather_omp(phy_bil, phy_mpi)
     507    IF (is_omp_master) CALL xios_send_field('bils_limout',phy_mpi)
     508
     509    CALL gather_omp(phy_alb, phy_mpi)
     510    IF (is_omp_master) CALL xios_send_field('alb_limout',phy_mpi)
     511
     512    CALL gather_omp(phy_rug, phy_mpi)
     513    IF (is_omp_master) CALL xios_send_field('rug_limout',phy_mpi)
    508514
    509515  END SUBROUTINE writelim_unstruct
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_cal_mod.F90

    r3867 r3895  
    3737  SUBROUTINE phys_cal_init(annee_ref,day_ref)
    3838  USE IOIPSL, ONLY:  ymds2ju, getin, ioconf_calendar
    39   USE mod_phys_lmdz_para, ONLY:  is_master,bcast
     39  USE mod_phys_lmdz_para, ONLY:  is_master,is_omp_master,bcast
    4040  IMPLICIT NONE
    4141    INTEGER,INTENT(IN) :: annee_ref
     
    5252    CALL bcast(calend)
    5353
    54     IF (calend == 'earth_360d') THEN
    55       CALL ioconf_calendar('360d')
    56     ELSE IF (calend == 'earth_365d') THEN
    57       CALL ioconf_calendar('noleap')
    58     ELSE IF (calend == 'earth_366d') THEN
    59       CALL ioconf_calendar('gregorian')
    60     ELSE
    61       CALL abort_physic('phys_cal_init','Mauvais choix de calendrier',1)
     54    IF (is_omp_master) THEN
     55      IF (calend == 'earth_360d') THEN
     56        CALL ioconf_calendar('360d')
     57      ELSE IF (calend == 'earth_365d') THEN
     58        CALL ioconf_calendar('noleap')
     59      ELSE IF (calend == 'earth_366d') THEN
     60        CALL ioconf_calendar('gregorian')
     61      ELSE
     62        CALL abort_physic('phys_cal_init','Mauvais choix de calendrier',1)
     63      ENDIF
    6264    ENDIF
    63 
    6465
    6566    CALL ymds2ju(annee_ref, 1, day_ref, 0., jD_ref)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/physiq.F90

    r3881 r3895  
    788788
    789789  integer, save::  read_climoz ! read ozone climatology
     790!$OMP THREADPRIVATE(read_climoz)
    790791  !     (let it keep the default OpenMP shared attribute)
    791792  !     Allowed values are 0, 1 and 2
     
    796797
    797798  integer, save:: ncid_climoz ! NetCDF file containing ozone climatologies
     799!$OMP THREADPRIVATE(ncid_climoz)
    798800  !     (let it keep the default OpenMP shared attribute)
    799801
    800802  real, pointer, save:: press_climoz(:)
     803!$OMP THREADPRIVATE(press_climoz)
    801804  !     (let it keep the default OpenMP shared attribute)
    802805  !     edges of pressure intervals for ozone climatologies, in Pa, in strictly
     
    870873!albedo SB >>>
    871874  real,dimension(6),save :: SFRWL
     875!$OMP THREADPRIVATE(SFRWL)
    872876!albedo SB <<<
    873877
     
    881885  mydebug=.FALSE.
    882886  CALL set_timestep(pdtphys_)
    883   IF (.NOT. debut) CALL xios_update_calendar(itap+1)
     887  IF (.NOT. debut .AND. is_omp_master) CALL xios_update_calendar(itap+1)
    884888  !======================================================================
    885889  ! Ecriture eventuelle d'un profil verticale en entree de la physique.
     
    11191123                             flag_aerosol, flag_aerosol_strat, ok_cdnc)
    11201124
    1121      CALL xios_update_calendar(1)   
     1125     IF (is_omp_master) CALL xios_update_calendar(1)   
    11221126
    11231127     CALL create_etat0_limit_unstruct
     
    13491353     call iniradia(klon,klev,paprs(1,1:klev+1))
    13501354
    1351      !$omp single
    13521355     if (read_climoz >= 1) then
    13531356        call open_climoz(ncid_climoz, press_climoz)
    13541357     END IF
    1355      !$omp end single
    13561358     !
    13571359     !IM betaCRF
     
    16631665
    16641666          IF (grid_type==unstructured) THEN
    1665             CALL get_ozone_var((/"tro3_read","tro3_daylight_read"/),press_climoz,paprs,wo)
     1667            CALL get_ozone_var((/"tro3_read         ","tro3_daylight_read"/),press_climoz,paprs,wo)
    16661668          ELSE
    16671669            CALL regr_pr_av(ncid_climoz, (/"tro3         ", "tro3_daylight"/), &
     
    42744276     !         write(97) u_seri,v_seri,t_seri,q_seri
    42754277     !         close(97)
    4276      !$OMP MASTER
    42774278     if (read_climoz >= 1) then
    4278         if (is_mpi_root) then
    4279            call nf95_close(ncid_climoz)
    4280         end if
     4279        if (is_mpi_root) call nf95_close(ncid_climoz)
    42814280        deallocate(press_climoz) ! pointer
    42824281     end if
    4283      !$OMP END MASTER
    42844282  ENDIF
    42854283
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_lat_time_climoz_m.F90

    r3867 r3895  
    304304
    305305    allocate(o3_out(n_lat_out, n_plev, 360, read_climoz))
    306     IF (regr_lat) THEN
     306    IF (regr_lat_) THEN
    307307      allocate(o3_regr_lat(nbp_lat, n_plev, 0:13, read_climoz))
    308308
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_pr_av_m.F90

    r3819 r3895  
    4646
    4747    integer, intent(in):: ncid ! NetCDF ID of the file
     48
     49!ym   character(len=*), intent(in):: name(:) ! of the NetCDF variables
     50!ym  for strange reason, ifort doens't detect correctly the array size (return 0)
     51!ym   compilator bug , version dependent ?
     52
    4853    character(len=*), intent(in):: name(:) ! of the NetCDF variables
    4954    integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
     
    6671    integer varid, ncerr ! for NetCDF
    6772
    68     real  v1(nbp_lon, nbp_lat, size(press_in_edg) - 1, size(name))
     73    real  v1(nbp_lon, nbp_lat, size(press_in_edg) - 1, size(v3,3))
    6974    ! input fields at day "julien", on the global "dynamics" horizontal grid
    7075    ! First dimension is for longitude.
     
    7479    ! NetCDF variable "name(l)".
    7580
    76     real v2(klon, size(press_in_edg) - 1, size(name))
     81    real v2(klon, size(press_in_edg) - 1, size(v3,3))
    7782    ! fields scattered to the partial "physics" horizontal grid
    7883    ! "v2(i, k, l)" is at longitude "xlon(i)", latitude "xlat(i)",
     
    8590
    8691    call assert(size(v3, 1) == klon, size(v3, 2) == klev, "regr_pr_av v3 klon")
    87     n_var = assert_eq(size(name), size(v3, 3), "regr_pr_av v3 n_var")
     92    PRINT *,'size name',size(name)
     93!ym    n_var = assert_eq(size(name), size(v3, 3), "regr_pr_av v3 n_var")
     94!ym intel bugs compiler : ifort doesn't detect correcte size of nme (return 0)
     95
     96    n_var = size(v3, 3)
     97
    8898    call assert(shape(paprs) == (/klon, klev+1/), "regr_pr_av paprs")
    8999
Note: See TracChangeset for help on using the changeset viewer.