source: trunk/LMDZ.GENERIC/libf/phystd/writediagspecIR.F @ 537

Last change on this file since 537 was 533, checked in by jleconte, 13 years ago
  • Mesh area now present in 1d diag files.
  • Spectral Bandwidth included in the diagspec files
  • Correction of a initialzation bug on day_step and ecritphy in rcm1d
File size: 8.9 KB
RevLine 
[305]1      subroutine writediagspecIR(ngrid,nom,titre,unite,dim,px)
2
3!  Ecriture de variables diagnostiques au choix dans la physique
4!  dans un fichier NetCDF nomme  'diagfi'. Ces variables peuvent etre
5!  3d (ex : temperature), 2d (ex : temperature de surface), ou
6!  0d (pour un scalaire qui ne depend que du temps : ex : la longitude
7!  solaire)
8!  Dans la version 2000, la periode d'ecriture est celle de
9!  "ecritphy " regle dans le fichier de controle de run :  run.def
10!
11!    writediagfi peut etre appele de n'importe quelle subroutine
12!    de la physique, plusieurs fois. L'initialisation et la creation du
13!    fichier se fait au tout premier appel.
14!
15! WARNING : les variables dynamique (u,v,t,q,ps)
16!  sauvees par writediagfi avec une
17! date donnee sont legerement differentes que dans le fichier histoire car
18! on ne leur a pas encore ajoute de la dissipation et de la physique !!!
19! IL est  RECOMMANDE d'ajouter les tendance physique a ces variables
20! avant l'ecriture dans diagfi (cf. physiq.F)
21
22!
23!  parametres (input) :
24!  ----------
25!      ngrid : nombres de point ou est calcule la physique
26!                (ngrid = 2+(jjm-1)*iim - 1/jjm)
27!                 (= nlon ou klon dans la physique terrestre)
28!     
29!      unit : unite logique du fichier de sortie (toujours la meme)
30!      nom  : nom de la variable a sortir (chaine de caracteres)
31!      titre: titre de la variable (chaine de caracteres)
32!      unite : unite de la variable (chaine de caracteres)
33!      px : variable a sortir (real 0, 2, ou 3d)
34!      dim : dimension de px : 0, 2, ou 3 dimensions
35!
36!=================================================================
37!
38!      This is a modified version that accepts spectrally varying input
39!      RW (2010)
40!
41!=================================================================
42 
43! Addition by RW (2010) to allow OLR to be saved in .nc format
44      use radinc_h, only : L_NSPECTI
45
46      implicit none
47
48! Commons
49#include "dimensions.h"
50#include "dimphys.h"
51#include "paramet.h"
52#include "control.h"
53#include "comvert.h"
54#include "comgeom.h"
55#include "description.h"
56#include "netcdf.inc"
57#include "temps.h"
58#include "surfdat.h"
[533]59#include "callkeys.h"
[305]60
61! Arguments on input:
62      integer ngrid
63      character (len=*) :: nom,titre,unite
64      integer dim
65      real px(ngrid,L_NSPECTI)
66
67! Local variables:
68
69!      real dx3(iip1,jjp1,llm) ! to store a 3D data set
70!      real dx2(iip1,jjp1)     ! to store a 2D (surface) data set
71!      real dx0
72
73      real date
74
75      REAL phis(ip1jmp1)
76
77      integer irythme
78      integer ierr
79      integer iq
80      integer i,j,l,zmax , ig0
81
82      integer zitau
83      character firstnom*20
84      SAVE firstnom
85      SAVE zitau
86      SAVE date
87      data firstnom /'1234567890'/
88      data zitau /0/
89
90! Ajouts
91      integer, save :: ntime=0
92      integer :: idim,varid
93      integer :: nid
94      character (len =50):: fichnom
95      integer, dimension(4) :: id
96      integer, dimension(4) :: edges,corner
97
98! added by RDW for OLR output
99       real dx3(iip1,jjp1,L_NSPECTI) ! to store the data set
100
101
102!***************************************************************
103!Sortie des variables au rythme voulu
104
[533]105      irythme = int(ecritphy)*iradia ! sortie au rythme de ecritphy*iradia
106!EM+JL if the spetra need to be output more frequently, need to define a ecritSpec...
[305]107!     irythme = iphysiq  ! sortie a tous les pas physique
108
[533]109
[305]110!***************************************************************
111
112! The following test is here to enforce that writediagfi is not used with the
113! 1D version of the GCM
[526]114!not anymore (JL12)
115      if (ngrid.eq.-1) return
[305]116     
117c     nom=trim((nom))
118c     unite=trim((unite))
119c     titre=trim((titre))
120
121! Initialisation of 'firstnom' and create/open the "diagfi.nc" NetCDF file
122! ------------------------------------------------------------------------
123! (Au tout premier appel de la subroutine durant le run.)
124
125      fichnom="diagspecIR.nc"
126
127      if (firstnom.eq.'1234567890') then ! .true. for the very first call
128      !  to this subroutine; now set 'firstnom'
129         firstnom = nom
130         ! just to be sure, check that firstnom is large enough to hold nom
131         if (len_trim(firstnom).lt.len_trim(nom)) then
132           write(*,*) "writediagfi: Error !!!"
133           write(*,*) "   firstnom string not long enough!!"
134           write(*,*) "   increase its size to at least ",len_trim(nom)
135           stop
136         endif
137
138         ! Create the NetCDF file
139         ierr = NF_CREATE(fichnom, NF_CLOBBER, nid)
140         ! Define the 'Time' dimension
141         ierr = nf_def_dim(nid,"Time",NF_UNLIMITED,idim)
142         ! Define the 'Time' variable
143#ifdef NC_DOUBLE
144         ierr = NF_DEF_VAR (nid, "Time", NF_DOUBLE, 1, idim,varid)
145#else
146         ierr = NF_DEF_VAR (nid, "Time", NF_FLOAT, 1, idim,varid)
147#endif
148         ! Add a long_name attribute
149         ierr = NF_PUT_ATT_TEXT (nid, varid, "long_name",
150     .          4,"Time")
151         ! Add a units attribute
152         ierr = NF_PUT_ATT_TEXT(nid, varid,'units',29,
153     .          "days since 0000-00-0 00:00:00")
154         ! Switch out of NetCDF Define mode
155         ierr = NF_ENDDEF(nid)
156
157         ! write "header" of file (longitudes, latitudes, geopotential, ...)
158         call gr_fi_dyn(1,ngrid,iip1,jjp1,phisfi,phis)
159!         call iniwrite(nid,day_ini,phis)
160         call iniwrite_specIR(nid,day_ini,phis)
161
162         zitau = -1 ! initialize zitau
163      else
164         ! Open the NetCDF file
165         ierr = NF_OPEN(fichnom,NF_WRITE,nid)
166      endif ! if (firstnom.eq.'1234567890')
167
168! Increment time index 'zitau' if it is the "firstcall" (at given time level)
169! to writediagfi
170!------------------------------------------------------------------------
171      if (nom.eq.firstnom) then
172          zitau = zitau + iphysiq
173      end if
174
175!--------------------------------------------------------
176! Write the variables to output file if it's time to do so
177!--------------------------------------------------------
178
179      if ( MOD(zitau+1,irythme) .eq.0.) then
180
181! Compute/write/extend 'Time' coordinate (date given in days)
182! (done every "first call" (at given time level) to writediagfi)
183! Note: date is incremented as 1 step ahead of physics time
184!       (like the 'histoire' outputs)
185!--------------------------------------------------------
186
187        if (nom.eq.firstnom) then
188
189        ! We have identified a "first call" (at given date)
190           ntime=ntime+1 ! increment # of stored time steps
191           ! compute corresponding date (in days and fractions thereof)
192           date= float (zitau +1)/float (day_step)
193           ! Get NetCDF ID of 'Time' variable
194           ierr= NF_INQ_VARID(nid,"Time",varid)
195
196           !print*,'in writediagfi_spec.F, time=',varid
197
198           ! Write (append) the new date to the 'Time' array
199#ifdef NC_DOUBLE
200           ierr= NF_PUT_VARA_DOUBLE(nid,varid,ntime,1,date)
201#else
202           ierr= NF_PUT_VARA_REAL(nid,varid,ntime,1,date)
203#endif
204           if (ierr.ne.NF_NOERR) then
205              write(*,*) "***** PUT_VAR matter in writediagspec_nc"
206              write(*,*) "***** with time"
207              write(*,*) 'ierr=', ierr   
208c             call abort
209           endif
210
211           write(6,*)'WRITEDIAGSPEC: date= ', date
212        end if ! of if (nom.eq.firstnom)
213
214
215 
216!Case of a 3D variable
217!---------------------
218        if (dim.eq.3) then
219
220!         recast (copy) variable from physics grid to dynamics grid
221           DO l=1,L_NSPECTI
222             DO i=1,iip1
223                dx3(i,1,l)=px(1,l)
224                dx3(i,jjp1,l)=px(ngrid,l)
225             ENDDO
226             DO j=2,jjm
227                ig0= 1+(j-2)*iim
228                DO i=1,iim
229                   dx3(i,j,l)=px(ig0+i,l)
230                ENDDO
231                dx3(iip1,j,l)=dx3(1,j,l)
232             ENDDO
233           ENDDO
234
235! name of the variable
236           ierr= NF_INQ_VARID(nid,nom,varid)
237           if (ierr /= NF_NOERR) then
238! corresponding dimensions
239              ierr= NF_INQ_DIMID(nid,"longitude",id(1))
240              ierr= NF_INQ_DIMID(nid,"latitude",id(2))
[526]241              ierr= NF_INQ_DIMID(nid,"IR Wavenumber",id(3))
[305]242              ierr= NF_INQ_DIMID(nid,"Time",id(4))
243
244! Create the variable if it doesn't exist yet
245
246              write (*,*) "=========================="
247              write (*,*) "DIAGSPEC: creating variable ",nom
248              call def_var(nid,nom,titre,unite,4,id,varid,ierr)
249
250           endif
251
252           corner(1)=1
253           corner(2)=1
254           corner(3)=1
255           corner(4)=ntime
256
257           edges(1)=iip1
258           edges(2)=jjp1
259           edges(3)=L_NSPECTI
260           edges(4)=1
261#ifdef NC_DOUBLE
262           ierr= NF_PUT_VARA_DOUBLE(nid,varid,corner,edges,dx3)
263#else
264           ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx3)
265#endif
266
267           if (ierr.ne.NF_NOERR) then
268              write(*,*) "***** PUT_VAR problem in writediagspec"
269              write(*,*) "***** with ",nom
270              write(*,*) 'ierr=', ierr
271             call abort
272           endif
273
274        endif ! of if (dim.eq.3) elseif(dim.eq.2)...
275
276      endif ! of if ( MOD(zitau+1,irythme) .eq.0.)
277
278      ierr= NF_CLOSE(nid)
279
280      end
Note: See TracBrowser for help on using the repository browser.