Changeset 5090 for LMDZ6/branches/Amaury_dev
- Timestamp:
- Jul 20, 2024, 6:08:57 PM (4 months ago)
- Location:
- LMDZ6/branches/Amaury_dev/libf
- Files:
-
- 15 edited
- 1 moved
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/branches/Amaury_dev/libf/dyn3d/dynredem_mod.F90
r5088 r5090 3 3 USE netcdf, ONLY: nf90_strerror,nf90_noerr,nf90_redef,nf90_put_var,nf90_enddef,nf90_put_att,& 4 4 nf90_inq_varid,nf90_get_var,nf90_def_var 5 USE lmdz_ netcdf_format, ONLY: nf90_format5 USE lmdz_cppkeys_wrapper, ONLY: nf90_format 6 6 IMPLICIT NONE; PRIVATE 7 7 PUBLIC :: dynredem_write_u, dynredem_write_v, dynredem_read_u, err -
LMDZ6/branches/Amaury_dev/libf/dyn3d/gcm.F90
r5082 r5090 26 26 USE logic_mod, ONLY: ecripar, iflag_phys, read_start 27 27 28 USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_PHYS 29 28 30 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 29 31 ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique 30 32 ! A nettoyer. On ne veut qu'une ou deux routines d'interface 31 33 ! dynamique -> physique pour l'initialisation 32 #ifdef CPP_PHYS 34 ! AB 2024/07/20: remplace CPP key by fortran logical, but ^ still relevant, see later use of iniphys later on 33 35 USE iniphysiq_mod, ONLY: iniphysiq 34 #endif35 36 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 36 37 … … 406 407 407 408 IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN 408 409 #ifdef CPP_PHYS 410 CALL iniphysiq(iim,jjm,llm, &409 ! Physics: 410 IF (CPPKEY_PHYS) THEN 411 CALL iniphysiq(iim,jjm,llm, & 411 412 (jjm-1)*iim+2,comm_lmdz, & 412 413 daysec,day_ini,dtphys/nsplit_phys, & 413 414 rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp, & 414 415 iflag_phys) 415 #endif 416 END IF 416 417 ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100)) 417 418 -
LMDZ6/branches/Amaury_dev/libf/dyn3d/leapfrog.F
r5081 r5090 27 27 & start_time,dt 28 28 USE strings_mod, ONLY: msg 29 USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_PHYS 29 30 30 31 IMPLICIT NONE … … 462 463 #endif 463 464 ! #endif of #ifdef CPP_IOIPSL 464 #ifdef CPP_PHYS 465 CALL calfis( lafin , jD_cur, jH_cur,465 IF (CPPKEY_PHYS) THEN 466 CALL calfis( lafin , jD_cur, jH_cur, 466 467 $ ucov,vcov,teta,q,masse,ps,p,pk,phis,phi , 467 468 $ du,dv,dteta,dq, 468 469 $ flxw,dufi,dvfi,dtetafi,dqfi,dpfi ) 469 #endif 470 END IF 470 471 c ajout des tendances physiques: 471 472 c ------------------------------ -
LMDZ6/branches/Amaury_dev/libf/dyn3d/replay3d.F90
r4589 r5090 22 22 USE mod_const_mpi, ONLY: comm_lmdz 23 23 24 25 26 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!27 ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique28 ! A nettoyer. On ne veut qu'une ou deux routines d'interface29 ! dynamique -> physique pour l'initialisation30 #ifdef CPP_PHYS31 USE iniphysiq_mod, ONLY: iniphysiq32 #endif33 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!34 35 24 IMPLICIT NONE 36 25 37 26 ! ...... Version du 10/01/98 .......... 38 27 39 ! avec coordonnees verticales hybrides 28 ! avec coordonnees verticales hybrides 40 29 ! avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 ) 41 30 -
LMDZ6/branches/Amaury_dev/libf/dyn3dmem/bands.F90
r2771 r5090 381 381 subroutine AdjustBands_physic 382 382 use times 383 #ifdef CPP_PHYS 384 ! Ehouarn: what follows is only related to // physics 383 384 ! Ehouarn: what follows is only related to // physics 385 USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_PHYS 385 386 USE mod_phys_lmdz_para, only : klon_mpi_para_nb 386 #endif 387 387 388 USE parallel_lmdz 388 389 implicit none … … 408 409 medium=medium/mpi_size 409 410 NbTot=0 410 #ifdef CPP_PHYS 411 IF (CPPKEY_PHYS) THEN 411 412 do i=0,mpi_size-1 412 413 Inc(i)=nint(klon_mpi_para_nb(i)*(medium-value(i))/value(i)) … … 431 432 distrib_phys(i)=klon_mpi_para_nb(i)+inc(i) 432 433 enddo 433 #endif 434 END IF 434 435 435 436 end subroutine AdjustBands_physic -
LMDZ6/branches/Amaury_dev/libf/dyn3dmem/dynredem_mod.F90
r5088 r5090 6 6 USE netcdf, ONLY: nf90_strerror,nf90_noerr,nf90_redef,nf90_put_var,nf90_inquire_dimension,& 7 7 nf90_inq_varid,nf90_get_var,nf90_def_var,nf90_enddef,nf90_put_att 8 USE lmdz_ netcdf_format, ONLY: nf90_format8 USE lmdz_cppkeys_wrapper, ONLY: nf90_format 9 9 PRIVATE 10 10 PUBLIC :: dynredem_write_u, dynredem_write_v, dynredem_read_u, err -
LMDZ6/branches/Amaury_dev/libf/dyn3dmem/gcm.F90
r5082 r5090 12 12 USE parallel_lmdz 13 13 USE infotrac, ONLY: nqtot, init_infotrac 14 !#ifdef CPP_PHYS15 ! USE mod_interface_dyn_phys, ONLY: init_interface_dyn_phys16 !#endif17 14 USE mod_hallo 18 15 USE Bands … … 20 17 USE control_mod 21 18 22 #ifdef CPP_PHYS 19 23 20 USE iniphysiq_mod, ONLY: iniphysiq 24 #endif 21 USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_PHYS 22 25 23 USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, r, rad 26 24 USE logic_mod ! all of it, because of copyin clause when calling leapfrog … … 415 413 IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN 416 414 ! Physics: 417 #ifdef CPP_PHYS 418 CALL iniphysiq(iim,jjm,llm, &419 distrib_phys(mpi_rank),comm_lmdz, &420 daysec,day_ini,dtphys/nsplit_phys, &421 rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp, &422 iflag_phys)423 #endif 415 IF (CPPKEY_PHYS) THEN 416 CALL iniphysiq(iim,jjm,llm, & 417 distrib_phys(mpi_rank),comm_lmdz, & 418 daysec,day_ini,dtphys/nsplit_phys, & 419 rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp, & 420 iflag_phys) 421 END IF 424 422 ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100)) 425 423 -
LMDZ6/branches/Amaury_dev/libf/dyn3dmem/lmdz_call_calfis.F90
r5087 r5090 88 88 USE comvert_mod, ONLY: ap, bp, pressure_exner 89 89 USE temps_mod, ONLY: day_ini, day_ref, jd_ref, jh_ref, start_time 90 #ifdef CPP_PHYS91 90 USE lmdz_calfis_loc 92 #endif 91 USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_PHYS 93 92 94 93 IMPLICIT NONE … … 233 232 !$OMP BARRIER 234 233 235 #ifdef CPP_PHYS 236 CALL calfis_loc(lafin ,jD_cur, jH_cur, &234 IF (CPPKEY_PHYS) THEN 235 CALL calfis_loc(lafin ,jD_cur, jH_cur, & 237 236 ucov,vcov,teta,q,masse,ps,p,pk,phis,phi , & 238 237 du,dv,dteta,dq, & 239 238 flxw, dufi,dvfi,dtetafi,dqfi,dpfi ) 240 #endif 239 END IF 241 240 ijb=ij_begin 242 241 ije=ij_end -
LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/calfis.F
r5086 r5090 27 27 $ pdpsfi) 28 28 c 29 c Auteur : P. Le Van, F. Hourdin 29 c Auteur : P. Le Van, F. Hourdin 30 30 c ......... 31 31 USE infotrac, ONLY: nqtot, tracers 32 32 USE control_mod, ONLY: planet_type, nsplit_phys 33 #ifdef CPP_PHYS34 33 USE callphysiq_mod, ONLY: call_physiq 35 #endif 34 USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_PHYS 36 35 USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, kappa, pi 37 36 USE comvert_mod, ONLY: preff, presnivs 38 37 39 38 IMPLICIT NONE 40 39 c======================================================================= … … 48 47 c ---------- 49 48 c 50 c - les vents sont donnes dans la physique par leurs composantes 49 c - les vents sont donnes dans la physique par leurs composantes 51 50 c naturelles. 52 51 c - la variable thermodynamique de la physique est une variable 53 c intensive : T 52 c intensive : T 54 53 c pour la dynamique on prend T * ( preff / p(l) ) **kappa 55 54 c - les deux seules variables dependant de la geometrie necessaires 56 c pour la physique sont la latitude pour le rayonnement et 57 c l'aire de la maille quand on veut integrer une grandeur 55 c pour la physique sont la latitude pour le rayonnement et 56 c l'aire de la maille quand on veut integrer une grandeur 58 57 c horizontalement. 59 c - les points de la physique sont les points scalaires de la 58 c - les points de la physique sont les points scalaires de la 60 59 c la dynamique; numerotation: 61 60 c 1 pour le pole nord … … 67 66 c ------- 68 67 c pucov covariant zonal velocity 69 c pvcov covariant meridional velocity 68 c pvcov covariant meridional velocity 70 69 c pteta potential temperature 71 70 c pps surface pressure … … 77 76 c -------- 78 77 c pdufi tendency for the natural zonal velocity (ms-1) 79 c pdvfi tendency for the natural meridional velocity 78 c pdvfi tendency for the natural meridional velocity 80 79 c pdhfi tendency for the potential temperature 81 80 c pdtsfi tendency for the surface temperature … … 165 164 REAL flxwfi(ngridmx,llm) ! Flux de masse verticale sur la grille physiq 166 165 c 167 166 168 167 REAL SSUM 169 168 … … 201 200 c ---------------------------------- 202 201 203 202 204 203 zpsrf(1) = pps(1,1) 205 204 … … 217 216 c ----------------------------------------------------------------- 218 217 c .... zplev definis aux (llm +1) interfaces des couches .... 219 c .... zplay definis aux ( llm ) milieux des couches .... 218 c .... zplay definis aux ( llm ) milieux des couches .... 220 219 c ----------------------------------------------------------------- 221 220 … … 329 328 330 329 c .... Calcul de la vitesse verticale ( en Pa*m*s ou Kg/s ) .... 331 c JG : ancien calcule de omega utilise dans physiq.F. Maintenant le flux 332 c de masse est calclue dans advtrac.F 330 c JG : ancien calcule de omega utilise dans physiq.F. Maintenant le flux 331 c de masse est calclue dans advtrac.F 333 332 c DO l=1,llm 334 333 c pvervel(1,l)=pw(1,1,l) * g /apoln … … 351 350 DO j=2,jjm 352 351 ig0 = 1+(j-2)*iim 353 zufi(ig0+1,l)= 0.5 * 352 zufi(ig0+1,l)= 0.5 * 354 353 $ ( pucov(iim,j,l)/cu(iim,j) + pucov(1,j,l)/cu(1,j) ) 355 pcvgu(ig0+1,l)= 0.5 * 354 pcvgu(ig0+1,l)= 0.5 * 356 355 $ ( pducov(iim,j,l)/cu(iim,j) + pducov(1,j,l)/cu(1,j) ) 357 356 DO i=2,iim … … 373 372 do j=1,jjm 374 373 zrot(i,j,l) = (pvcov(i+1,j,l) - pvcov(i,j,l) 375 $ + pucov(i,j+1,l) - pucov(i,j,l)) 376 $ / (cu(i,j)+cu(i,j+1)) 374 $ + pucov(i,j+1,l) - pucov(i,j,l)) 375 $ / (cu(i,j)+cu(i,j+1)) 377 376 $ / (cv(i+1,j)+cv(i,j)) *4 378 377 enddo … … 402 401 403 402 404 c 47. champs de vents aux pole nord 403 c 47. champs de vents aux pole nord 405 404 c ------------------------------ 406 405 c U = 1 / pi * integrale [ v * cos(long) * d long ] … … 475 474 zdqfic(:,:,:)=0. 476 475 477 #ifdef CPP_PHYS 476 IF (CPPKEY_PHYS) THEN 478 477 479 478 do isplit=1,nsplit_phys … … 500 499 ! . nqtot, !! nq 501 500 ! . tracers(:)%name,!! tracer names from dynamical core (given in infotrac) 502 ! . debut_split, !! firstcall 501 ! . debut_split, !! firstcall 503 502 ! . lafin_split, !! lastcall 504 503 ! . jD_cur, !! pday. see leapfrog … … 534 533 enddo ! of do isplit=1,nsplit_phys 535 534 536 #endif 537 ! of #ifdef CPP_PHYS 535 END IF 538 536 539 537 zdufi(:,:)=zdufic(:,:)/nsplit_phys … … 541 539 zdtfi(:,:)=zdtfic(:,:)/nsplit_phys 542 540 zdqfi(:,:,:)=zdqfic(:,:,:)/nsplit_phys 543 544 545 500 CONTINUE546 541 547 542 c----------------------------------------------------------------------- … … 681 676 682 677 c----------------------------------------------------------------------- 683 684 700 CONTINUE685 686 678 firstcal = .FALSE. 687 679 -
LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/lmdz_calfis_loc.F90
r5066 r5090 28 28 pdqfi, & 29 29 pdpsfi) 30 #ifdef CPP_PHYS 31 ! If using physics 32 ! 33 ! Auteur : P. Le Van, F. Hourdin 34 ! ......... 30 35 31 USE dimphy 36 32 USE mod_phys_lmdz_mpi_data, mpi_root_xx=>mpi_master … … 39 35 USE mod_interface_dyn_phys 40 36 USE IOPHY 41 #endif 37 42 38 USE lmdz_mpi 43 39 … … 49 45 USE infotrac, ONLY : nqtot, tracers 50 46 USE control_mod, ONLY : planet_type, nsplit_phys 51 #ifdef CPP_PHYS52 47 USE callphysiq_mod, ONLY: call_physiq 53 #endif 48 USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_PHYS 49 54 50 USE comvert_mod, ONLY : preff, presnivs 55 51 USE comconst_mod, ONLY : cpp, daysec, dtphys, dtvr, kappa, pi … … 146 142 REAL, INTENT(OUT) :: pdpsfi(iip1, jjb_u:jje_u) ! tendency on surface pressure (Pa/s) 147 143 148 #ifdef CPP_PHYS 144 149 145 ! Ehouarn: for now calfis_p needs some informations from physics to compile 150 146 ! Local variables : … … 237 233 INTEGER :: jjb,jje 238 234 235 IF (CPPKEY_PHYS) THEN 236 239 237 ! 240 238 !----------------------------------------------------------------------- … … 249 247 IF ( firstcal ) THEN 250 248 debut = .TRUE. 251 IF (ngridmx .NE.2+(jjm-1)*iim) THEN249 IF (ngridmx/=2+(jjm-1)*iim) THEN 252 250 write(lunout,*) 'STOP dans calfis' 253 251 write(lunout,*) & … … 719 717 zdqfic_omp(:,:,:)=0. 720 718 721 #ifdef CPP_PHYS722 719 do isplit=1,nsplit_phys 723 720 … … 750 747 enddo 751 748 752 #endif753 ! of #ifdef CPP_PHYS754 755 749 756 750 zdufi_omp(:,:)=zdufic_omp(:,:)/nsplit_phys … … 847 841 848 842 klon=klon_mpi 849 500 CONTINUE850 843 !$OMP BARRIER 851 844 … … 1204 1197 !----------------------------------------------------------------------- 1205 1198 1206 700 CONTINUE1207 1208 1199 firstcal = .FALSE. 1209 #endif 1210 ! of #ifdef CPP_PHYS 1200 END IF 1211 1201 END SUBROUTINE calfis_loc 1212 1202 -
LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/limit_netcdf.F90
r5088 r5090 76 76 NF90_CLOBBER, NF90_ENDDEF, NF90_UNLIMITED, NF90_FLOAT, & 77 77 NF90_64BIT_OFFSET 78 USE lmdz_ netcdf_format, ONLY: nf90_format78 USE lmdz_cppkeys_wrapper, ONLY: nf90_format 79 79 USE inter_barxy_m, ONLY: inter_barxy 80 80 USE netcdf95, ONLY: nf95_def_var, nf95_put_att, nf95_put_var -
LMDZ6/branches/Amaury_dev/libf/misc/lmdz_cppkeys_wrapper.F90
r5089 r5090 1 1 ! --------------------------------------------- 2 ! This module serves as a wrapper around netcdf. 3 ! It serves two primary functions: 4 ! 1) Turn netcdf into a "real" fortran module, without the INCLUDE call 5 ! 2) Handle the NC_DOUBLE CPP key. This key should ONLY be used here. 6 ! The "real" netcdf module/headers should ONLY be called here. 2 ! This file is part of an effort to replace most uses of preprocessor CPP keys by fortran variables, 3 ! to improve readability, compilation coverage, and linting. 4 ! CPP keys used here should ONLY be used here, 5 ! and imported through USE ..., ONLY: ... elsewhere 6 ! CPP keys supported (key -> fortran variables associated): 7 ! NC_DOUBLE -> nf90_format 8 ! CPP_PHYS -> CPPKEY_PHYS 7 9 ! --------------------------------------------- 8 10 9 MODULE lmdz_ netcdf_format11 MODULE lmdz_cppkeys_wrapper 10 12 USE, INTRINSIC :: ISO_FORTRAN_ENV, ONLY : REAL64, REAL32 11 13 USE netcdf, ONLY: nf90_float, nf90_double 12 14 IMPLICIT NONE; PRIVATE 13 PUBLIC nf90_format 15 PUBLIC nf90_format, CPPKEY_PHYS 14 16 15 17 #ifdef NC_DOUBLE … … 18 20 INTEGER, PARAMETER :: nf90_format = nf90_float 19 21 #endif 20 END MODULE lmdz_netcdf_format 22 23 #ifdef CPP_PHYS 24 LOGICAL, PARAMETER :: CPPKEY_PHYS = .TRUE. 25 #else 26 LOGICAL, PARAMETER :: CPPKEY_PHYS = .FALSE. 27 #endif 28 29 END MODULE lmdz_cppkeys_wrapper -
LMDZ6/branches/Amaury_dev/libf/misc/write_field.F90
r5088 r5090 2 2 USE netcdf, ONLY: nf90_sync, nf90_put_var, nf90_enddef, nf90_def_dim, nf90_unlimited, & 3 3 nf90_clobber, nf90_create, nf90_def_var 4 USE lmdz_ netcdf_format, ONLY: nf90_format4 USE lmdz_cppkeys_wrapper, ONLY: nf90_format 5 5 6 6 implicit none -
LMDZ6/branches/Amaury_dev/libf/phylmd/iostart.F90
r5088 r5090 387 387 SUBROUTINE put_field_rgen(pass, field_name,title,field,field_size) 388 388 USE netcdf, ONLY: nf90_def_var,nf90_put_att,nf90_inq_varid,nf90_put_var 389 USE lmdz_ netcdf_format, ONLY: nf90_format389 USE lmdz_cppkeys_wrapper, ONLY: nf90_format 390 390 USE dimphy 391 391 USE geometry_mod … … 511 511 SUBROUTINE put_var_rgen(pass, var_name,title,var,var_size) 512 512 USE netcdf, ONLY: nf90_def_var,nf90_put_var,nf90_inq_varid,nf90_put_att 513 USE lmdz_ netcdf_format, ONLY: nf90_format513 USE lmdz_cppkeys_wrapper, ONLY: nf90_format 514 514 USE dimphy 515 515 USE mod_phys_lmdz_para -
LMDZ6/branches/Amaury_dev/libf/phylmd/phyaqua_mod.F90
r5088 r5090 573 573 nf90_enddef, nf90_put_att, nf90_unlimited, nf90_noerr, nf90_global, nf90_clobber, & 574 574 nf90_64bit_offset, nf90_def_dim, nf90_create 575 USE lmdz_ netcdf_format, ONLY: nf90_format575 USE lmdz_cppkeys_wrapper, ONLY: nf90_format 576 576 IMPLICIT NONE 577 577 -
LMDZ6/branches/Amaury_dev/libf/phylmdiso/phyaqua_mod.F90
r5088 r5090 594 594 nf90_def_dim,nf90_create,nf90_put_var,nf90_unlimited,nf90_global,nf90_64bit_offset,& 595 595 nf90_enddef 596 USE lmdz_ netcdf_format, ONLY: nf90_format596 USE lmdz_cppkeys_wrapper, ONLY: nf90_format 597 597 IMPLICIT NONE 598 598
Note: See TracChangeset
for help on using the changeset viewer.