/[lmdze]/trunk/libf/dyn3d/dynredem1.f90
ViewVC logotype

Contents of /trunk/libf/dyn3d/dynredem1.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 23 - (show annotations)
Mon Dec 14 15:25:16 2009 UTC (14 years, 5 months ago) by guez
File size: 2161 byte(s)
Split "orografi.f": one file for each procedure. Put the created files
in new directory "Orography".

Removed argument "vcov" of procedure "sortvarc". Removed arguments
"itau" and "time" of procedure "caldyn0". Removed arguments "itau",
"time" and "vcov" of procedure "sortvarc0".

Removed argument "time" of procedure "dynredem1". Removed NetCDF
variable "temps" in files "start.nc" and "restart.nc", because its
value is always 0.

Removed argument "nq" of procedures "iniadvtrac" and "leapfrog". The
number of "tracers read in "traceur.def" must now be equal to "nqmx",
or "nqmx" must equal 4 if there is no file "traceur.def". Replaced
variable "nq" by constant "nqmx" in "leapfrog".

NetCDF variable for ozone field in "coefoz.nc" must now be called
"tro3" instead of "r".

Fixed bug in "zenang".

1 SUBROUTINE dynredem1(fichnom, vcov, ucov, teta, q, masse, ps)
2
3 ! From dyn3d/dynredem.F, v 1.2 2004/06/22 11:45:30
4 ! Ecriture du fichier de redémarrage au format NetCDF
5
6 USE dimens_m, ONLY : iim, jjm, llm, nqmx
7 USE temps, ONLY : itaufin, itau_dyn
8 USE iniadvtrac_m, ONLY : tname
9 use netcdf, only: nf90_write
10 use netcdf95, only: nf95_close, nf95_gw_var, nf95_inq_varid, nf95_open, &
11 nf95_put_var
12
13 IMPLICIT NONE
14
15 CHARACTER(len=*), INTENT (IN) :: fichnom
16 REAL, INTENT (IN) :: vcov(iim + 1, jjm, llm), ucov(iim+1, jjm+1, llm)
17 REAL, INTENT (IN) :: teta(iim+1, jjm+1, llm)
18 REAL, INTENT (IN) :: q(iim+1, jjm+1, llm, nqmx)
19 REAL, INTENT (IN) :: ps(iim+1, jjm+1), masse(iim+1, jjm+1, llm)
20
21 ! Variables local to the procedure:
22 INTEGER nid, nvarid
23 INTEGER iq
24 REAL, pointer:: tab_cntrl(:) ! tableau des paramètres du run
25 INTEGER :: nb = 0
26
27 !---------------------------------------------------------
28
29 PRINT *, 'Call sequence information: dynredem1'
30
31 call nf95_open(fichnom, nf90_write, nid)
32
33 ! Écriture/extension de la coordonnée temps
34 nb = nb + 1
35 call nf95_inq_varid(nid, 'temps', nvarid)
36 call nf95_put_var(nid, nvarid, values=0., start=(/nb/))
37 PRINT *, "Enregistrement pour nb = ", nb
38
39 ! Récriture du tableau de contrôle, "itaufin" n'est plus défini quand
40 ! on passe dans "dynredem0"
41 call nf95_inq_varid(nid, 'controle', nvarid)
42 call nf95_gw_var(nid, nvarid, tab_cntrl)
43 tab_cntrl(31) = real(itau_dyn + itaufin)
44 call nf95_put_var(nid, nvarid, tab_cntrl)
45 deallocate(tab_cntrl) ! pointer
46
47 ! Écriture des champs
48
49 call nf95_inq_varid(nid, 'ucov', nvarid)
50 call nf95_put_var(nid, nvarid, ucov)
51
52 call nf95_inq_varid(nid, 'vcov', nvarid)
53 call nf95_put_var(nid, nvarid, vcov)
54
55 call nf95_inq_varid(nid, 'teta', nvarid)
56 call nf95_put_var(nid, nvarid, teta)
57
58 DO iq = 1, nqmx
59 call nf95_inq_varid(nid, tname(iq), nvarid)
60 call nf95_put_var(nid, nvarid, q(:, :, :, iq))
61 END DO
62
63 call nf95_inq_varid(nid, 'masse', nvarid)
64 call nf95_put_var(nid, nvarid, masse)
65
66 call nf95_inq_varid(nid, 'ps', nvarid)
67 call nf95_put_var(nid, nvarid, ps)
68
69 call nf95_close(nid)
70
71 END SUBROUTINE dynredem1

  ViewVC Help
Powered by ViewVC 1.1.21