source: trunk/LMDZ.GENERIC/libf/phystd/writediagspecVI.F @ 2176

Last change on this file since 2176 was 1543, checked in by emillour, 9 years ago

All models: Further adaptations to keep up with changes in LMDZ5 concerning
physics/dynamics separation:

  • dyn3d:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • dyn3dpar:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • updated calfis_p.F to follow up with changes.
  • copied over updated "bands.F90" from LMDZ5.
  • dynphy_lonlat:
  • calfis_p.F90, mod_interface_dyn_phys.F90, follow up of changes in phy_common/mod_* routines
  • phy_common:
  • added "geometry_mod.F90" to store information about the grid (replaces phy*/comgeomphy.F90) and give variables friendlier names: rlond => longitude , rlatd => latitude, airephy => cell_area, cuphy => dx , cvphy => dy
  • added "physics_distribution_mod.F90"
  • updated "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_mpi_data.F90", "mod_phys_lmdz_para.F90", "mod_phys_lmdz_mpi_transfert.F90", "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_omp_data.F90", "mod_phys_lmdz_omp_transfert.F90", "write_field_phy.F90" and "ioipsl_getin_p_mod.F90" to LMDZ5 versions.
  • phy[venus/titan/mars/std]:
  • removed "init_phys_lmdz.F90", "comgeomphy.F90"; adapted routines to use geometry_mod (longitude, latitude, cell_area, etc.)

EM

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