GCC Code Coverage Report
Directory: ./ Exec Total Coverage
File: phylmd/physiqex_mod.F90 Lines: 0 23 0.0 %
Date: 2023-06-30 12:56:34 Branches: 0 60 0.0 %

Line Branch Exec Source
1
! $Id: physiq.F 1565 2011-08-31 12:53:29Z jghattas $
2
MODULE physiqex_mod
3
4
IMPLICIT NONE
5
6
CONTAINS
7
8
      SUBROUTINE physiqex (nlon,nlev, &
9
     &            debut,lafin,pdtphys, &
10
     &            paprs,pplay,pphi,pphis,presnivs, &
11
     &            u,v,rot,t,qx, &
12
     &            flxmass_w, &
13
     &            d_u, d_v, d_t, d_qx, d_ps)
14
15
      USE dimphy, only : klon,klev
16
      USE infotrac_phy, only : nqtot
17
      USE geometry_mod, only : latitude
18
!      USE comcstphy, only : rg
19
      USE ioipsl, only : ymds2ju
20
      USE phys_state_var_mod, only : phys_state_var_init
21
      USE phyetat0_mod, only: phyetat0
22
      USE output_physiqex_mod, ONLY: output_physiqex
23
24
      IMPLICIT none
25
!
26
! Routine argument:
27
!
28
29
      integer,intent(in) :: nlon ! number of atmospheric colums
30
      integer,intent(in) :: nlev ! number of vertical levels (should be =klev)
31
      logical,intent(in) :: debut ! signals first call to physics
32
      logical,intent(in) :: lafin ! signals last call to physics
33
      real,intent(in) :: pdtphys ! physics time step (s)
34
      real,intent(in) :: paprs(klon,klev+1) ! interlayer pressure (Pa)
35
      real,intent(in) :: pplay(klon,klev) ! mid-layer pressure (Pa)
36
      real,intent(in) :: pphi(klon,klev) ! geopotential at mid-layer
37
      real,intent(in) :: pphis(klon) ! surface geopotential
38
      real,intent(in) :: presnivs(klev) ! pseudo-pressure (Pa) of mid-layers
39
      real,intent(in) :: u(klon,klev) ! eastward zonal wind (m/s)
40
      real,intent(in) :: v(klon,klev) ! northward meridional wind (m/s)
41
      real,intent(in) :: rot(klon,klev) ! northward meridional wind (m/s)
42
      real,intent(in) :: t(klon,klev) ! temperature (K)
43
      real,intent(in) :: qx(klon,klev,nqtot) ! tracers (.../kg_air)
44
      real,intent(in) :: flxmass_w(klon,klev) ! vertical mass flux
45
      real,intent(out) :: d_u(klon,klev) ! physics tendency on u (m/s/s)
46
      real,intent(out) :: d_v(klon,klev) ! physics tendency on v (m/s/s)
47
      real,intent(out) :: d_t(klon,klev) ! physics tendency on t (K/s)
48
      real,intent(out) :: d_qx(klon,klev,nqtot) ! physics tendency on tracers
49
      real,intent(out) :: d_ps(klon) ! physics tendency on surface pressure
50
51
!    include "clesphys.h"
52
    INTEGER        length
53
    PARAMETER    ( length = 100 )
54
    REAL tabcntr0( length       )
55
    INTEGER, PARAMETER :: longcles=20
56
    REAL, SAVE :: clesphy0(longcles)
57
    !$OMP THREADPRIVATE(clesphy0)
58
59
60
real :: temp_newton(klon,klev)
61
integer :: k
62
logical, save :: first=.true.
63
!$OMP THREADPRIVATE(first)
64
65
real,save :: rg=9.81
66
!$OMP THREADPRIVATE(rg)
67
68
! For I/Os
69
integer :: itau0
70
real :: zjulian
71
72
73
!------------------------------------------------------------
74
! Initialisations de la physique au premier pas de temps
75
!------------------------------------------------------------
76
77
print*,'Debut physiqex',debut
78
! initializations
79
if (debut) then ! Things to do only for the first call to physics
80
print*,'Debut physiqex IN'
81
82
! load initial conditions for physics (including the grid)
83
  call phys_state_var_init(1) ! some initializations, required before calling phyetat0
84
  call phyetat0("startphy.nc", clesphy0, tabcntr0)
85
86
! Initialize outputs:
87
  itau0=0
88
  ! compute zjulian for annee0=1979 and month=1 dayref=1 and hour=0.0
89
  !CALL ymds2ju(annee0, month, dayref, hour, zjulian)
90
  call ymds2ju(1979, 1, 1, 0.0, zjulian)
91
92
#ifndef CPP_IOIPSL_NO_OUTPUT
93
  ! Initialize IOIPSL output file
94
#endif
95
96
endif ! of if (debut)
97
98
!------------------------------------------------------------
99
! Initialisations a chaque pas de temps
100
!------------------------------------------------------------
101
102
103
! set all tendencies to zero
104
d_u(1:klon,1:klev)=0.
105
d_v(1:klon,1:klev)=0.
106
d_t(1:klon,1:klev)=0.
107
d_qx(1:klon,1:klev,1:nqtot)=0.
108
d_ps(1:klon)=0.
109
110
!------------------------------------------------------------
111
! Calculs
112
!------------------------------------------------------------
113
114
! compute tendencies to return to the dynamics:
115
! "friction" on the first layer
116
d_u(1:klon,1)=-u(1:klon,1)/86400.
117
d_v(1:klon,1)=-v(1:klon,1)/86400.
118
! newtonian relaxation towards temp_newton()
119
do k=1,klev
120
  temp_newton(1:klon,k)=280.+cos(latitude(1:klon))*40.-pphi(1:klon,k)/rg*6.e-3
121
  d_t(1:klon,k)=(temp_newton(1:klon,k)-t(1:klon,k))/1.e5
122
enddo
123
124
125
!------------------------------------------------------------
126
! Entrees sorties
127
!------------------------------------------------------------
128
129
130
call output_physiqex(debut,zjulian,pdtphys,presnivs,paprs,u,v,t,qx,0.*t,0.*t,0.*t,0.*t,0.*t,0.*t)
131
132
133
! if lastcall, then it is time to write "restartphy.nc" file
134
if (lafin) then
135
  call phyredem("restartphy.nc")
136
endif
137
138
139
end subroutine physiqex
140
141
END MODULE physiqex_mod