GCC Code Coverage Report


Directory: ./
File: phys/paramlmdz_phy_mod.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 68 68 100.0%
Branches: 55 62 88.7%

Line Branch Exec Source
1 MODULE paramLMDZ_phy_mod
2
3 ! Olivier 13/07/2016
4 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
5
6 CONTAINS
7
8 481 SUBROUTINE ini_paramLMDZ_phy(dtime,nid_ctesGCM)
9
10 USE iophy
11 USE dimphy
12 USE ioipsl, only: histbeg, histvert, histdef, histend, ymds2ju
13 USE mod_phys_lmdz_mpi_data, ONLY: is_mpi_root
14 USE geometry_mod, ONLY: longitude_deg, latitude_deg
15 USE mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, klon_glo
16 USE time_phylmdz_mod, ONLY: annee_ref, day_ref, itau_phy, pdtphys
17 USE mod_phys_lmdz_transfert_para, ONLY: gather, bcast
18
19 IMPLICIT NONE
20
21 include "clesphys.h"
22 include "YOMCST.h"
23
24 REAL, INTENT(OUT) :: dtime
25 INTEGER, INTENT(OUT) :: nid_ctesGCM
26
27 2 REAL,DIMENSION(klon_glo) :: rlat_glo
28 2 REAL,DIMENSION(klon_glo) :: rlon_glo
29 INTEGER i, idayref, ISW, itau_w
30 REAL zstophy, zout
31 2 REAL zx_lon(nbp_lon,nbp_lat)
32 2 REAL zx_lat(nbp_lon,nbp_lat)
33
34 CHARACTER*1 ch1
35 INTEGER nhori
36 INTEGER, PARAMETER :: np=1
37
38 REAL zjulian
39 SAVE zjulian
40 !$OMP THREADPRIVATE(zjulian)
41
42 !IM Implemente en modes sequentiel et parallele
43
44 1 CALL gather(latitude_deg,rlat_glo)
45 1 CALL bcast(rlat_glo)
46 1 CALL gather(longitude_deg,rlon_glo)
47 1 CALL bcast(rlon_glo)
48
49 !$OMP MASTER
50
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (is_mpi_root) THEN
51 !
52 ! zstophy = pdtphys
53 ! zout = -1
54 !--OB modified for daily output
55 1 zstophy = 86400.
56 1 zout = 86400.
57 !
58 1 idayref = day_ref
59 1 CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
60 !
61 1 CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlon_glo,zx_lon)
62
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (nbp_lon.GT.1) THEN
63
2/2
✓ Branch 0 taken 32 times.
✓ Branch 1 taken 1 times.
33 DO i = 1, nbp_lon
64 32 zx_lon(i,1) = rlon_glo(i+1)
65 33 zx_lon(i,nbp_lat) = rlon_glo(i+1)
66 ENDDO
67 ENDIF
68 !
69 1 CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlat_glo,zx_lat)
70 !
71 CALL histbeg("paramLMDZ_phy.nc", &
72 np,zx_lon(np:np,1), np,zx_lat(1,np:np), &
73 1,1,1,1, &
74 itau_phy, zjulian, dtime, &
75
1/2
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
1 nhori, nid_ctesGCM)
76 !
77 CALL histdef(nid_ctesGCM, "R_ecc", &
78 "Excentricite","-", &
79 1,1,nhori, 1,1,1, -99, 32, &
80 1 "ave(X)", zstophy,zout)
81 !
82 CALL histdef(nid_ctesGCM, "R_peri", &
83 "Equinoxe","-", &
84 1,1,nhori, 1,1,1, -99, 32, &
85 1 "ave(X)", zstophy,zout)
86 !
87 CALL histdef(nid_ctesGCM, "R_incl", &
88 "Inclinaison","deg", &
89 1,1,nhori, 1,1,1, -99, 32, &
90 1 "ave(X)", zstophy,zout)
91 !
92 CALL histdef(nid_ctesGCM, "solaire", &
93 "Constante solaire","W/m2", &
94 1,1,nhori, 1,1,1, -99, 32, &
95 1 "ave(X)", zstophy,zout)
96 !
97 1 IF (iflag_rrtm.EQ.1) THEN
98
2/2
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 1 times.
7 DO ISW=1, NSW
99 6 WRITE(ch1,'(i1)') ISW
100 CALL histdef(nid_ctesGCM, "rsun"//ch1, &
101 "Fraction constante solaire bande "//ch1,"W/m2", &
102 1,1,nhori, 1,1,1, -99, 32, &
103 7 "ave(X)", zstophy,zout)
104 ENDDO
105 ENDIF
106 !
107 CALL histdef(nid_ctesGCM, "co2_ppm", &
108 "Concentration du CO2", "ppm", &
109 1,1,nhori, 1,1,1, -99, 32, &
110 1 "ave(X)", zstophy,zout)
111 !
112 CALL histdef(nid_ctesGCM, "CH4_ppb", &
113 "Concentration du CH4", "ppb", &
114 1,1,nhori, 1,1,1, -99, 32, &
115 1 "ave(X)", zstophy,zout)
116 !
117 CALL histdef(nid_ctesGCM, "N2O_ppb", &
118 "Concentration du N2O", "ppb", &
119 1,1,nhori, 1,1,1, -99, 32, &
120 1 "ave(X)", zstophy,zout)
121 !
122 CALL histdef(nid_ctesGCM, "CFC11_ppt", &
123 "Concentration du CFC11", "ppt", &
124 1,1,nhori, 1,1,1, -99, 32, &
125 1 "ave(X)", zstophy,zout)
126 !
127 CALL histdef(nid_ctesGCM, "CFC12_ppt", &
128 "Concentration du CFC12", "ppt", &
129 1,1,nhori, 1,1,1, -99, 32, &
130 1 "ave(X)", zstophy,zout)
131 !
132 1 CALL histend(nid_ctesGCM)
133
134 ENDIF !(is_mpi_root)
135 !$OMP END MASTER
136
137 1 END SUBROUTINE ini_paramLMDZ_phy
138
139 !=================================================================
140
141 480 SUBROUTINE write_paramLMDZ_phy(itap,nid_ctesGCM,ok_sync)
142
143
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 USE mod_phys_lmdz_mpi_data, ONLY: is_mpi_root
144 USE time_phylmdz_mod, ONLY: day_step_phy, annee_ref, itau_phy, start_time
145 USE mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, klon_glo
146
147 USE iophy
148 USE ioipsl, ONLY: histwrite, histsync
149
150 USE YOESW, ONLY : RSUN
151
152 IMPLICIT NONE
153
154 include "clesphys.h"
155 include "YOMCST.h"
156
157 INTEGER, INTENT(IN) :: itap, nid_ctesGCM
158 LOGICAL, INTENT(IN) :: ok_sync
159
160 INTEGER itau_w, ISW
161 960 INTEGER ndex2d(nbp_lon*nbp_lat)
162 REAL :: zx_tmp_0d(1,1)
163 INTEGER, PARAMETER :: np=1
164
165 CHARACTER*1 ch1
166
167 !$OMP MASTER
168
1/2
✓ Branch 0 taken 480 times.
✗ Branch 1 not taken.
480 IF (is_mpi_root) THEN
169 !
170
2/2
✓ Branch 0 taken 506880 times.
✓ Branch 1 taken 480 times.
507360 ndex2d = 0
171 480 itau_w = itau_phy + itap + int(start_time * day_step_phy)
172 !
173 ! Variables globales
174 !
175
4/4
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 480 times.
✓ Branch 3 taken 480 times.
1920 zx_tmp_0d=R_ecc
176 CALL histwrite(nid_ctesGCM,"R_ecc",itau_w, &
177 480 zx_tmp_0d,np,ndex2d)
178 !
179
4/4
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 480 times.
✓ Branch 3 taken 480 times.
1920 zx_tmp_0d=R_peri
180 CALL histwrite(nid_ctesGCM,"R_peri",itau_w, &
181 480 zx_tmp_0d,np,ndex2d)
182 !
183
4/4
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 480 times.
✓ Branch 3 taken 480 times.
1920 zx_tmp_0d=R_incl
184 CALL histwrite(nid_ctesGCM,"R_incl",itau_w, &
185 480 zx_tmp_0d,np,ndex2d)
186 !
187
4/4
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 480 times.
✓ Branch 3 taken 480 times.
1920 zx_tmp_0d=solaire
188 CALL histwrite(nid_ctesGCM,"solaire",itau_w, &
189 480 zx_tmp_0d,np,ndex2d)
190 !
191
1/2
✓ Branch 0 taken 480 times.
✗ Branch 1 not taken.
480 IF (iflag_rrtm.EQ.1) THEN
192
2/2
✓ Branch 0 taken 2880 times.
✓ Branch 1 taken 480 times.
3360 DO ISW=1, NSW
193 2880 WRITE(ch1,'(i1)') ISW
194
4/4
✓ Branch 0 taken 2880 times.
✓ Branch 1 taken 2880 times.
✓ Branch 2 taken 2880 times.
✓ Branch 3 taken 2880 times.
11520 zx_tmp_0d=RSUN(ISW)
195 CALL histwrite(nid_ctesGCM,"rsun"//ch1,itau_w, &
196 3360 zx_tmp_0d,np,ndex2d)
197 ENDDO
198 ENDIF
199 !
200
4/4
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 480 times.
✓ Branch 3 taken 480 times.
1920 zx_tmp_0d=co2_ppm
201 CALL histwrite(nid_ctesGCM,"co2_ppm",itau_w, &
202 480 zx_tmp_0d,np,ndex2d)
203 !
204
4/4
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 480 times.
✓ Branch 3 taken 480 times.
1920 zx_tmp_0d=CH4_ppb
205 CALL histwrite(nid_ctesGCM,"CH4_ppb",itau_w, &
206 480 zx_tmp_0d,np,ndex2d)
207 !
208
4/4
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 480 times.
✓ Branch 3 taken 480 times.
1920 zx_tmp_0d=N2O_ppb
209 CALL histwrite(nid_ctesGCM,"N2O_ppb",itau_w, &
210 480 zx_tmp_0d,np,ndex2d)
211 !
212
4/4
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 480 times.
✓ Branch 3 taken 480 times.
1920 zx_tmp_0d=CFC11_ppt
213 CALL histwrite(nid_ctesGCM,"CFC11_ppt",itau_w, &
214 480 zx_tmp_0d,np,ndex2d)
215 !
216
4/4
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 480 times.
✓ Branch 3 taken 480 times.
1920 zx_tmp_0d=CFC12_ppt
217 CALL histwrite(nid_ctesGCM,"CFC12_ppt",itau_w, &
218 480 zx_tmp_0d,np,ndex2d)
219 !
220 !=================================================================
221 !
222
1/2
✓ Branch 0 taken 480 times.
✗ Branch 1 not taken.
480 IF (ok_sync) THEN
223 480 call histsync(nid_ctesGCM)
224 ENDIF
225
226 ENDIF !(is_mpi_root) then
227 !$OMP END MASTER
228
229 480 END SUBROUTINE write_paramLMDZ_phy
230
231 END MODULE paramLMDZ_phy_mod
232