Changeset 3895
- Timestamp:
- Jan 25, 2016, 10:47:14 AM (9 years ago)
- 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 15 15 USE mod_grid_phy_lmdz, ONLY : grid_type, unstructured 16 16 USE regr_lat_time_climoz_m 17 USE mod_phys_lmdz_para 17 18 USE XIOS 18 19 IMPLICIT NONE … … 23 24 24 25 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 31 34 ENDIF 32 35 ENDIF … … 40 43 SUBROUTINE get_ozone_var(name,press_in_edg,paprs,v3) 41 44 USE dimphy 45 USE mod_phys_lmdz_para 42 46 USE xios 43 47 USE regr1_step_av_m, only: regr1_step_av … … 48 52 REAL, INTENT(OUT):: v3(:, :, :) ! (klon, klev, size(name)) 49 53 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)) 51 56 INTEGER :: m,i 52 57 53 58 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) 56 61 ! Regrid in pressure at each horizontal position: 57 62 DO i = 1, klon -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/conf_phys_m.F90
r3831 r3895 204 204 LOGICAL,SAVE :: carbon_cycle_tr_omp 205 205 LOGICAL,SAVE :: carbon_cycle_cpl_omp 206 206 INTEGER,SAVE :: read_climoz_omp 207 207 208 integer, intent(out):: read_climoz ! read ozone climatology, OpenMP shared 208 209 ! Allowed values are 0, 1 and 2 … … 1846 1847 ! 1847 1848 read_climoz = 0 ! default value 1848 call getin('read_climoz', read_climoz )1849 call getin('read_climoz', read_climoz_omp) 1849 1850 1850 1851 carbon_cycle_tr_omp=.FALSE. … … 2069 2070 callstats = callstats_omp 2070 2071 ecrit_LES = ecrit_LES_omp 2072 read_climoz = read_climoz_omp 2071 2073 carbon_cycle_tr = carbon_cycle_tr_omp 2072 2074 carbon_cycle_cpl = carbon_cycle_cpl_omp -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/create_etat0_limit_unstruct.f90
r3867 r3895 34 34 ENDDO 35 35 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) 37 37 38 38 IF (iflag_phys<100) THEN 39 39 40 40 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.) 43 44 ENDIF 44 45 … … 57 58 USE ioipsl, ONLY : getin 58 59 USE dimphy 60 USE xios 59 61 IMPLICIT NONE 60 62 INTEGER :: iflag_phys … … 69 71 CALL create_etat0_unstruct 70 72 CALL create_limit_unstruct 73 IF (is_omp_master) CALL xios_context_finalize() 74 !$OMP BARRIER 71 75 CALL abort_physic ('create_etat0_limit_unstruct','Initial state file are created, all is fine' ,1) 72 76 ENDIF … … 74 78 IF (create_etat0_limit) THEN 75 79 CALL iniaqua(klon,iflag_phys) 80 IF (is_omp_master) CALL xios_context_finalize() 81 !$OMP BARRIER 76 82 CALL abort_physic ('create_etat0_limit_unstruct','Initial state file are created, all is fine' ,1) 77 83 ENDIF -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/create_etat0_unstruct.f90
r3867 r3895 16 16 USE phys_state_var_mod 17 17 USE indice_sol_mod 18 USE mod_phys_lmdz_para 18 19 IMPLICIT NONE 19 20 INCLUDE 'dimsoil.h' … … 29 30 REAL, DIMENSION(klon,nbsrf) :: qsolsrf, snsrf 30 31 REAL, DIMENSION(klon,nsoilmx,nbsrf) :: tsoil 32 33 REAL, DIMENSION(klon_mpi) :: tsol_mpi, qsol_mpi, zmasq_mpi, lic_mpi 34 31 35 INTEGER :: ji,j,i 32 36 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 38 48 rads(:) = 0.0 39 49 rugmer(:) = 0.001 … … 71 81 pctsrf(:,is_oce)=(1.-zmasq(:)) 72 82 WHERE(pctsrf(:,is_oce)<EPSFRA) pctsrf(:,is_oce)=0. 83 84 !! WARNING DON'T FORGET FOR LATER 73 85 !!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 !! 82 87 83 88 ! Init: tsol, qsol, sn, evap, tsoil, rain_fall, snow_fall, solsw, sollw, frugs … … 91 96 END DO 92 97 !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 95 108 !albedo SB <<< 96 109 fevap(:,:) = 0. … … 112 125 113 126 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 116 134 z0m(:,is_sic) = 0.001 117 135 z0h(:,:)=z0m(:,:) -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/create_limit_unstruct.f90
r3867 r3895 14 14 USE indice_sol_mod 15 15 USE phys_state_var_mod 16 USE mod_phys_lmdz_para 16 17 IMPLICIT NONE 17 18 INCLUDE "iniprint.h" … … 20 21 REAL, DIMENSION(klon,lmdep) :: rugos 21 22 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 22 27 INTEGER :: ndays 23 28 REAL :: fi_ice(klon) … … 28 33 REAL, ALLOCATABLE :: pctsrf_t(:,:,:) 29 34 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(:,:) 30 40 INTEGER :: l,k 31 41 INTEGER :: nbad 32 42 33 43 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 39 56 ALLOCATE(sic_year(klon,ndays)) 40 57 ALLOCATE(sst_year(klon,ndays)) 41 58 ALLOCATE(rugos_year(klon,ndays)) 42 59 ALLOCATE(albedo_year(klon,ndays)) 60 ALLOCATE(pctsrf_t(klon,nbsrf,ndays)) 61 ALLOCATE(phy_bil(klon,ndays)); phy_bil=0.0 43 62 44 63 ! sic … … 62 81 63 82 64 ALLOCATE(pctsrf_t(klon,nbsrf,ndays))65 83 DO k=1,ndays 66 84 fi_ice=sic_year(:,k) … … 99 117 END DO 100 118 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 111 141 112 142 END SUBROUTINE create_limit_unstruct -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/limit_read_mod.F90
r3871 r3895 35 35 USE mod_grid_phy_lmdz 36 36 USE surface_data 37 USE mod_phys_lmdz_para 37 38 USE XIOS 38 39 IMPLICIT NONE … … 42 43 IF ( type_ocean /= 'couple') THEN 43 44 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) 45 46 ENDIF 46 47 ENDIF … … 110 111 !**************************************************************************************** 111 112 112 IF (type_ocean == 'couple'.OR. &113 IF (type_ocean == 'couple'.OR. & 113 114 (type_ocean == 'slab' .AND. version_ocean == 'sicINT')) THEN 114 115 ! limit.nc has not yet been read. Do it now! … … 243 244 IF (grid_type==unstructured) THEN 244 245 245 !$OMP MASTER ! Only master thread246 247 246 248 247 IF ( type_ocean /= 'couple') THEN 249 248 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)) 252 251 ! IF (read_continents .OR. itime == 1) THEN 253 254 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)) 255 254 ! ENDIF 256 255 ENDIF! type_ocean /= couple 257 256 258 257 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) 260 259 ENDIF 261 260 262 261 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) 265 264 ENDIF 266 265 … … 280 279 END IF 281 280 282 !$OMP END MASTER283 281 284 282 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/open_climoz_m.F90
r3809 r3895 18 18 use netcdf95, only: nf95_open, nf95_close, nf95_gw_var, nf95_inq_varid 19 19 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 23 21 24 22 integer, intent(out):: ncid ! of "climoz_LMDZ.nc", OpenMP shared … … 41 39 42 40 print *, "Call sequence information: open_climoz" 43 44 if (is_mpi_root) then 41 if (is_master) then 45 42 call nf95_open("climoz_LMDZ.nc", nf90_nowrite, ncid) 46 43 … … 50 47 plev = plev * 100. 51 48 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 61 53 press_in_edg(1) = 0. 62 54 ! We choose edges halfway in logarithm: … … 65 57 ! (infinity, but any value guaranteed to be greater than the 66 58 ! surface pressure would do) 67 end if68 call bcast_mpi(press_in_edg)69 deallocate(plev) ! pointer59 deallocate(plev) ! pointer 60 endif 61 call bcast(press_in_edg) 70 62 71 63 end subroutine open_climoz -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phyaqua_mod.F90
r3867 r3895 32 32 USE mod_phys_lmdz_para, ONLY: is_master 33 33 USE mod_phys_lmdz_transfert_para, ONLY: bcast 34 USE mod_grid_phy_lmdz 34 35 IMPLICIT NONE 35 36 … … 235 236 CALL profil_sst(nlon, latitude, type_profil, phy_sst) 236 237 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 240 246 241 247 ! --------------------------------------------------------------------- … … 477 483 REAL, INTENT (IN) :: phy_fsic(klon, 360) 478 484 479 REAL :: phy_ glo(klon_mpi, 360) ! temporary variable, to store phy_***(:)485 REAL :: phy_mpi(klon_mpi, 360) ! temporary variable, to store phy_***(:) 480 486 ! on the whole physics grid 481 487 … … 483 489 PRINT *, 'writelim: Ecriture du fichier limit' 484 490 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) 490 496 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) 493 499 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) 508 514 509 515 END SUBROUTINE writelim_unstruct -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_cal_mod.F90
r3867 r3895 37 37 SUBROUTINE phys_cal_init(annee_ref,day_ref) 38 38 USE IOIPSL, ONLY: ymds2ju, getin, ioconf_calendar 39 USE mod_phys_lmdz_para, ONLY: is_master, bcast39 USE mod_phys_lmdz_para, ONLY: is_master,is_omp_master,bcast 40 40 IMPLICIT NONE 41 41 INTEGER,INTENT(IN) :: annee_ref … … 52 52 CALL bcast(calend) 53 53 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 62 64 ENDIF 63 64 65 65 66 CALL ymds2ju(annee_ref, 1, day_ref, 0., jD_ref) -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/physiq.F90
r3881 r3895 788 788 789 789 integer, save:: read_climoz ! read ozone climatology 790 !$OMP THREADPRIVATE(read_climoz) 790 791 ! (let it keep the default OpenMP shared attribute) 791 792 ! Allowed values are 0, 1 and 2 … … 796 797 797 798 integer, save:: ncid_climoz ! NetCDF file containing ozone climatologies 799 !$OMP THREADPRIVATE(ncid_climoz) 798 800 ! (let it keep the default OpenMP shared attribute) 799 801 800 802 real, pointer, save:: press_climoz(:) 803 !$OMP THREADPRIVATE(press_climoz) 801 804 ! (let it keep the default OpenMP shared attribute) 802 805 ! edges of pressure intervals for ozone climatologies, in Pa, in strictly … … 870 873 !albedo SB >>> 871 874 real,dimension(6),save :: SFRWL 875 !$OMP THREADPRIVATE(SFRWL) 872 876 !albedo SB <<< 873 877 … … 881 885 mydebug=.FALSE. 882 886 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) 884 888 !====================================================================== 885 889 ! Ecriture eventuelle d'un profil verticale en entree de la physique. … … 1119 1123 flag_aerosol, flag_aerosol_strat, ok_cdnc) 1120 1124 1121 CALL xios_update_calendar(1)1125 IF (is_omp_master) CALL xios_update_calendar(1) 1122 1126 1123 1127 CALL create_etat0_limit_unstruct … … 1349 1353 call iniradia(klon,klev,paprs(1,1:klev+1)) 1350 1354 1351 !$omp single1352 1355 if (read_climoz >= 1) then 1353 1356 call open_climoz(ncid_climoz, press_climoz) 1354 1357 END IF 1355 !$omp end single1356 1358 ! 1357 1359 !IM betaCRF … … 1663 1665 1664 1666 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) 1666 1668 ELSE 1667 1669 CALL regr_pr_av(ncid_climoz, (/"tro3 ", "tro3_daylight"/), & … … 4274 4276 ! write(97) u_seri,v_seri,t_seri,q_seri 4275 4277 ! close(97) 4276 !$OMP MASTER4277 4278 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) 4281 4280 deallocate(press_climoz) ! pointer 4282 4281 end if 4283 !$OMP END MASTER4284 4282 ENDIF 4285 4283 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_lat_time_climoz_m.F90
r3867 r3895 304 304 305 305 allocate(o3_out(n_lat_out, n_plev, 360, read_climoz)) 306 IF (regr_lat ) THEN306 IF (regr_lat_) THEN 307 307 allocate(o3_regr_lat(nbp_lat, n_plev, 0:13, read_climoz)) 308 308 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_pr_av_m.F90
r3819 r3895 46 46 47 47 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 48 53 character(len=*), intent(in):: name(:) ! of the NetCDF variables 49 54 integer, intent(in):: julien ! jour julien, 1 <= julien <= 360 … … 66 71 integer varid, ncerr ! for NetCDF 67 72 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)) 69 74 ! input fields at day "julien", on the global "dynamics" horizontal grid 70 75 ! First dimension is for longitude. … … 74 79 ! NetCDF variable "name(l)". 75 80 76 real v2(klon, size(press_in_edg) - 1, size( name))81 real v2(klon, size(press_in_edg) - 1, size(v3,3)) 77 82 ! fields scattered to the partial "physics" horizontal grid 78 83 ! "v2(i, k, l)" is at longitude "xlon(i)", latitude "xlat(i)", … … 85 90 86 91 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 88 98 call assert(shape(paprs) == (/klon, klev+1/), "regr_pr_av paprs") 89 99
Note: See TracChangeset
for help on using the changeset viewer.