source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/writediagspecVI.F @ 222

Last change on this file since 222 was 222, checked in by ymipsl, 10 years ago

Creating temporary dynamico/lmdz/saturn branche

YM

File size: 9.8 KB
Line 
1      subroutine writediagspecVI(ngrid,nom,titre,unite,dimpx,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!      dimpx : 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 OSR to be saved in .nc format
44      use radinc_h, only : L_NSPECTV
45!      USE surfdat_h
46#ifdef CPP_PARA
47      use mod_phys_lmdz_para, only : is_mpi_root, is_master, gather
48      use mod_grid_phy_lmdz, only : klon_glo, Grid1Dto2D_glo
49#endif
50      use control_mod, only: ecritphy, iphysiq, day_step
51
52      implicit none
53
54! Commons
55#include "dimensions.h"
56#include "dimphys.h"
57#include "paramet.h"
58!#include "control.h"
59#include "comvert.h"
60#include "comgeom.h"
61#include "netcdf.inc"
62#include "temps.h"
63#include "callkeys.h"
64
65! Arguments on input:
66      integer ngrid
67      character (len=*) :: nom,titre,unite
68      integer dimpx
69      real px(ngrid,L_NSPECTV)
70
71! Local variables:
72
73!      real dx3(iip1,jjp1,llm) ! to store a 3D data set
74!      real dx2(iip1,jjp1)     ! to store a 2D (surface) data set
75!      real dx0
76
77      real date
78
79!      REAL phis(ip1jmp1)
80
81      integer irythme
82      integer ierr
83      integer iq
84      integer i,j,l,zmax , ig0
85
86      integer zitau
87      character firstnom*20
88      SAVE firstnom
89      SAVE zitau
90      SAVE date
91      data firstnom /'1234567890'/
92      data zitau /0/
93
94! Ajouts
95      integer, save :: ntime=0
96      integer :: idim,varid
97      integer :: nid
98      character (len =50):: fichnom
99      integer, dimension(4) :: id
100      integer, dimension(4) :: edges,corner
101
102! added by RDW for OSR output
103       real dx3(iip1,jjp1,L_NSPECTV) ! to store the data set
104
105#ifdef CPP_PARA
106! Added to work in parallel mode
107      real dx3_glop(klon_glo,L_NSPECTV)
108      real dx3_glo(iim,jjp1,L_NSPECTV) ! to store a global 3D data set
109#else
110      logical,parameter :: is_master=.true.
111      logical,parameter :: is_mpi_root=.true.
112#endif
113
114!***************************************************************
115!Sortie des variables au rythme voulu
116
117      irythme = ecritphy*iradia ! sortie au rythme de ecritphy
118!EM+JL if the spetra need to be output more frequently, need to define a ecritSpec...
119!     irythme = iphysiq  ! sortie a tous les pas physique
120
121!***************************************************************
122
123! Initialisation of 'firstnom' and create/open the "diagfi.nc" NetCDF file
124! ------------------------------------------------------------------------
125! (Au tout premier appel de la subroutine durant le run.)
126
127      fichnom="diagspecVI.nc"
128
129      if (firstnom.eq.'1234567890') then ! .true. for the very first call
130      !  to this subroutine; now set 'firstnom'
131         firstnom = nom
132         ! just to be sure, check that firstnom is large enough to hold nom
133         if (len_trim(firstnom).lt.len_trim(nom)) then
134           write(*,*) "writediagfi: Error !!!"
135           write(*,*) "   firstnom string not long enough!!"
136           write(*,*) "   increase its size to at least ",len_trim(nom)
137           stop
138         endif
139
140         ! Create the NetCDF file
141         if (is_master) then
142         ierr = NF_CREATE(fichnom, NF_CLOBBER, nid)
143         ! Define the 'Time' dimension
144         ierr = nf_def_dim(nid,"Time",NF_UNLIMITED,idim)
145         ! Define the 'Time' variable
146#ifdef NC_DOUBLE
147         ierr = NF_DEF_VAR (nid, "Time", NF_DOUBLE, 1, idim,varid)
148#else
149         ierr = NF_DEF_VAR (nid, "Time", NF_FLOAT, 1, idim,varid)
150#endif
151         ! Add a long_name attribute
152         ierr = NF_PUT_ATT_TEXT (nid, varid, "long_name",
153     .          4,"Time")
154         ! Add a units attribute
155         ierr = NF_PUT_ATT_TEXT(nid, varid,'units',29,
156     .          "days since 0000-00-0 00:00:00")
157         ! Switch out of NetCDF Define mode
158         ierr = NF_ENDDEF(nid)
159
160         ! write "header" of file (longitudes, latitudes, geopotential, ...)
161!         call gr_fi_dyn(1,ngrid,iip1,jjp1,phisfi,phis)
162!         call iniwrite(nid,day_ini,phis)
163         call iniwrite_specVI(nid,day_ini)
164         endif ! of if (is_master)
165
166         zitau = -1 ! initialize zitau
167      else
168         if (is_master) then
169           ! Open the NetCDF file
170           ierr = NF_OPEN(fichnom,NF_WRITE,nid)
171         endif
172      endif ! if (firstnom.eq.'1234567890')
173
174! Increment time index 'zitau' if it is the "firstcall" (at given time level)
175! to writediagfi
176!------------------------------------------------------------------------
177      if (nom.eq.firstnom) then
178          zitau = zitau + iphysiq
179      end if
180
181!--------------------------------------------------------
182! Write the variables to output file if it's time to do so
183!--------------------------------------------------------
184
185      if ( MOD(zitau+1,irythme) .eq.0.) then
186
187! Compute/write/extend 'Time' coordinate (date given in days)
188! (done every "first call" (at given time level) to writediagfi)
189! Note: date is incremented as 1 step ahead of physics time
190!       (like the 'histoire' outputs)
191!--------------------------------------------------------
192
193        if (nom.eq.firstnom) then
194
195        ! We have identified a "first call" (at given date)
196           ntime=ntime+1 ! increment # of stored time steps
197           ! compute corresponding date (in days and fractions thereof)
198           date= float (zitau +1)/float (day_step)
199
200           if (is_master) then
201             ! Get NetCDF ID of 'Time' variable
202             ierr= NF_INQ_VARID(nid,"Time",varid)
203
204             ! Write (append) the new date to the 'Time' array
205#ifdef NC_DOUBLE
206             ierr= NF_PUT_VARA_DOUBLE(nid,varid,ntime,1,date)
207#else
208             ierr= NF_PUT_VARA_REAL(nid,varid,ntime,1,date)
209#endif
210             if (ierr.ne.NF_NOERR) then
211              write(*,*) "***** PUT_VAR matter in writediagspec_nc"
212              write(*,*) "***** with time"
213              write(*,*) 'ierr=', ierr   
214c             call abort
215             endif
216
217             write(6,*)'WRITEDIAGSPEC: date= ', date
218           endif ! of if (is_master)
219        end if ! of if (nom.eq.firstnom)
220
221
222 
223!Case of a 3D variable
224!---------------------
225        if (dimpx.eq.3) then
226
227!         A. Recast (copy) variable from physics grid to dynamics grid
228#ifdef CPP_PARA
229  ! gather field on a "global" (without redundant longitude) array
230          call Gather(px,dx3_glop)
231!$OMP MASTER
232          if (is_mpi_root) then
233            call Grid1Dto2D_glo(dx3_glop,dx3_glo)
234            ! copy dx3_glo() to dx3(:) and add redundant longitude
235            dx3(1:iim,:,:)=dx3_glo(1:iim,:,:)
236            dx3(iip1,:,:)=dx3(1,:,:)
237          endif
238!$OMP END MASTER
239!$OMP BARRIER
240#else
241           DO l=1,L_NSPECTV
242             DO i=1,iip1
243                dx3(i,1,l)=px(1,l)
244                dx3(i,jjp1,l)=px(ngrid,l)
245             ENDDO
246             DO j=2,jjm
247                ig0= 1+(j-2)*iim
248                DO i=1,iim
249                   dx3(i,j,l)=px(ig0+i,l)
250                ENDDO
251                dx3(iip1,j,l)=dx3(1,j,l)
252             ENDDO
253           ENDDO
254#endif
255
256!         B. Write (append) the variable to the NetCDF file
257          if (is_master) then
258
259! name of the variable
260           ierr= NF_INQ_VARID(nid,nom,varid)
261           if (ierr /= NF_NOERR) then
262! corresponding dimensions
263              ierr= NF_INQ_DIMID(nid,"longitude",id(1))
264              ierr= NF_INQ_DIMID(nid,"latitude",id(2))
265              ierr= NF_INQ_DIMID(nid,"VI Wavenumber",id(3))
266              ierr= NF_INQ_DIMID(nid,"Time",id(4))
267
268! Create the variable if it doesn't exist yet
269
270              write (*,*) "=========================="
271              write (*,*) "DIAGSPEC: creating variable ",nom
272              call def_var(nid,nom,titre,unite,4,id,varid,ierr)
273
274           endif
275
276           corner(1)=1
277           corner(2)=1
278           corner(3)=1
279           corner(4)=ntime
280
281           edges(1)=iip1
282           edges(2)=jjp1
283           edges(3)=L_NSPECTV
284           edges(4)=1
285#ifdef NC_DOUBLE
286           ierr= NF_PUT_VARA_DOUBLE(nid,varid,corner,edges,dx3)
287#else
288           ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx3)
289#endif
290
291           if (ierr.ne.NF_NOERR) then
292              write(*,*) "***** PUT_VAR problem in writediagspec"
293              write(*,*) "***** with ",nom
294              write(*,*) 'ierr=', ierr
295             call abort
296           endif
297
298          endif ! of if (is_master)
299
300        endif ! of if (dimpx.eq.3)
301
302      endif ! of if ( MOD(zitau+1,irythme) .eq.0.)
303
304      ! Close the NetCDF file
305      if (is_master) then
306        ierr= NF_CLOSE(nid)
307      endif
308
309      end
Note: See TracBrowser for help on using the repository browser.