source: trunk/WRF.COMMON/INTERFACES/dynphy_wrf_venus_lmd/callphysiq_mod.F @ 3529

Last change on this file since 3529 was 2277, checked in by mlefevre, 5 years ago

MESOSCALE. Updates of physics interface for Venus, prescribed and void physics.

File size: 2.7 KB
Line 
1!
2! $Id: $
3!
4MODULE callphysiq_mod
5
6IMPLICIT NONE
7
8 !! ----------------------------------------------------------
9 !! ---- CALL TO VENUS PHYSICS
10 !! ----------------------------------------------------------
11
12CONTAINS
13
14SUBROUTINE call_physiq(planet_type, klon,llm,nqtot,                       &
15                       debut_split,lafin_split)
16
17  USE variables_mod
18  USE physiq_mod, ONLY: physiq
19  USE module_model_constants, only : p0,rcp,cp
20  IMPLICIT NONE
21
22  character(len=10),INTENT(IN) :: planet_type ! planet type ('earth','mars',...)
23
24  INTEGER,INTENT(IN) :: klon ! (local) number of atmospheric columns
25  INTEGER,INTENT(IN) :: llm  ! number of atmospheric layers
26  INTEGER,INTENT(IN) :: nqtot ! number of tracers
27  LOGICAL,INTENT(IN) :: debut_split ! .true. if very first call to physics
28  LOGICAL,INTENT(IN) :: lafin_split ! .true. if last call to physics
29  REAL*8 :: zplevmoy(llm+1) ! planet-averaged mean pressure (Pa) at interfaces
30  REAL*8 :: ztmoy(llm)
31
32!  ! Local variables
33!  CHARACTER(len=11) :: modname="call_physiq"
34!  LOGICAL,SAVE :: firstcall=.true.
35!!$OMP THREADPRIVATE(firstcall)
36!
37!! Sanity check on physics package type
38!  IF (firstcall) THEN
39!    IF (planet_type.ne."mars") THEN
40!      CALL abort_gcm(modname,"wrong planet_type for this physics package",1)
41!    ENDIF
42!    firstcall=.false.
43!  ENDIF
44
45! Sanity check on physics package type
46 IF (debut_split) THEN
47   IF (planet_type.ne."venus") THEN
48     PRINT*,"wrong planet_type for this physics package"
49     STOP
50   ENDIF
51 ENDIF
52
53! Set dummy variables for Mars to zero (additional and prob useless security)
54! NB: tname already filled with tracers' names (though not used here)
55  zpk_omp(1:klon,1:llm)=cp*((zplay_omp(1:klon,1:llm)/p0)**rcp)
56  !print*,'zpk_omp',zpk_omp(1,:)
57  zphis_omp(1:klon)=zphi_omp(1:klon,1)
58  presnivs_omp(:)=0.
59  zrfi_omp(:,:)=0.
60  ztmoy(:)=ztfi_omp(1,:)
61  zplevmoy(:)=zplev_omp(1,:)
62! Call physics package with required inputs/outputs
63  CALL physiq(klon,           &
64              llm,            &
65              nqtot,          &
66              debut_split,    &
67              lafin_split,    &
68              jD_cur,         &
69              jH_cur_split,   &
70              zdt_split,      &
71              zplev_omp,      &
72              zplay_omp,      &
73              zpk_omp,        &
74              zphi_omp,       &
75              zphis_omp,      &
76              presnivs_omp,   &
77              zufi_omp,       &
78              zvfi_omp,       &
79              ztfi_omp,       &
80              zqfi_omp,       &
81              flxwfi_omp,     &
82              zdufi_omp,      &
83              zdvfi_omp,      &
84              zdtfi_omp,      &
85              zdqfi_omp,      &
86              zdpsrf_omp)
87END SUBROUTINE call_physiq
88
89END MODULE callphysiq_mod
Note: See TracBrowser for help on using the repository browser.