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

Last change on this file since 1152 was 993, checked in by emillour, 12 years ago

Generic GCM:

  • Some more cleanup in dynamics:
    • Moved "start2archive" (and auxilliary routines) to phystd
    • removed unused (obsolete) testharm.F , para_netcdf.h , readhead_NC.F , angtot.h from dyn3d
    • removed obsolete addit.F (and change corresponding lines in gcm)
    • remove unused "description.h" (and many places where it was "included")

EM

File size: 9.8 KB
RevLine 
[965]1      subroutine writediagspecIR(ngrid,nom,titre,unite,dimpx,px)
[305]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)
[965]34!      dimpx : dimension de px : 0, 2, ou 3 dimensions
[305]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
[965]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
[305]50
51      implicit none
52
53! Commons
54#include "dimensions.h"
55#include "dimphys.h"
56#include "paramet.h"
57#include "control.h"
58#include "comvert.h"
59#include "comgeom.h"
60#include "netcdf.inc"
61#include "temps.h"
[533]62#include "callkeys.h"
[305]63
64! Arguments on input:
[965]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)
[305]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
[965]78!      REAL phis(ip1jmp1)
[305]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
93! Ajouts
94      integer, save :: ntime=0
95      integer :: idim,varid
96      integer :: nid
97      character (len =50):: fichnom
98      integer, dimension(4) :: id
99      integer, dimension(4) :: edges,corner
100
101! added by RDW for OLR output
102       real dx3(iip1,jjp1,L_NSPECTI) ! to store the data set
103
[965]104#ifdef CPP_PARA
105! Added to work in parallel mode
106      real dx3_glop(klon_glo,L_NSPECTI)
107      real dx3_glo(iim,jjp1,L_NSPECTI) ! to store a global 3D data set
108#else
109      logical,parameter :: is_master=.true.
110      logical,parameter :: is_mpi_root=.true.
111#endif
[305]112
113!***************************************************************
114!Sortie des variables au rythme voulu
115
[533]116      irythme = int(ecritphy)*iradia ! sortie au rythme de ecritphy*iradia
117!EM+JL if the spetra need to be output more frequently, need to define a ecritSpec...
[305]118!     irythme = iphysiq  ! sortie a tous les pas physique
119
[533]120
[305]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="diagspecIR.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
[965]134           write(*,*) "writediagspecIR: Error !!!"
[305]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
[965]141         if (is_master) then
[305]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
[965]160!         call gr_fi_dyn(1,size(phisfi_glo),iip1,jjp1,phisfi_glo,phis)
161         ! write "header" of file (longitudes, latitudes, area, ...)
162         call iniwrite_specIR(nid,day_ini)
163         endif ! of if (is_master)
[305]164
165         zitau = -1 ! initialize zitau
166      else
[965]167         if (is_master) then
168           ! Open the NetCDF file
169           ierr = NF_OPEN(fichnom,NF_WRITE,nid)
170         endif
[305]171      endif ! if (firstnom.eq.'1234567890')
172
173! Increment time index 'zitau' if it is the "firstcall" (at given time level)
174! to writediagfi
175!------------------------------------------------------------------------
176      if (nom.eq.firstnom) then
177          zitau = zitau + iphysiq
178      end if
179
180!--------------------------------------------------------
181! Write the variables to output file if it's time to do so
182!--------------------------------------------------------
183
184      if ( MOD(zitau+1,irythme) .eq.0.) then
185
186! Compute/write/extend 'Time' coordinate (date given in days)
187! (done every "first call" (at given time level) to writediagfi)
188! Note: date is incremented as 1 step ahead of physics time
189!       (like the 'histoire' outputs)
190!--------------------------------------------------------
191
192        if (nom.eq.firstnom) then
193
194        ! We have identified a "first call" (at given date)
195           ntime=ntime+1 ! increment # of stored time steps
196           ! compute corresponding date (in days and fractions thereof)
197           date= float (zitau +1)/float (day_step)
198
[965]199           if (is_master) then
200             ! Get NetCDF ID of 'Time' variable
201             ierr= NF_INQ_VARID(nid,"Time",varid)
[305]202
[965]203             ! Write (append) the new date to the 'Time' array
[305]204#ifdef NC_DOUBLE
[965]205             ierr= NF_PUT_VARA_DOUBLE(nid,varid,ntime,1,date)
[305]206#else
[965]207             ierr= NF_PUT_VARA_REAL(nid,varid,ntime,1,date)
[305]208#endif
[965]209             if (ierr.ne.NF_NOERR) then
[305]210              write(*,*) "***** PUT_VAR matter in writediagspec_nc"
211              write(*,*) "***** with time"
212              write(*,*) 'ierr=', ierr   
213c             call abort
[965]214             endif
[305]215
[965]216             write(6,*)'WRITEDIAGSPEC: date= ', date
217           endif ! of if (is_master)
[305]218        end if ! of if (nom.eq.firstnom)
219
220
221 
222!Case of a 3D variable
223!---------------------
[965]224        if (dimpx.eq.3) then
[305]225
[965]226!         A. Recast (copy) variable from physics grid to dynamics grid
227#ifdef CPP_PARA
228  ! gather field on a "global" (without redundant longitude) array
229          call Gather(px,dx3_glop)
230!$OMP MASTER
231          if (is_mpi_root) then
232            call Grid1Dto2D_glo(dx3_glop,dx3_glo)
233            ! copy dx3_glo() to dx3(:) and add redundant longitude
234            dx3(1:iim,:,:)=dx3_glo(1:iim,:,:)
235            dx3(iip1,:,:)=dx3(1,:,:)
236          endif
237!$OMP END MASTER
238!$OMP BARRIER
239#else
[305]240           DO l=1,L_NSPECTI
241             DO i=1,iip1
242                dx3(i,1,l)=px(1,l)
243                dx3(i,jjp1,l)=px(ngrid,l)
244             ENDDO
245             DO j=2,jjm
246                ig0= 1+(j-2)*iim
247                DO i=1,iim
248                   dx3(i,j,l)=px(ig0+i,l)
249                ENDDO
250                dx3(iip1,j,l)=dx3(1,j,l)
251             ENDDO
252           ENDDO
[965]253#endif
[305]254
[965]255!         B. Write (append) the variable to the NetCDF file
256          if (is_master) then
257
[305]258! name of the variable
259           ierr= NF_INQ_VARID(nid,nom,varid)
260           if (ierr /= NF_NOERR) then
261! corresponding dimensions
262              ierr= NF_INQ_DIMID(nid,"longitude",id(1))
263              ierr= NF_INQ_DIMID(nid,"latitude",id(2))
[526]264              ierr= NF_INQ_DIMID(nid,"IR Wavenumber",id(3))
[305]265              ierr= NF_INQ_DIMID(nid,"Time",id(4))
266
267! Create the variable if it doesn't exist yet
268
269              write (*,*) "=========================="
[965]270              write (*,*) "DIAGSPECIR: creating variable ",nom
[305]271              call def_var(nid,nom,titre,unite,4,id,varid,ierr)
272
273           endif
274
275           corner(1)=1
276           corner(2)=1
277           corner(3)=1
278           corner(4)=ntime
279
280           edges(1)=iip1
281           edges(2)=jjp1
282           edges(3)=L_NSPECTI
283           edges(4)=1
284#ifdef NC_DOUBLE
285           ierr= NF_PUT_VARA_DOUBLE(nid,varid,corner,edges,dx3)
286#else
287           ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx3)
288#endif
289
290           if (ierr.ne.NF_NOERR) then
291              write(*,*) "***** PUT_VAR problem in writediagspec"
292              write(*,*) "***** with ",nom
293              write(*,*) 'ierr=', ierr
294             call abort
295           endif
296
[965]297          endif ! of if (is_master)
[305]298
[965]299        endif ! of if (dimpx.eq.3)
300
[305]301      endif ! of if ( MOD(zitau+1,irythme) .eq.0.)
302
[965]303      ! Close the NetCDF file
304      if (is_master) then
305        ierr= NF_CLOSE(nid)
306      endif
[305]307
308      end
Note: See TracBrowser for help on using the repository browser.