Changeset 5116 for LMDZ6/branches/Amaury_dev/libf/phydev
- Timestamp:
- Jul 24, 2024, 2:54:37 PM (6 months ago)
- Location:
- LMDZ6/branches/Amaury_dev/libf/phydev
- Files:
-
- 5 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/branches/Amaury_dev/libf/phydev/comcstphy.F90
r1907 r5116 1 1 module comcstphy 2 2 3 real:: rradius ! planet radius (m)4 real:: rr ! recuced gas constant: R/molar mass of atm5 real:: rg ! gravity6 real:: rcpp ! specific heat of the atmosphere3 REAL :: rradius ! planet radius (m) 4 REAL :: rr ! recuced gas constant: R/molar mass of atm 5 REAL :: rg ! gravity 6 REAL :: rcpp ! specific heat of the atmosphere 7 7 8 8 end module comcstphy -
LMDZ6/branches/Amaury_dev/libf/phydev/iophy.F90
r5113 r5116 25 25 26 26 SUBROUTINE init_iophy_new(rlat, rlon) 27 USE dimphy, only: klon28 USE lmdz_phys_para, only: gather, bcast, &27 USE dimphy, ONLY: klon 28 USE lmdz_phys_para, ONLY: gather, bcast, & 29 29 jj_nb, jj_begin, jj_end, ii_begin, ii_end, & 30 30 mpi_size, mpi_rank, klon_mpi, & 31 31 is_sequential, is_south_pole_dyn 32 USE lmdz_grid_phy, only: nbp_lon, nbp_lat, klon_glo32 USE lmdz_grid_phy, ONLY: nbp_lon, nbp_lat, klon_glo 33 33 USE lmdz_print_control, ONLY: lunout, prt_level 34 34 USE lmdz_grid_phy, ONLY: nbp_lon, nbp_lat 35 USE ioipsl, only: flio_dom_set36 use wxios, only: wxios_domain_param, using_xios35 USE ioipsl, ONLY: flio_dom_set 36 use wxios, ONLY: wxios_domain_param, using_xios 37 37 IMPLICIT NONE 38 38 real, dimension(klon), intent(in) :: rlon … … 50 50 INTEGER, DIMENSION(2) :: dhe 51 51 INTEGER :: i 52 integer:: data_ibegin, data_iend52 INTEGER :: data_ibegin, data_iend 53 53 54 54 CALL gather(rlat, rlat_glo) … … 61 61 io_lat(1) = rlat_glo(1) 62 62 io_lat(nbp_lat) = rlat_glo(klon_glo) 63 IF ((nbp_lon * nbp_lat) > 1) then63 IF ((nbp_lon * nbp_lat) > 1) THEN 64 64 DO i = 2, nbp_lat - 1 65 65 io_lat(i) = rlat_glo(2 + (i - 2) * nbp_lon) … … 93 93 dpl = (/ nbp_lon, jj_end /) 94 94 dhs = (/ ii_begin - 1, 0 /) 95 if (mpi_rank==mpi_size - 1) then95 if (mpi_rank==mpi_size - 1) THEN 96 96 dhe = (/0, 0/) 97 97 else … … 117 117 END IF 118 118 119 if (prt_level>=10) then120 write(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " iibegin=", ii_begin, " ii_end=", ii_end, " jjbegin=", jj_begin, " jj_nb=", jj_nb, " jj_end=", jj_end121 write(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " nbp_lon=", nbp_lon, " nbp_lat=", nbp_lat122 write(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " data_ibegin=", data_ibegin, " data_iend=", data_iend123 write(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " data_ibegin=", data_ibegin, " data_iend=", data_iend124 write(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " is_south_pole=", is_south_pole_dyn119 if (prt_level>=10) THEN 120 WRITE(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " iibegin=", ii_begin, " ii_end=", ii_end, " jjbegin=", jj_begin, " jj_nb=", jj_nb, " jj_end=", jj_end 121 WRITE(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " nbp_lon=", nbp_lon, " nbp_lat=", nbp_lat 122 WRITE(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " data_ibegin=", data_ibegin, " data_iend=", data_iend 123 WRITE(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " data_ibegin=", data_ibegin, " data_iend=", data_iend 124 WRITE(lunout, *) "init_iophy_new: mpirank=", mpi_rank, " is_south_pole=", is_south_pole_dyn 125 125 endif 126 126 … … 139 139 140 140 SUBROUTINE histbeg_phy(name, itau0, zjulian, dtime, nhori, nid_day) 141 USE lmdz_phys_para, only: is_sequential, jj_begin, jj_end, jj_nb142 use ioipsl, only: histbeg141 USE lmdz_phys_para, ONLY: is_sequential, jj_begin, jj_end, jj_nb 142 use ioipsl, ONLY: histbeg 143 143 USE lmdz_print_control, ONLY: prt_level, lunout 144 144 USE lmdz_grid_phy, ONLY: nbp_lon … … 153 153 154 154 !$OMP MASTER 155 if (is_sequential) then155 if (is_sequential) THEN 156 156 CALL histbeg(name, nbp_lon, io_lon, jj_nb, io_lat(jj_begin:jj_end), & 157 157 1, nbp_lon, 1, jj_nb, itau0, zjulian, dtime, nhori, nid_day) … … 169 169 ! SUBROUTINE histbeg_phyxios(name,itau0,zjulian,dtime,ffreq,lev,nhori,nid_day) 170 170 SUBROUTINE histbeg_phyxios(name, ffreq, lev) 171 USE lmdz_phys_para, only: is_using_mpi, is_mpi_root172 use wxios, only: wxios_add_file171 USE lmdz_phys_para, ONLY: is_using_mpi, is_mpi_root 172 use wxios, ONLY: wxios_add_file 173 173 IMPLICIT NONE 174 174 … … 198 198 199 199 SUBROUTINE histwrite2d_phy(nid, lpoint, name, itau, field) 200 USE dimphy, only: klon201 USE lmdz_phys_para, only: Gather_omp, grid1Dto2D_mpi, &200 USE dimphy, ONLY: klon 201 USE lmdz_phys_para, ONLY: Gather_omp, grid1Dto2D_mpi, & 202 202 is_sequential, klon_mpi_begin, klon_mpi_end, & 203 203 jj_nb, klon_mpi 204 USE ioipsl, only: histwrite204 USE ioipsl, ONLY: histwrite 205 205 USE lmdz_grid_phy, ONLY: nbp_lon 206 206 USE lmdz_abort_physic, ONLY: abort_physic … … 216 216 REAL :: Field2d(nbp_lon, jj_nb) 217 217 218 integer:: ip218 INTEGER :: ip 219 219 real, allocatable, dimension(:) :: fieldok 220 220 … … 224 224 !$OMP MASTER 225 225 CALL grid1Dto2D_mpi(buffer_omp, Field2d) 226 if(.NOT.lpoint) THEN226 IF(.NOT.lpoint) THEN 227 227 ALLOCATE(index2d(nbp_lon * jj_nb)) 228 228 ALLOCATE(fieldok(nbp_lon * jj_nb)) … … 232 232 ALLOCATE(index2d(npstn)) 233 233 234 if(is_sequential) then234 IF(is_sequential) THEN 235 235 ! klon_mpi_begin=1 236 236 ! klon_mpi_end=klon … … 258 258 259 259 SUBROUTINE histwrite3d_phy(nid, lpoint, name, itau, field) 260 USE dimphy, only: klon261 USE lmdz_phys_para, only: Gather_omp, grid1Dto2D_mpi, &260 USE dimphy, ONLY: klon 261 USE lmdz_phys_para, ONLY: Gather_omp, grid1Dto2D_mpi, & 262 262 is_sequential, klon_mpi_begin, klon_mpi_end, & 263 263 jj_nb, klon_mpi 264 USE ioipsl, only: histwrite264 USE ioipsl, ONLY: histwrite 265 265 USE lmdz_grid_phy, ONLY: nbp_lon 266 266 USE lmdz_abort_physic, ONLY: abort_physic … … 284 284 !$OMP MASTER 285 285 CALL grid1Dto2D_mpi(buffer_omp, field3d) 286 if(.NOT.lpoint) THEN286 IF(.NOT.lpoint) THEN 287 287 ALLOCATE(index3d(nbp_lon * jj_nb * nlev)) 288 288 ALLOCATE(fieldok(nbp_lon * jj_nb, nlev)) … … 293 293 ALLOCATE(fieldok(npstn, nlev)) 294 294 295 if(is_sequential) then295 IF(is_sequential) THEN 296 296 ! klon_mpi_begin=1 297 297 ! klon_mpi_end=klon … … 323 323 324 324 SUBROUTINE histwrite2d_xios(field_name, field) 325 USE dimphy, only: klon326 USE lmdz_phys_para, only: gather_omp, grid1Dto2D_mpi, &325 USE dimphy, ONLY: klon 326 USE lmdz_phys_para, ONLY: gather_omp, grid1Dto2D_mpi, & 327 327 jj_nb, klon_mpi 328 USE lmdz_xios, only: xios_send_field328 USE lmdz_xios, ONLY: xios_send_field 329 329 USE lmdz_print_control, ONLY: prt_level, lunout 330 330 USE lmdz_grid_phy, ONLY: nbp_lon … … 357 357 358 358 SUBROUTINE histwrite3d_xios(field_name, field) 359 USE dimphy, only: klon, klev360 USE lmdz_phys_para, only: gather_omp, grid1Dto2D_mpi, &359 USE dimphy, ONLY: klon, klev 360 USE lmdz_phys_para, ONLY: gather_omp, grid1Dto2D_mpi, & 361 361 jj_nb, klon_mpi 362 USE lmdz_xios, only: xios_send_field362 USE lmdz_xios, ONLY: xios_send_field 363 363 USE lmdz_print_control, ONLY: prt_level, lunout 364 364 USE lmdz_grid_phy, ONLY: nbp_lon … … 373 373 INTEGER :: ip, n, nlev 374 374 375 IF (prt_level >= 10) write(lunout, *)'Begin histrwrite3d_xios ', trim(field_name)375 IF (prt_level >= 10) WRITE(lunout, *)'Begin histrwrite3d_xios ', trim(field_name) 376 376 377 377 !Et on.... écrit … … 386 386 !$OMP END MASTER 387 387 388 IF (prt_level >= 10) write(lunout, *)'End histrwrite3d_xios ', trim(field_name)388 IF (prt_level >= 10) WRITE(lunout, *)'End histrwrite3d_xios ', trim(field_name) 389 389 END SUBROUTINE histwrite3d_xios 390 390 -
LMDZ6/branches/Amaury_dev/libf/phydev/phyetat0.F90
r5112 r5116 6 6 ! and do some resulting initializations 7 7 8 USE dimphy, only: klon8 USE dimphy, ONLY: klon 9 9 USE iostart, ONLY: open_startphy,get_field,close_startphy 10 10 USE iophy, ONLY: init_iophy_new -
LMDZ6/branches/Amaury_dev/libf/phydev/phys_state_var_mod.F90
r5101 r5116 19 19 ! use dimphy, ONLY: klon 20 20 21 ! if (.not.allocated(rlat)) then21 ! if (.not.allocated(rlat)) THEN 22 22 ! ALLOCATE(rlat(klon),rlon(klon)) 23 23 ! else 24 ! write(*,*) "phys_state_var_init: warning, rlat already allocated"24 ! WRITE(*,*) "phys_state_var_init: warning, rlat already allocated" 25 25 ! endif 26 26 -
LMDZ6/branches/Amaury_dev/libf/phydev/physiq_mod.F90
r5112 r5116 24 24 25 25 USE lmdz_xios, ONLY: xios_update_calendar, using_xios 26 USE wxios, only: wxios_add_vaxis, wxios_set_cal, wxios_closedef26 USE wxios, ONLY: wxios_add_vaxis, wxios_set_cal, wxios_closedef 27 27 USE iophy, ONLY: histwrite_phy 28 28 … … 54 54 integer,save :: itau=0 ! counter to count number of calls to physics 55 55 !$OMP THREADPRIVATE(itau) 56 real:: temp_newton(klon,klev)57 integer:: k56 REAL :: temp_newton(klon,klev) 57 INTEGER :: k 58 58 logical, save :: first=.TRUE. 59 59 !$OMP THREADPRIVATE(first) 60 60 61 61 ! For I/Os 62 integer:: itau063 real:: zjulian64 real:: dtime65 integer:: nhori ! horizontal coordinate ID62 INTEGER :: itau0 63 REAL :: zjulian 64 REAL :: dtime 65 INTEGER :: nhori ! horizontal coordinate ID 66 66 integer,save :: nid_hist ! output file ID 67 67 !$OMP THREADPRIVATE(nid_hist) 68 integer:: zvertid ! vertical coordinate ID68 INTEGER :: zvertid ! vertical coordinate ID 69 69 integer,save :: iwrite_phys ! output every iwrite_phys physics step 70 70 !$OMP THREADPRIVATE(iwrite_phys) 71 71 integer,save :: iwrite_phys_omp ! intermediate variable to read iwrite_phys 72 72 ! (must be shared by all threads) 73 real:: t_ops ! frequency of the IOIPSL operations (eg average over...)74 real:: t_wrt ! frequency of the IOIPSL outputs73 REAL :: t_ops ! frequency of the IOIPSL operations (eg average over...) 74 REAL :: t_wrt ! frequency of the IOIPSL outputs 75 75 76 76 ! initializations … … 165 165 ! IOIPSL 166 166 #ifndef CPP_IOIPSL_NO_OUTPUT 167 IF (modulo(itau,iwrite_phys)==0) then167 IF (modulo(itau,iwrite_phys)==0) THEN 168 168 CALL histwrite_phy(nid_hist,.FALSE.,"temperature",itau,t) 169 169 CALL histwrite_phy(nid_hist,.FALSE.,"u",itau,u) … … 191 191 192 192 ! if lastcall, then it is time to write "restartphy.nc" file 193 IF (lafin) then193 IF (lafin) THEN 194 194 CALL phyredem("restartphy.nc") 195 195 END IF
Note: See TracChangeset
for help on using the changeset viewer.