| Directory: | ./ |
|---|---|
| File: | dyn/dynredem.f90 |
| Date: | 2022-01-11 19:19:34 |
| Exec | Total | Coverage | |
|---|---|---|---|
| Lines: | 105 | 117 | 89.7% |
| Branches: | 57 | 72 | 79.2% |
| Line | Branch | Exec | Source |
|---|---|---|---|
| 1 | 3 | SUBROUTINE dynredem0(fichnom,iday_end,phis) | |
| 2 | ! | ||
| 3 | !------------------------------------------------------------------------------- | ||
| 4 | ! Write the NetCDF restart file (initialization). | ||
| 5 | !------------------------------------------------------------------------------- | ||
| 6 | USE IOIPSL | ||
| 7 | USE infotrac | ||
| 8 | USE netcdf, ONLY: NF90_CREATE, NF90_DEF_DIM, NF90_INQ_VARID, NF90_GLOBAL, & | ||
| 9 | NF90_CLOSE, NF90_PUT_ATT, NF90_UNLIMITED, NF90_CLOBBER, & | ||
| 10 | NF90_64BIT_OFFSET | ||
| 11 | USE dynredem_mod, ONLY: cre_var, put_var1, put_var2, err, modname, fil | ||
| 12 | USE comvert_mod, ONLY: ap,bp,aps,bps,presnivs,pseudoalt,pa,preff, & | ||
| 13 | nivsig,nivsigs | ||
| 14 | USE comconst_mod, ONLY: cpp, daysec, dtvr, g, kappa, omeg, rad | ||
| 15 | USE logic_mod, ONLY: fxyhypb, ysinus | ||
| 16 | USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy, & | ||
| 17 | taux,tauy | ||
| 18 | USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn, itaufin, start_time | ||
| 19 | USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0 | ||
| 20 | |||
| 21 | IMPLICIT NONE | ||
| 22 | include "dimensions.h" | ||
| 23 | include "paramet.h" | ||
| 24 | include "comgeom2.h" | ||
| 25 | include "description.h" | ||
| 26 | include "iniprint.h" | ||
| 27 | !=============================================================================== | ||
| 28 | ! Arguments: | ||
| 29 | CHARACTER(LEN=*), INTENT(IN) :: fichnom !--- FILE NAME | ||
| 30 | INTEGER, INTENT(IN) :: iday_end !--- | ||
| 31 | REAL, INTENT(IN) :: phis(iip1, jjp1) !--- GROUND GEOPOTENTIAL | ||
| 32 | !=============================================================================== | ||
| 33 | ! Local variables: | ||
| 34 | INTEGER :: iq, l | ||
| 35 | INTEGER, PARAMETER :: length=100 | ||
| 36 | REAL :: tab_cntrl(length) !--- RUN PARAMETERS TABLE | ||
| 37 | ! For NetCDF: | ||
| 38 | CHARACTER(LEN=30) :: unites | ||
| 39 | INTEGER :: indexID | ||
| 40 | INTEGER :: rlonuID, rlonvID, rlatuID, rlatvID | ||
| 41 | INTEGER :: sID, sigID, nID, vID, timID | ||
| 42 | INTEGER :: yyears0, jjour0, mmois0 | ||
| 43 | REAL :: zan0, zjulian, hours | ||
| 44 | !=============================================================================== | ||
| 45 | 1 | modname='dynredem0'; fil=fichnom | |
| 46 | 1 | CALL ymds2ju(annee_ref, 1, iday_end, 0.0, zjulian) | |
| 47 | 1 | CALL ju2ymds(zjulian, yyears0, mmois0, jjour0, hours) | |
| 48 | |||
| 49 | 1 | tab_cntrl(:) = 0. | |
| 50 | 1 | tab_cntrl(1) = REAL(iim) | |
| 51 | 1 | tab_cntrl(2) = REAL(jjm) | |
| 52 | 1 | tab_cntrl(3) = REAL(llm) | |
| 53 | 1 | tab_cntrl(4) = REAL(day_ref) | |
| 54 | 1 | tab_cntrl(5) = REAL(annee_ref) | |
| 55 | 1 | tab_cntrl(6) = rad | |
| 56 | 1 | tab_cntrl(7) = omeg | |
| 57 | 1 | tab_cntrl(8) = g | |
| 58 | 1 | tab_cntrl(9) = cpp | |
| 59 | 1 | tab_cntrl(10) = kappa | |
| 60 | 1 | tab_cntrl(11) = daysec | |
| 61 | 1 | tab_cntrl(12) = dtvr | |
| 62 | 1 | tab_cntrl(13) = etot0 | |
| 63 | 1 | tab_cntrl(14) = ptot0 | |
| 64 | 1 | tab_cntrl(15) = ztot0 | |
| 65 | 1 | tab_cntrl(16) = stot0 | |
| 66 | 1 | tab_cntrl(17) = ang0 | |
| 67 | 1 | tab_cntrl(18) = pa | |
| 68 | 1 | tab_cntrl(19) = preff | |
| 69 | |||
| 70 | ! ..... parameters for zoom ...... | ||
| 71 | 1 | tab_cntrl(20) = clon | |
| 72 | 1 | tab_cntrl(21) = clat | |
| 73 | 1 | tab_cntrl(22) = grossismx | |
| 74 | 1 | tab_cntrl(23) = grossismy | |
| 75 | ! | ||
| 76 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | IF ( fxyhypb ) THEN |
| 77 | 1 | tab_cntrl(24) = 1. | |
| 78 | 1 | tab_cntrl(25) = dzoomx | |
| 79 | 1 | tab_cntrl(26) = dzoomy | |
| 80 | 1 | tab_cntrl(27) = 0. | |
| 81 | 1 | tab_cntrl(28) = taux | |
| 82 | 1 | tab_cntrl(29) = tauy | |
| 83 | ELSE | ||
| 84 | ✗ | tab_cntrl(24) = 0. | |
| 85 | ✗ | tab_cntrl(25) = dzoomx | |
| 86 | ✗ | tab_cntrl(26) = dzoomy | |
| 87 | ✗ | tab_cntrl(27) = 0. | |
| 88 | ✗ | tab_cntrl(28) = 0. | |
| 89 | ✗ | tab_cntrl(29) = 0. | |
| 90 | ✗ | IF( ysinus ) tab_cntrl(27) = 1. | |
| 91 | END IF | ||
| 92 | 1 | tab_cntrl(30) = REAL(iday_end) | |
| 93 | 1 | tab_cntrl(31) = REAL(itau_dyn + itaufin) | |
| 94 | ! start_time: start_time of simulation (not necessarily 0.) | ||
| 95 | 1 | tab_cntrl(32) = start_time | |
| 96 | |||
| 97 | !--- File creation | ||
| 98 | 1 | CALL err(NF90_CREATE(fichnom,IOR(NF90_CLOBBER,NF90_64BIT_OFFSET),nid)) | |
| 99 | |||
| 100 | !--- Some global attributes | ||
| 101 | 1 | CALL err(NF90_PUT_ATT(nid,NF90_GLOBAL,"title","Fichier demarrage dynamique")) | |
| 102 | |||
| 103 | !--- Dimensions | ||
| 104 | 1 | CALL err(NF90_DEF_DIM(nid,"index", length, indexID)) | |
| 105 | 1 | CALL err(NF90_DEF_DIM(nid,"rlonu", iip1, rlonuID)) | |
| 106 | 1 | CALL err(NF90_DEF_DIM(nid,"rlatu", jjp1, rlatuID)) | |
| 107 | 1 | CALL err(NF90_DEF_DIM(nid,"rlonv", iip1, rlonvID)) | |
| 108 | 1 | CALL err(NF90_DEF_DIM(nid,"rlatv", jjm, rlatvID)) | |
| 109 | 1 | CALL err(NF90_DEF_DIM(nid,"sigs", llm, sID)) | |
| 110 | 1 | CALL err(NF90_DEF_DIM(nid,"sig", llmp1, sigID)) | |
| 111 | 1 | CALL err(NF90_DEF_DIM(nid,"temps", NF90_UNLIMITED, timID)) | |
| 112 | |||
| 113 | !--- Define and save invariant fields | ||
| 114 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | CALL put_var1(nid,"controle","Parametres de controle" ,[indexID],tab_cntrl) |
| 115 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | CALL put_var1(nid,"rlonu" ,"Longitudes des points U",[rlonuID],rlonu) |
| 116 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | CALL put_var1(nid,"rlatu" ,"Latitudes des points U" ,[rlatuID],rlatu) |
| 117 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | CALL put_var1(nid,"rlonv" ,"Longitudes des points V",[rlonvID],rlonv) |
| 118 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | CALL put_var1(nid,"rlatv" ,"Latitudes des points V" ,[rlatvID],rlatv) |
| 119 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | CALL put_var1(nid,"nivsigs" ,"Numero naturel des couches s" ,[sID] ,nivsigs) |
| 120 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | CALL put_var1(nid,"nivsig" ,"Numero naturel des couches sigma",[sigID],nivsig) |
| 121 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | CALL put_var1(nid,"ap" ,"Coefficient A pour hybride" ,[sigID],ap) |
| 122 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | CALL put_var1(nid,"bp" ,"Coefficient B pour hybride" ,[sigID],bp) |
| 123 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | CALL put_var1(nid,"presnivs","" ,[sID] ,presnivs) |
| 124 | ! covariant <-> contravariant <-> natural conversion coefficients | ||
| 125 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
|
3 | CALL put_var2(nid,"cu","Coefficient de passage pour U",[rlonuID,rlatuID],cu) |
| 126 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
|
3 | CALL put_var2(nid,"cv","Coefficient de passage pour V",[rlonvID,rlatvID],cv) |
| 127 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
|
3 | CALL put_var2(nid,"aire","Aires de chaque maille" ,[rlonvID,rlatuID],aire) |
| 128 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
|
3 | CALL put_var2(nid,"phisinit","Geopotentiel au sol" ,[rlonvID,rlatuID],phis) |
| 129 | |||
| 130 | !--- Define fields saved later | ||
| 131 | WRITE(unites,"('days since ',i4,'-',i2.2,'-',i2.2,' 00:00:00')"),& | ||
| 132 | 1 | yyears0,mmois0,jjour0 | |
| 133 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | CALL cre_var(nid,"temps","Temps de simulation",[timID],unites) |
| 134 |
2/2✓ Branch 0 taken 4 times.
✓ Branch 1 taken 1 times.
|
5 | CALL cre_var(nid,"ucov" ,"Vitesse U" ,[rlonuID,rlatuID,sID,timID]) |
| 135 |
2/2✓ Branch 0 taken 4 times.
✓ Branch 1 taken 1 times.
|
5 | CALL cre_var(nid,"vcov" ,"Vitesse V" ,[rlonvID,rlatvID,sID,timID]) |
| 136 |
2/2✓ Branch 0 taken 4 times.
✓ Branch 1 taken 1 times.
|
5 | CALL cre_var(nid,"teta" ,"Temperature",[rlonvID,rlatuID,sID,timID]) |
| 137 |
2/2✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
|
6 | DO iq=1,nqtot |
| 138 |
2/2✓ Branch 0 taken 20 times.
✓ Branch 1 taken 5 times.
|
26 | CALL cre_var(nid,tname(iq),ttext(iq),[rlonvID,rlatuID,sID,timID]) |
| 139 | END DO | ||
| 140 |
2/2✓ Branch 0 taken 4 times.
✓ Branch 1 taken 1 times.
|
5 | CALL cre_var(nid,"masse","Masse d air" ,[rlonvID,rlatuID,sID,timID]) |
| 141 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
|
4 | CALL cre_var(nid,"ps" ,"Pression au sol",[rlonvID,rlatuID ,timID]) |
| 142 | 1 | CALL err(NF90_CLOSE (nid)) | |
| 143 | |||
| 144 | 1 | WRITE(lunout,*)TRIM(modname)//': iim,jjm,llm,iday_end',iim,jjm,llm,iday_end | |
| 145 | 1 | WRITE(lunout,*)TRIM(modname)//': rad,omeg,g,cpp,kappa',rad,omeg,g,cpp,kappa | |
| 146 | |||
| 147 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
2 | END SUBROUTINE dynredem0 |
| 148 | ! | ||
| 149 | !------------------------------------------------------------------------------- | ||
| 150 | |||
| 151 | |||
| 152 | !------------------------------------------------------------------------------- | ||
| 153 | ! | ||
| 154 | 2 | SUBROUTINE dynredem1(fichnom,time,vcov,ucov,teta,q,masse,ps) | |
| 155 | ! | ||
| 156 | !------------------------------------------------------------------------------- | ||
| 157 | ! Purpose: Write the NetCDF restart file (append). | ||
| 158 | !------------------------------------------------------------------------------- | ||
| 159 | USE infotrac | ||
| 160 | USE control_mod | ||
| 161 | USE netcdf, ONLY: NF90_OPEN, NF90_NOWRITE, NF90_GET_VAR, NF90_INQ_VARID, & | ||
| 162 | NF90_CLOSE, NF90_WRITE, NF90_PUT_VAR, NF90_NoErr | ||
| 163 | USE dynredem_mod, ONLY: dynredem_write_u, dynredem_write_v, dynredem_read_u, & | ||
| 164 | err, modname, fil, msg | ||
| 165 | USE temps_mod, ONLY: itau_dyn, itaufin | ||
| 166 | |||
| 167 | IMPLICIT NONE | ||
| 168 | include "dimensions.h" | ||
| 169 | include "paramet.h" | ||
| 170 | include "description.h" | ||
| 171 | include "comgeom.h" | ||
| 172 | include "iniprint.h" | ||
| 173 | !=============================================================================== | ||
| 174 | ! Arguments: | ||
| 175 | CHARACTER(LEN=*), INTENT(IN) :: fichnom !-- FILE NAME | ||
| 176 | REAL, INTENT(IN) :: time !-- TIME | ||
| 177 | REAL, INTENT(IN) :: vcov(iip1,jjm, llm) !-- V COVARIANT WIND | ||
| 178 | REAL, INTENT(IN) :: ucov(iip1,jjp1,llm) !-- U COVARIANT WIND | ||
| 179 | REAL, INTENT(IN) :: teta(iip1,jjp1,llm) !-- POTENTIAL TEMPERATURE | ||
| 180 | REAL, INTENT(INOUT) :: q(iip1,jjp1,llm,nqtot) !-- TRACERS | ||
| 181 | REAL, INTENT(IN) :: masse(iip1,jjp1,llm) !-- MASS PER CELL | ||
| 182 | REAL, INTENT(IN) :: ps(iip1,jjp1) !-- GROUND PRESSURE | ||
| 183 | !=============================================================================== | ||
| 184 | ! Local variables: | ||
| 185 | INTEGER :: l, iq, nid, vID, ierr, nid_trac, vID_trac | ||
| 186 | INTEGER, SAVE :: nb=0 | ||
| 187 | INTEGER, PARAMETER :: length=100 | ||
| 188 | REAL :: tab_cntrl(length) ! tableau des parametres du run | ||
| 189 | CHARACTER(LEN=256) :: var, dum | ||
| 190 | LOGICAL :: lread_inca | ||
| 191 | !=============================================================================== | ||
| 192 | |||
| 193 | 1 | modname='dynredem1'; fil=fichnom | |
| 194 | 1 | CALL err(NF90_OPEN(fil,NF90_WRITE,nid),"open",fil) | |
| 195 | |||
| 196 | !--- Write/extend time coordinate | ||
| 197 | 1 | nb = nb + 1 | |
| 198 | 1 | var="temps" | |
| 199 | 1 | CALL err(NF90_INQ_VARID(nid,var,vID),"inq",var) | |
| 200 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | CALL err(NF90_PUT_VAR(nid,vID,[time]),"put",var) |
| 201 | 1 | WRITE(lunout,*)TRIM(modname)//": Saving for ", nb, time | |
| 202 | |||
| 203 | !--- Rewrite control table (itaufin undefined in dynredem0) | ||
| 204 | 1 | var="controle" | |
| 205 | 1 | CALL err(NF90_INQ_VARID(nid,var,vID),"inq",var) | |
| 206 | 1 | CALL err(NF90_GET_VAR(nid,vID,tab_cntrl),"get",var) | |
| 207 | 1 | tab_cntrl(31)=DBLE(itau_dyn + itaufin) | |
| 208 | 1 | CALL err(NF90_INQ_VARID(nid,var,vID),"inq",var) | |
| 209 | 1 | CALL err(NF90_PUT_VAR(nid,vID,tab_cntrl),"put",var) | |
| 210 | |||
| 211 | !--- Save fields | ||
| 212 | 1 | CALL dynredem_write_u(nid,"ucov" ,ucov ,llm) | |
| 213 | 1 | CALL dynredem_write_v(nid,"vcov" ,vcov ,llm) | |
| 214 | 1 | CALL dynredem_write_u(nid,"teta" ,teta ,llm) | |
| 215 | 1 | CALL dynredem_write_u(nid,"masse",masse,llm) | |
| 216 | 1 | CALL dynredem_write_u(nid,"ps" ,ps ,1) | |
| 217 | |||
| 218 | !--- Tracers in file "start_trac.nc" (added by Anne) | ||
| 219 | 1 | lread_inca=.FALSE.; fil="start_trac.nc" | |
| 220 |
2/4✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
|
1 | IF(type_trac=='inca' .OR. type_trac=='inco') INQUIRE(FILE=fil,EXIST=lread_inca) |
| 221 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
|
1 | IF(lread_inca) CALL err(NF90_OPEN(fil,NF90_NOWRITE,nid_trac),"open") |
| 222 | |||
| 223 | !--- Save tracers | ||
| 224 |
2/2✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
|
6 | DO iq=1,nqtot; var=tname(iq); ierr=-1 |
| 225 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
|
5 | IF(lread_inca) THEN !--- Possibly read from "start_trac.nc" |
| 226 | ✗ | fil="start_trac.nc" | |
| 227 | ✗ | ierr=NF90_INQ_VARID(nid_trac,var,vID_trac) | |
| 228 | ✗ | dum='inq'; IF(ierr==NF90_NoErr) dum='fnd' | |
| 229 | ✗ | WRITE(lunout,*)msg(dum,var) | |
| 230 | |||
| 231 | |||
| 232 | ✗ | IF(ierr==NF90_NoErr) CALL dynredem_read_u(nid_trac,var,q(:,:,:,iq),llm) | |
| 233 | END IF | ||
| 234 |
1/2✓ Branch 0 taken 5 times.
✗ Branch 1 not taken.
|
5 | fil=fichnom |
| 235 | 6 | CALL dynredem_write_u(nid,var,q(:,:,:,iq),llm) | |
| 236 | END DO | ||
| 237 | 1 | CALL err(NF90_CLOSE(nid),"close") | |
| 238 | 1 | fil="start_trac.nc" | |
| 239 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
|
1 | IF(lread_inca) CALL err(NF90_CLOSE(nid_trac),"close") |
| 240 | |||
| 241 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | END SUBROUTINE dynredem1 |
| 242 | |||
| 243 |