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

Last change on this file since 1477 was 1422, checked in by milmd, 10 years ago

In GENERIC, MARS and COMMON models replace some include files by modules (usefull for decoupling physics with dynamics).

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