/[lmdze]/trunk/Sources/phylmd/phyredem.f
ViewVC logotype

Diff of /trunk/Sources/phylmd/phyredem.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/libf/phylmd/phyredem.f revision 3 by guez, Wed Feb 27 13:16:39 2008 UTC trunk/phylmd/phyredem.f revision 99 by guez, Wed Jul 2 18:39:15 2014 UTC
# Line 1  Line 1 
1  !  module phyredem_m
2  ! $Header: /home/cvsroot/LMDZ4/libf/phylmd/phyredem.F,v 1.3 2005/05/25 13:10:09 fairhead Exp $  
3  !    IMPLICIT NONE
4  c  
5        SUBROUTINE phyredem (fichnom,dtime,radpas,  contains
6       .           rlat,rlon, pctsrf,tsol,tsoil,  
7  cIM "slab" ocean    SUBROUTINE phyredem(fichnom, rlat, rlon, pctsrf, tsol, tsoil, tslab, &
8       .           tslab,seaice,         seaice, qsurf, qsol, snow, albedo, alblw, evap, rain_fall, snow_fall, &
9       .           qsurf,qsol,snow,         solsw, sollw, fder, radsol, frugs, agesno, zmea, zstd, zsig, zgam, &
10       .           albedo, alblw, evap, rain_fall, snow_fall,         zthe, zpic, zval, t_ancien, q_ancien, rnebcon, ratqs, clwcon, &
11       .           solsw, sollw,fder,         run_off_lic_0, sig1, w01)
12       .           radsol,frugs,agesno,  
13       .           zmea,zstd,zsig,zgam,zthe,zpic,zval,rugsrel,      ! From phylmd/phyredem.F, version 1.3 2005/05/25 13:10:09
14       .           t_ancien, q_ancien, rnebcon, ratqs, clwcon,      ! Author: Z. X. Li (LMD/CNRS)
15       .           run_off_lic_0)      ! Date: 1993/08/18
16        use dimens_m      ! Objet : écriture de l'état de démarrage ou redémarrage pour la physique
17        use indicesol  
18        use dimphy      USE dimphy, ONLY: klev, klon, zmasq
19        use conf_gcm_m      USE dimsoil, ONLY: nsoilmx
20        use dimsoil      USE indicesol, ONLY: is_lic, is_oce, is_sic, is_ter, nbsrf
21        use temps      USE netcdf, ONLY: nf90_clobber, nf90_global, nf90_float
22        use clesphys      USE netcdf95, ONLY: nf95_create, nf95_put_att, nf95_def_dim, &
23        IMPLICIT none           nf95_def_var, nf95_enddef, nf95_redef, nf95_put_var, nf95_close
24  c======================================================================      USE temps, ONLY: itau_phy
25  c Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818  
26  c Objet: Ecriture de l'etat de redemarrage pour la physique      CHARACTER(len=*), INTENT(IN):: fichnom
27  c======================================================================      REAL, INTENT(IN):: rlat(klon), rlon(klon)
28        include "netcdf.inc"      REAL, INTENT(IN):: pctsrf(klon, nbsrf)
29  c======================================================================      REAL, INTENT(IN):: tsol(:, :) ! (klon, nbsrf)
30        CHARACTER*(*) fichnom      REAL, INTENT(IN):: tsoil(:, :, :) ! (klon, nsoilmx, nbsrf)
31        REAL dtime      REAL, INTENT(IN):: tslab(:), seaice(:) ! (klon) slab ocean
32        INTEGER radpas      REAL, INTENT(IN):: qsurf(:, :) ! (klon, nbsrf)
33        REAL, intent(in):: rlat(klon), rlon(klon)      REAL, intent(in):: qsol(:) ! (klon)
34        REAL tsol(klon,nbsrf)      REAL, INTENT(IN):: snow(klon, nbsrf)
35        REAL tsoil(klon,nsoilmx,nbsrf)      REAL, INTENT(IN):: albedo(klon, nbsrf)
36  cIM "slab" ocean      REAL, INTENT(IN):: alblw(klon, nbsrf)
37        REAL tslab(klon), seaice(klon)      REAL, INTENT(IN):: evap(klon, nbsrf)
38        REAL qsurf(klon,nbsrf)      REAL, INTENT(IN):: rain_fall(klon)
39        REAL qsol(klon)      REAL, INTENT(IN):: snow_fall(klon)
40        REAL snow(klon,nbsrf)      REAL, INTENT(IN):: solsw(klon)
41        REAL albedo(klon,nbsrf)      REAL, INTENT(IN):: sollw(klon)
42  cIM BEG      REAL, INTENT(IN):: fder(klon)
43        REAL alblw(klon,nbsrf)      REAL, INTENT(IN):: radsol(klon)
44  cIM END      REAL, INTENT(IN):: frugs(klon, nbsrf)
45        REAL evap(klon,nbsrf)      REAL, INTENT(IN):: agesno(klon, nbsrf)
46        REAL rain_fall(klon)      REAL, INTENT(IN):: zmea(klon)
47        REAL snow_fall(klon)      REAL, intent(in):: zstd(klon)
48        real solsw(klon)      REAL, intent(in):: zsig(klon)
49        real sollw(klon)      REAL, intent(in):: zgam(klon)
50        real fder(klon)      REAL, intent(in):: zthe(klon)
51        REAL radsol(klon)      REAL, intent(in):: zpic(klon)
52        REAL frugs(klon,nbsrf)      REAL, intent(in):: zval(klon)
53        REAL agesno(klon,nbsrf)      REAL, intent(in):: t_ancien(klon, klev), q_ancien(klon, klev)
54        REAL zmea(klon)      REAL, intent(in):: rnebcon(klon, klev), ratqs(klon, klev)
55        REAL zstd(klon)      REAL, intent(in):: clwcon(klon, klev)
56        REAL zsig(klon)      REAL, intent(in):: run_off_lic_0(klon)
57        REAL zgam(klon)      real, intent(in):: sig1(klon, klev) ! section adiabatic updraft
58        REAL zthe(klon)  
59        REAL zpic(klon)      real, intent(in):: w01(klon, klev)
60        REAL zval(klon)      ! vertical velocity within adiabatic updraft
61        REAL rugsrel(klon)  
62        REAL pctsrf(klon, nbsrf)      ! Local:
63        REAL t_ancien(klon,klev), q_ancien(klon,klev)  
64        real clwcon(klon,klev),rnebcon(klon,klev),ratqs(klon,klev)      INTEGER ncid, idim2, idim3
65        REAL run_off_lic_0(klon)      integer varid, varid_run_off_lic_0, varid_sig1, varid_w01, varid_rlon
66  c      integer varid_rlat, varid_zmasq, varid_fter, varid_flic, varid_foce
67        INTEGER nid, nvarid, idim1, idim2, idim3      integer varid_fsic
68        INTEGER ierr      INTEGER isoil, nsrf
69        INTEGER length      CHARACTER(len=7) str7
70        PARAMETER (length=100)      CHARACTER(len=2) str2
71        REAL tab_cntrl(length)  
72  c      !------------------------------------------------------------
73        INTEGER isoil, nsrf  
74        CHARACTER*7 str7      PRINT *, 'Call sequence information: phyredem'
75        CHARACTER*2 str2      CALL nf95_create(fichnom, nf90_clobber, ncid)
76  c  
77        print *, "Call sequence information: phyredem"      call nf95_put_att(ncid, nf90_global, 'title', &
78        ierr = NF_CREATE(fichnom, NF_CLOBBER, nid)           'Fichier redémarrage physique')
79        IF (ierr.NE.NF_NOERR) THEN      call nf95_put_att(ncid, nf90_global, "itau_phy", itau_phy)
80          write(6,*)' Pb d''ouverture du fichier '//fichnom  
81          write(6,*)' ierr = ', ierr      call nf95_def_dim(ncid, 'points_physiques', klon, idim2)
82          STOP 1      call nf95_def_dim(ncid, 'klev', klev, idim3)
83        ENDIF  
84  c      call nf95_def_var(ncid, 'longitude', nf90_float, idim2, varid_rlon)
85        ierr = NF_PUT_ATT_TEXT (nid, NF_GLOBAL, "title", 28,      call nf95_def_var(ncid, 'latitude', nf90_float, idim2, varid_rlat)
86       .                       "Fichier redemmarage physique")  
87  c      call nf95_def_var(ncid, 'masque', nf90_float, idim2, varid_zmasq)
88        ierr = NF_DEF_DIM (nid, "index", length, idim1)      call nf95_put_att(ncid, varid_zmasq, 'title', 'masque terre mer')
89        ierr = NF_DEF_DIM (nid, "points_physiques", klon, idim2)  
90        ierr = NF_DEF_DIM (nid, "horizon_vertical", klon*klev, idim3)      ! Fractions de chaque sous-surface
91  c  
92        ierr = NF_ENDDEF(nid)      call nf95_def_var(ncid, 'FTER', nf90_float, idim2, varid_fter)
93  c      call nf95_put_att(ncid, varid_fter, 'title', 'fraction de continent')
94        DO ierr = 1, length  
95           tab_cntrl(ierr) = 0.0      call nf95_def_var(ncid, 'FLIC', nf90_float, idim2, varid_flic)
96        ENDDO      call nf95_put_att(ncid, varid_flic, 'title', 'fraction glace de terre')
97        tab_cntrl(1) = dtime  
98        tab_cntrl(2) = radpas      call nf95_def_var(ncid, 'FOCE', nf90_float, idim2, varid_foce)
99        tab_cntrl(3) = co2_ppm      call nf95_put_att(ncid, varid_foce, 'title', 'fraction ocean')
100        tab_cntrl(4) = solaire  
101        tab_cntrl(5) = iflag_con      call nf95_def_var(ncid, 'FSIC', nf90_float, idim2, varid_fsic)
102        tab_cntrl(6) = nbapp_rad      call nf95_put_att(ncid, varid_fsic, 'title', 'fraction glace mer')
103    
104        IF( cycle_diurne ) tab_cntrl( 7 ) = 1.      call nf95_enddef(ncid)
105        IF(   soil_model ) tab_cntrl( 8 ) = 1.  
106        IF(     new_oliq ) tab_cntrl( 9 ) = 1.      call nf95_put_var(ncid, varid_rlon, rlon)
107        IF(     ok_orodr ) tab_cntrl(10 ) = 1.      call nf95_put_var(ncid, varid_rlat, rlat)
108        IF(     ok_orolf ) tab_cntrl(11 ) = 1.      call nf95_put_var(ncid, varid_zmasq, zmasq)
109        call nf95_put_var(ncid, varid_fter, pctsrf(:, is_ter))
110        tab_cntrl(13) = day_end      call nf95_put_var(ncid, varid_flic, pctsrf(:, is_lic))
111        tab_cntrl(14) = annee_ref      call nf95_put_var(ncid, varid_foce, pctsrf(:, is_oce))
112        tab_cntrl(15) = itau_phy      call nf95_put_var(ncid, varid_fsic, pctsrf(:, is_sic))
113  c  
114        ierr = NF_REDEF (nid)      DO nsrf = 1, nbsrf
115        ierr = NF_DEF_VAR (nid, "controle", NF_FLOAT, 1, idim1,nvarid)         IF (nsrf<=99) THEN
116        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 22,            WRITE (str2, '(i2.2)') nsrf
117       .                        "Parametres de controle")            call nf95_redef(ncid)
118        ierr = NF_ENDDEF(nid)            call nf95_def_var(ncid, 'TS'//str2, nf90_float, idim2, varid)
119        ierr = NF_PUT_VAR_REAL (nid,nvarid,tab_cntrl)            call nf95_put_att(ncid, varid, 'title', &
120  c                 'Temperature de surface No.'//str2)
121        ierr = NF_REDEF (nid)            call nf95_enddef(ncid)
122        ierr = NF_DEF_VAR (nid, "longitude", NF_FLOAT, 1, idim2,nvarid)         ELSE
123        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 32,            PRINT *, 'Trop de sous-mailles'
124       .                        "Longitudes de la grille physique")            STOP 1
125        ierr = NF_ENDDEF(nid)         END IF
126        ierr = NF_PUT_VAR_REAL (nid,nvarid,rlon)         call nf95_put_var(ncid, varid, tsol(:, nsrf))
127  c      END DO
128        ierr = NF_REDEF (nid)  
129        ierr = NF_DEF_VAR (nid, "latitude", NF_FLOAT, 1, idim2,nvarid)      DO nsrf = 1, nbsrf
130        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 31,         DO isoil = 1, nsoilmx
131       .                        "Latitudes de la grille physique")            IF (isoil<=99 .AND. nsrf<=99) THEN
132        ierr = NF_ENDDEF(nid)               WRITE (str7, '(i2.2, "srf", i2.2)') isoil, nsrf
133        ierr = NF_PUT_VAR_REAL (nid,nvarid,rlat)               call nf95_redef(ncid)
134  c               call nf95_def_var(ncid, 'Tsoil'//str7, nf90_float, idim2, varid)
135  C PB ajout du masque terre/mer               call nf95_put_att(ncid, varid, 'title', &
136  C                    'Temperature du sol No.'//str7)
137        ierr = NF_REDEF (nid)               call nf95_enddef(ncid)
138        ierr = NF_DEF_VAR (nid, "masque", NF_FLOAT, 1, idim2,nvarid)            ELSE
139        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 16,               PRINT *, 'Trop de couches'
140       .                        "masque terre mer")               STOP 1
141        ierr = NF_ENDDEF(nid)            END IF
142        ierr = NF_PUT_VAR_REAL (nid,nvarid,zmasq)            call nf95_put_var(ncid, varid, tsoil(:, isoil, nsrf))
143  c BP ajout des fraction de chaque sous-surface         END DO
144  C      END DO
145  C 1. fraction de terre  
146  C      !IM "slab" ocean
147        ierr = NF_REDEF (nid)      call nf95_redef(ncid)
148        ierr = NF_DEF_VAR (nid, "FTER", NF_FLOAT, 1, idim2,nvarid)      call nf95_def_var(ncid, 'TSLAB', nf90_float, idim2, varid)
149        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 21,      call nf95_put_att(ncid, varid, 'title', &
150       .                        "fraction de continent")           'Ecart de la SST (pour slab-ocean)')
151        ierr = NF_ENDDEF(nid)      call nf95_enddef(ncid)
152        ierr = NF_PUT_VAR_REAL (nid,nvarid,pctsrf(1 : klon, is_ter))      call nf95_put_var(ncid, varid, tslab)
153  C  
154  C 2. Fraction de glace de terre      call nf95_redef(ncid)
155  C      call nf95_def_var(ncid, 'SEAICE', nf90_float, idim2, varid)
156        ierr = NF_REDEF (nid)      call nf95_put_att(ncid, varid, 'title', &
157        ierr = NF_DEF_VAR (nid, "FLIC", NF_FLOAT, 1, idim2,nvarid)           'Glace de mer kg/m2 (pour slab-ocean)')
158        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 24,      call nf95_enddef(ncid)
159       .                        "fraction glace de terre")      call nf95_put_var(ncid, varid, seaice)
160        ierr = NF_ENDDEF(nid)  
161        ierr = NF_PUT_VAR_REAL (nid,nvarid,pctsrf(1 : klon, is_lic))      DO nsrf = 1, nbsrf
162  C         IF (nsrf<=99) THEN
163  C 3. fraction ocean            WRITE (str2, '(i2.2)') nsrf
164  C            call nf95_redef(ncid)
165        ierr = NF_REDEF (nid)            call nf95_def_var(ncid, 'QS'//str2, nf90_float, idim2, varid)
166        ierr = NF_DEF_VAR (nid, "FOCE", NF_FLOAT, 1, idim2,nvarid)            call nf95_put_att(ncid, varid, 'title', &
167        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 14,                 'Humidite de surface No.'//str2)
168       .                        "fraction ocean")            call nf95_enddef(ncid)
169        ierr = NF_ENDDEF(nid)         ELSE
170        ierr = NF_PUT_VAR_REAL (nid,nvarid,pctsrf(1 : klon, is_oce))            PRINT *, 'Trop de sous-mailles'
171  C            STOP 1
172  C 4. Fraction glace de mer         END IF
173  C         call nf95_put_var(ncid, varid, qsurf(:, nsrf))
174        ierr = NF_REDEF (nid)      END DO
175        ierr = NF_DEF_VAR (nid, "FSIC", NF_FLOAT, 1, idim2,nvarid)  
176        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 18,      call nf95_redef(ncid)
177       .                        "fraction glace mer")      call nf95_def_var(ncid, 'QSOL', nf90_float, idim2, varid)
178        ierr = NF_ENDDEF(nid)      call nf95_put_att(ncid, varid, 'title', 'Eau dans le sol (mm)')
179        ierr = NF_PUT_VAR_REAL (nid,nvarid,pctsrf(1 : klon, is_sic))      call nf95_enddef(ncid)
180  C      call nf95_put_var(ncid, varid, qsol)
181  C  
182  c      DO nsrf = 1, nbsrf
183        DO nsrf = 1, nbsrf         IF (nsrf<=99) THEN
184          IF (nsrf.LE.99) THEN            WRITE (str2, '(i2.2)') nsrf
185          WRITE(str2,'(i2.2)') nsrf            call nf95_redef(ncid)
186          ierr = NF_REDEF (nid)            call nf95_def_var(ncid, 'ALBE'//str2, nf90_float, idim2, varid)
187          ierr = NF_DEF_VAR (nid, "TS"//str2, NF_FLOAT, 1, idim2,nvarid)            call nf95_put_att(ncid, varid, 'title', &
188          ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 28,                 'albedo de surface No.'//str2)
189       .                        "Temperature de surface No."//str2)            call nf95_enddef(ncid)
190          ierr = NF_ENDDEF(nid)         ELSE
191          ELSE            PRINT *, 'Trop de sous-mailles'
192          PRINT*, "Trop de sous-mailles"            STOP 1
193          stop 1         END IF
194          ENDIF         call nf95_put_var(ncid, varid, albedo(:, nsrf))
195          ierr = NF_PUT_VAR_REAL (nid,nvarid,tsol(1,nsrf))      END DO
196        ENDDO  
197  c      !IM BEG albedo LW
198        DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
199        DO isoil=1, nsoilmx         IF (nsrf<=99) THEN
200          IF (isoil.LE.99 .AND. nsrf.LE.99) THEN            WRITE (str2, '(i2.2)') nsrf
201          WRITE(str7,'(i2.2,"srf",i2.2)') isoil,nsrf            call nf95_redef(ncid)
202          ierr = NF_REDEF (nid)            call nf95_def_var(ncid, 'ALBLW'//str2, nf90_float, idim2, varid)
203          ierr = NF_DEF_VAR (nid, "Tsoil"//str7,NF_FLOAT,1,idim2,nvarid)            call nf95_put_att(ncid, varid, 'title', &
204          ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 29,                 'albedo LW de surface No.'//str2)
205       .                        "Temperature du sol No."//str7)            call nf95_enddef(ncid)
206          ierr = NF_ENDDEF(nid)         ELSE
207          ELSE            PRINT *, 'Trop de sous-mailles'
208          PRINT*, "Trop de couches"            STOP 1
209          stop 1         END IF
210          ENDIF         call nf95_put_var(ncid, varid, alblw(:, nsrf))
211          ierr = NF_PUT_VAR_REAL (nid,nvarid,tsoil(1,isoil,nsrf))      END DO
212        ENDDO      !IM END albedo LW
213        ENDDO  
214  c      DO nsrf = 1, nbsrf
215  cIM "slab" ocean         IF (nsrf<=99) THEN
216        ierr = NF_REDEF (nid)            WRITE (str2, '(i2.2)') nsrf
217        ierr = NF_DEF_VAR (nid, "TSLAB", NF_FLOAT, 1, idim2,nvarid)            call nf95_redef(ncid)
218        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 33,            call nf95_def_var(ncid, 'EVAP'//str2, nf90_float, idim2, varid)
219       .                        "Ecart de la SST (pour slab-ocean)")            call nf95_put_att(ncid, varid, 'title', &
220        ierr = NF_ENDDEF(nid)                 'Evaporation de surface No.'//str2)
221        ierr = NF_PUT_VAR_REAL (nid,nvarid,tslab)            call nf95_enddef(ncid)
222  c         ELSE
223        ierr = NF_REDEF (nid)            PRINT *, 'Trop de sous-mailles'
224        ierr = NF_DEF_VAR (nid, "SEAICE", NF_FLOAT, 1, idim2,nvarid)            STOP 1
225        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 33,         END IF
226       .                        "Glace de mer kg/m2 (pour slab-ocean)")         call nf95_put_var(ncid, varid, evap(:, nsrf))
227        ierr = NF_ENDDEF(nid)      END DO
228        ierr = NF_PUT_VAR_REAL (nid,nvarid,seaice)  
229  c      DO nsrf = 1, nbsrf
230        DO nsrf = 1, nbsrf         IF (nsrf<=99) THEN
231          IF (nsrf.LE.99) THEN            WRITE (str2, '(i2.2)') nsrf
232          WRITE(str2,'(i2.2)') nsrf            call nf95_redef(ncid)
233          ierr = NF_REDEF (nid)            call nf95_def_var(ncid, 'SNOW'//str2, nf90_float, idim2, varid)
234          ierr = NF_DEF_VAR (nid,"QS"//str2,NF_FLOAT,1,idim2,nvarid)            call nf95_put_att(ncid, varid, 'title', &
235          ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 25,                 'Neige de surface No.'//str2)
236       .                        "Humidite de surface No."//str2)            call nf95_enddef(ncid)
237          ierr = NF_ENDDEF(nid)         ELSE
238          ELSE            PRINT *, 'Trop de sous-mailles'
239          PRINT*, "Trop de sous-mailles"            STOP 1
240          stop 1         END IF
241          ENDIF         call nf95_put_var(ncid, varid, snow(:, nsrf))
242        ierr = NF_PUT_VAR_REAL (nid,nvarid,qsurf(1,nsrf))      END DO
243        END DO  
244  C      call nf95_redef(ncid)
245        ierr = NF_REDEF (nid)      call nf95_def_var(ncid, 'RADS', nf90_float, idim2, varid)
246        ierr = NF_DEF_VAR (nid,"QSOL",NF_FLOAT,1,idim2,nvarid)      call nf95_put_att(ncid, varid, 'title', &
247        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 20,           'Rayonnement net a la surface')
248       .    "Eau dans le sol (mm)")      call nf95_enddef(ncid)
249        ierr = NF_ENDDEF(nid)      call nf95_put_var(ncid, varid, radsol)
250        ierr = NF_PUT_VAR_REAL (nid,nvarid,qsol)  
251  c      call nf95_redef(ncid)
252        DO nsrf = 1, nbsrf      call nf95_def_var(ncid, 'solsw', nf90_float, idim2, varid)
253          IF (nsrf.LE.99) THEN      call nf95_put_att(ncid, varid, 'title', &
254          WRITE(str2,'(i2.2)') nsrf           'Rayonnement solaire a la surface')
255          ierr = NF_REDEF (nid)      call nf95_enddef(ncid)
256          ierr = NF_DEF_VAR (nid,"ALBE"//str2,NF_FLOAT,1,idim2,nvarid)      call nf95_put_var(ncid, varid, solsw)
257          ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 23,  
258       .                        "albedo de surface No."//str2)      call nf95_redef(ncid)
259          ierr = NF_ENDDEF(nid)      call nf95_def_var(ncid, 'sollw', nf90_float, idim2, varid)
260          ELSE      call nf95_put_att(ncid, varid, 'title', &
261          PRINT*, "Trop de sous-mailles"           'Rayonnement IF a la surface')
262          stop 1      call nf95_enddef(ncid)
263          ENDIF      call nf95_put_var(ncid, varid, sollw)
264        ierr = NF_PUT_VAR_REAL (nid,nvarid,albedo(1,nsrf))  
265        ENDDO      call nf95_redef(ncid)
266        call nf95_def_var(ncid, 'fder', nf90_float, idim2, varid)
267  cIM BEG albedo LW      call nf95_put_att(ncid, varid, 'title', 'Derive de flux')
268          DO nsrf = 1, nbsrf      call nf95_enddef(ncid)
269          IF (nsrf.LE.99) THEN      call nf95_put_var(ncid, varid, fder)
270          WRITE(str2,'(i2.2)') nsrf  
271          ierr = NF_REDEF (nid)      call nf95_redef(ncid)
272          ierr = NF_DEF_VAR (nid,"ALBLW"//str2,NF_FLOAT,1,idim2,nvarid)      call nf95_def_var(ncid, 'rain_f', nf90_float, idim2, varid)
273          ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 23,      call nf95_put_att(ncid, varid, 'title', 'precipitation liquide')
274       .                        "albedo LW de surface No."//str2)      call nf95_enddef(ncid)
275          ierr = NF_ENDDEF(nid)      call nf95_put_var(ncid, varid, rain_fall)
276          ELSE  
277          PRINT*, "Trop de sous-mailles"      call nf95_redef(ncid)
278          stop 1      call nf95_def_var(ncid, 'snow_f', nf90_float, idim2, varid)
279          ENDIF      call nf95_put_att(ncid, varid, 'title', 'precipitation solide')
280        ierr = NF_PUT_VAR_REAL (nid,nvarid,alblw(1,nsrf))      call nf95_enddef(ncid)
281        ENDDO      call nf95_put_var(ncid, varid, snow_fall)
282  cIM END albedo LW  
283  c      DO nsrf = 1, nbsrf
284        DO nsrf = 1, nbsrf         IF (nsrf<=99) THEN
285          IF (nsrf.LE.99) THEN            WRITE (str2, '(i2.2)') nsrf
286          WRITE(str2,'(i2.2)') nsrf            call nf95_redef(ncid)
287          ierr = NF_REDEF (nid)            call nf95_def_var(ncid, 'RUG'//str2, nf90_float, idim2, varid)
288          ierr = NF_DEF_VAR (nid,"EVAP"//str2,NF_FLOAT,1,idim2,nvarid)            call nf95_put_att(ncid, varid, 'title', &
289          ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 28,                 'rugosite de surface No.'//str2)
290       .                        "Evaporation de surface No."//str2)            call nf95_enddef(ncid)
291          ierr = NF_ENDDEF(nid)         ELSE
292          ELSE            PRINT *, 'Trop de sous-mailles'
293          PRINT*, "Trop de sous-mailles"            STOP 1
294          stop 1         END IF
295          ENDIF         call nf95_put_var(ncid, varid, frugs(:, nsrf))
296        ierr = NF_PUT_VAR_REAL (nid,nvarid,evap(1,nsrf))      END DO
297        ENDDO  
298        DO nsrf = 1, nbsrf
299  c         IF (nsrf<=99) THEN
300        DO nsrf = 1, nbsrf            WRITE (str2, '(i2.2)') nsrf
301          IF (nsrf.LE.99) THEN            call nf95_redef(ncid)
302          WRITE(str2,'(i2.2)') nsrf            call nf95_def_var(ncid, 'AGESNO'//str2, nf90_float, idim2, varid)
303          ierr = NF_REDEF (nid)            call nf95_put_att(ncid, varid, 'title', &
304          ierr = NF_DEF_VAR (nid,"SNOW"//str2,NF_FLOAT,1,idim2,nvarid)                 'Age de la neige surface No.'//str2)
305          ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 22,            call nf95_enddef(ncid)
306       .                        "Neige de surface No."//str2)         ELSE
307          ierr = NF_ENDDEF(nid)            PRINT *, 'Trop de sous-mailles'
308          ELSE            STOP 1
309          PRINT*, "Trop de sous-mailles"         END IF
310          stop 1         call nf95_put_var(ncid, varid, agesno(:, nsrf))
311          ENDIF      END DO
312        ierr = NF_PUT_VAR_REAL (nid,nvarid,snow(1,nsrf))  
313        ENDDO      call nf95_redef(ncid)
314        call nf95_def_var(ncid, 'ZMEA', nf90_float, idim2, varid)
315  c      call nf95_enddef(ncid)
316        ierr = NF_REDEF (nid)      call nf95_put_var(ncid, varid, zmea)
317        ierr = NF_DEF_VAR (nid, "RADS", NF_FLOAT, 1, idim2,nvarid)  
318        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 28,      call nf95_redef(ncid)
319       .                        "Rayonnement net a la surface")      call nf95_def_var(ncid, 'ZSTD', nf90_float, idim2, varid)
320        ierr = NF_ENDDEF(nid)      call nf95_enddef(ncid)
321        ierr = NF_PUT_VAR_REAL (nid,nvarid,radsol)      call nf95_put_var(ncid, varid, zstd)
322  c      call nf95_redef(ncid)
323        ierr = NF_REDEF (nid)      call nf95_def_var(ncid, 'ZSIG', nf90_float, idim2, varid)
324        ierr = NF_DEF_VAR (nid, "solsw", NF_FLOAT, 1, idim2,nvarid)      call nf95_enddef(ncid)
325        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 32,      call nf95_put_var(ncid, varid, zsig)
326       .                        "Rayonnement solaire a la surface")      call nf95_redef(ncid)
327        ierr = NF_ENDDEF(nid)      call nf95_def_var(ncid, 'ZGAM', nf90_float, idim2, varid)
328        ierr = NF_PUT_VAR_REAL (nid,nvarid,solsw)      call nf95_enddef(ncid)
329  c      call nf95_put_var(ncid, varid, zgam)
330        ierr = NF_REDEF (nid)      call nf95_redef(ncid)
331        ierr = NF_DEF_VAR (nid, "sollw", NF_FLOAT, 1, idim2,nvarid)      call nf95_def_var(ncid, 'ZTHE', nf90_float, idim2, varid)
332        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 27,      call nf95_enddef(ncid)
333       .                        "Rayonnement IF a la surface")      call nf95_put_var(ncid, varid, zthe)
334        ierr = NF_ENDDEF(nid)      call nf95_redef(ncid)
335        ierr = NF_PUT_VAR_REAL (nid,nvarid,sollw)      call nf95_def_var(ncid, 'ZPIC', nf90_float, idim2, varid)
336  c      call nf95_enddef(ncid)
337        ierr = NF_REDEF (nid)      call nf95_put_var(ncid, varid, zpic)
338        ierr = NF_DEF_VAR (nid, "fder", NF_FLOAT, 1, idim2,nvarid)      call nf95_redef(ncid)
339        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 14,      call nf95_def_var(ncid, 'ZVAL', nf90_float, idim2, varid)
340       .                        "Derive de flux")      call nf95_enddef(ncid)
341        ierr = NF_ENDDEF(nid)      call nf95_put_var(ncid, varid, zval)
342        ierr = NF_PUT_VAR_REAL (nid,nvarid,fder)  
343  c      call nf95_redef(ncid)
344        ierr = NF_REDEF (nid)      call nf95_def_var(ncid, 'TANCIEN', nf90_float, (/idim2, idim3/), varid)
345        ierr = NF_DEF_VAR (nid, "rain_f", NF_FLOAT, 1, idim2,nvarid)      call nf95_enddef(ncid)
346        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 21,      call nf95_put_var(ncid, varid, t_ancien)
347       .                        "precipitation liquide")  
348        ierr = NF_ENDDEF(nid)      call nf95_redef(ncid)
349        ierr = NF_PUT_VAR_REAL (nid,nvarid,rain_fall)      call nf95_def_var(ncid, 'QANCIEN', nf90_float, (/idim2, idim3/), varid)
350  c      call nf95_enddef(ncid)
351        ierr = NF_REDEF (nid)      call nf95_put_var(ncid, varid, q_ancien)
352        ierr = NF_DEF_VAR (nid, "snow_f", NF_FLOAT, 1, idim2,nvarid)  
353        ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 20,      call nf95_redef(ncid)
354       .                        "precipitation solide")      call nf95_def_var(ncid, 'RUGMER', nf90_float, idim2, varid)
355        ierr = NF_ENDDEF(nid)      call nf95_put_att(ncid, varid, 'title', &
356        ierr = NF_PUT_VAR_REAL (nid,nvarid,snow_fall)           'Longueur de rugosite sur mer')
357  c      call nf95_enddef(ncid)
358        DO nsrf = 1, nbsrf      call nf95_put_var(ncid, varid, frugs(:, is_oce))
359          IF (nsrf.LE.99) THEN  
360          WRITE(str2,'(i2.2)') nsrf      call nf95_redef(ncid)
361          ierr = NF_REDEF (nid)      call nf95_def_var(ncid, 'CLWCON', nf90_float, idim2, varid)
362          ierr = NF_DEF_VAR (nid,"RUG"//str2,NF_FLOAT,1,idim2,nvarid)      call nf95_put_att(ncid, varid, 'title', 'Eau liquide convective')
363          ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 23,      call nf95_enddef(ncid)
364       .                        "rugosite de surface No."//str2)      call nf95_put_var(ncid, varid, clwcon(:, 1))
365          ierr = NF_ENDDEF(nid)  
366          ELSE      call nf95_redef(ncid)
367          PRINT*, "Trop de sous-mailles"      call nf95_def_var(ncid, 'RNEBCON', nf90_float, idim2, varid)
368          stop 1      call nf95_put_att(ncid, varid, 'title', 'Nebulosite convective')
369          ENDIF      call nf95_enddef(ncid)
370        ierr = NF_PUT_VAR_REAL (nid,nvarid,frugs(1,nsrf))      call nf95_put_var(ncid, varid, rnebcon(:, 1))
371        ENDDO  
372  c      call nf95_redef(ncid)
373        DO nsrf = 1, nbsrf      call nf95_def_var(ncid, 'RATQS', nf90_float, idim2, varid)
374          IF (nsrf.LE.99) THEN      call nf95_put_att(ncid, varid, 'title', 'Ratqs')
375              WRITE(str2,'(i2.2)') nsrf      call nf95_enddef(ncid)
376              ierr = NF_REDEF (nid)      call nf95_put_var(ncid, varid, ratqs(:, 1))
377              ierr = NF_DEF_VAR (nid,"AGESNO"//str2,NF_FLOAT,1,idim2  
378       $          ,nvarid)      call nf95_redef(ncid)
379              ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 15,      call nf95_def_var(ncid, 'RUNOFFLIC0', nf90_float, idim2, &
380       .                        "Age de la neige surface No."//str2)           varid_run_off_lic_0)
381              ierr = NF_ENDDEF(nid)      call nf95_put_att(ncid, varid_run_off_lic_0, 'title', 'Runofflic0')
382          ELSE  
383              PRINT*, "Trop de sous-mailles"      call nf95_def_var(ncid, 'sig1', nf90_float, (/idim2, idim3/), varid_sig1)
384              stop 1      call nf95_put_att(ncid, varid_sig1, 'long_name', &
385          ENDIF           'section adiabatic updraft')
386        ierr = NF_PUT_VAR_REAL (nid,nvarid,agesno(1,nsrf))  
387        ENDDO      call nf95_def_var(ncid, 'w01', nf90_float, (/idim2, idim3/), varid_w01)
388  c      call nf95_put_att(ncid, varid_w01, 'long_name', &
389        ierr = NF_REDEF (nid)           'vertical velocity within adiabatic updraft')
390        ierr = NF_DEF_VAR (nid, "ZMEA", NF_FLOAT, 1, idim2,nvarid)  
391        ierr = NF_ENDDEF(nid)      call nf95_enddef(ncid)
392        ierr = NF_PUT_VAR_REAL (nid,nvarid,zmea)  
393  c      call nf95_put_var(ncid, varid_run_off_lic_0, run_off_lic_0)
394        ierr = NF_REDEF (nid)      call nf95_put_var(ncid, varid_sig1, sig1)
395        ierr = NF_DEF_VAR (nid, "ZSTD", NF_FLOAT, 1, idim2,nvarid)      call nf95_put_var(ncid, varid_w01, w01)
396        ierr = NF_ENDDEF(nid)  
397        ierr = NF_PUT_VAR_REAL (nid,nvarid,zstd)      call nf95_close(ncid)
398        ierr = NF_REDEF (nid)  
399        ierr = NF_DEF_VAR (nid, "ZSIG", NF_FLOAT, 1, idim2,nvarid)    END SUBROUTINE phyredem
400        ierr = NF_ENDDEF(nid)  
401        ierr = NF_PUT_VAR_REAL (nid,nvarid,zsig)  end module phyredem_m
       ierr = NF_REDEF (nid)  
       ierr = NF_DEF_VAR (nid, "ZGAM", NF_FLOAT, 1, idim2,nvarid)  
       ierr = NF_ENDDEF(nid)  
       ierr = NF_PUT_VAR_REAL (nid,nvarid,zgam)  
       ierr = NF_REDEF (nid)  
       ierr = NF_DEF_VAR (nid, "ZTHE", NF_FLOAT, 1, idim2,nvarid)  
       ierr = NF_ENDDEF(nid)  
       ierr = NF_PUT_VAR_REAL (nid,nvarid,zthe)  
       ierr = NF_REDEF (nid)  
       ierr = NF_DEF_VAR (nid, "ZPIC", NF_FLOAT, 1, idim2,nvarid)  
       ierr = NF_ENDDEF(nid)  
       ierr = NF_PUT_VAR_REAL (nid,nvarid,zpic)  
       ierr = NF_REDEF (nid)  
       ierr = NF_DEF_VAR (nid, "ZVAL", NF_FLOAT, 1, idim2,nvarid)  
       ierr = NF_ENDDEF(nid)  
       ierr = NF_PUT_VAR_REAL (nid,nvarid,zval)  
       ierr = NF_REDEF (nid)  
       ierr = NF_DEF_VAR (nid, "RUGSREL", NF_FLOAT, 1, idim2,nvarid)  
       ierr = NF_ENDDEF(nid)  
       ierr = NF_PUT_VAR_REAL (nid,nvarid,rugsrel)  
 c  
       ierr = NF_REDEF (nid)  
       ierr = NF_DEF_VAR (nid, "TANCIEN", NF_FLOAT, 1, idim3,nvarid)  
       ierr = NF_ENDDEF(nid)  
       ierr = NF_PUT_VAR_REAL (nid,nvarid,t_ancien)  
 c  
       ierr = NF_REDEF (nid)  
       ierr = NF_DEF_VAR (nid, "QANCIEN", NF_FLOAT, 1, idim3,nvarid)  
       ierr = NF_ENDDEF(nid)  
       ierr = NF_PUT_VAR_REAL (nid,nvarid,q_ancien)  
 c  
       ierr = NF_REDEF (nid)  
       ierr = NF_DEF_VAR (nid, "RUGMER", NF_FLOAT, 1, idim2,nvarid)  
       ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 28,  
      .                        "Longueur de rugosite sur mer")  
       ierr = NF_ENDDEF(nid)  
       ierr = NF_PUT_VAR_REAL (nid,nvarid,frugs(1,is_oce))  
 c  
       ierr = NF_REDEF (nid)  
       ierr = NF_DEF_VAR (nid, "CLWCON", NF_FLOAT, 1, idim2,nvarid)  
       ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 28,  
      .                        "Eau liquide convective")  
       ierr = NF_ENDDEF(nid)  
       ierr = NF_PUT_VAR_REAL (nid,nvarid,clwcon)  
 c  
       ierr = NF_REDEF (nid)  
       ierr = NF_DEF_VAR (nid, "RNEBCON", NF_FLOAT, 1, idim2,nvarid)  
       ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 28,  
      .                        "Nebulosite convective")  
       ierr = NF_ENDDEF(nid)  
       ierr = NF_PUT_VAR_REAL (nid,nvarid,rnebcon)  
 c  
       ierr = NF_REDEF (nid)  
       ierr = NF_DEF_VAR (nid, "RATQS", NF_FLOAT, 1, idim2,nvarid)  
       ierr = NF_PUT_ATT_TEXT(nid,nvarid,"title", 5,  
      .                        "Ratqs")  
       ierr = NF_ENDDEF(nid)  
       ierr = NF_PUT_VAR_REAL (nid,nvarid,ratqs)  
 c  
 c run_off_lic_0  
 c  
       ierr = NF_REDEF (nid)  
       ierr=NF_DEF_VAR(nid,"RUNOFFLIC0",NF_FLOAT, 1,idim2,nvarid)  
       ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 10,  
      .                        "Runofflic0")  
       ierr = NF_ENDDEF(nid)  
       ierr = NF_PUT_VAR_REAL (nid,nvarid,run_off_lic_0)  
 c  
 c  
       ierr = NF_CLOSE(nid)  
 c  
       RETURN  
       END  

Legend:
Removed from v.3  
changed lines
  Added in v.99

  ViewVC Help
Powered by ViewVC 1.1.21