source: trunk/LMDZ.MARS/util/concatnc.F90 @ 1073

Last change on this file since 1073 was 1073, checked in by tnavarro, 11 years ago

Better handling of the first date of the file : Read and write the controle field, if possible, for zrecast, localtime and concatnc + cosmetic change in lslin. This is retrocompatible with previous versions.

  • Property svn:executable set to *
File size: 46.3 KB
Line 
1program concatnc
2
3
4! ********************************************************
5! Program to concatenate data from Netcdf "diagfi" files,
6! outputs from the martian GCM
7! input : diagfi.nc  / concat.nc / stats.nc kind of files
8! author: Y. Wanherdrick
9! + aps(), bps() and phisinit() are now also written
10!   to output file (E. Millour, september 2006)
11!   if available (F. Forget, october 2006)
12! + handle 1D data (EM, January 2007)
13! + ap(), bp()  (F. Forget, February 2008)
14! + handle the possibility that number of GCM layers (aps, bps
15!   or sigma) may be different from number of vertical levels
16!   of data (which is the case for outputs from 'zrecast')
17!   (EM, April 2010)
18! + handle absence of ap() and bp() if aps and bps are available
19!    (case of stats file) FF, November 2011
20! + read and write controle field, if available. TN, October 2013
21! ********************************************************
22
23implicit none
24
25include "netcdf.inc" ! NetCDF definitions
26
27character (len=80), dimension(1000) :: file
28! file(): input file(s) names(s)
29character (len=30), dimension(15) :: notconcat
30! notconcat(): names of the (15) variables that won't be concatenated
31character (len=50), dimension(:), allocatable :: var
32! var(): name(s) of variable(s) that will be concatenated
33character (len=50) :: tmpvar,tmpfile,title,units
34! tmpvar(): used to temporarily store a variable name
35! tmpfile(): used to temporarily store a file name
36! title(): [netcdf] title attribute
37! units(): [netcdf] units attribute
38character (len=100) :: filename,vartmp
39! filename(): output file name
40! vartmp(): temporary variable name (read from netcdf input file)
41!character (len=1) :: ccopy
42! ccpy: 'y' or 'n' answer
43character (len=4) :: axis
44! axis: "ls" or "sol"
45integer :: nid,ierr,miss
46! nid: [netcdf] file ID #
47! ierr: [netcdf] subroutine returned error code
48! miss: [netcdf] subroutine returned error code
49integer :: i,j,k,inter
50! for various loops
51integer :: varid
52! varid: [netcdf] variable ID #
53integer :: memolatlen=0,memolonlen=0,memoaltlen=0
54! memolatlen: # of elements of lat(), read from the first input file
55! memolonlen: # of elements of lon(), read from the first input file
56! memoaltlen: # of elements of alt(), read from the first input file
57real, dimension(:), allocatable:: lat,lon,alt,ctl,time
58! lat(): array, stores latitude coordinates
59! lon(): array, stores longitude coordinates
60! alt(): array, stores altitude coordinates
61! ctl(): array, stores controle coordinates
62! time(): array, stores time coordinates
63integer :: nbvar,nbfile,nbvarfile,ndim
64! nbvar: # of variables to concatenate
65! nbfile: # number of input file(s)
66! nbvarfile: total # of variables in an input file
67! ndim: [netcdf] # (3 or 4) of dimensions (for variables)
68integer :: latdim,londim,altdim,ctldim,timedim
69! latdim: [netcdf] "latitude" dim ID
70! londim: [netcdf] "longitude" dim ID
71! altdim: [netcdf] "altdim" dim ID
72! ctldim: [netcdf] "ctldim" dim ID
73! timedim: [netcdf] "timedim" dim ID
74integer :: gcmlayerdim ! NetCDF dimension ID for # of layers in GCM
75integer :: latvar,lonvar,altvar,ctlvar,timevar
76! latvar: [netcdf] ID of "latitude" variable
77! lonvar: [netcdf] ID of "longitude" variable
78! altvar: [netcdf] ID of "altitude" variable
79! ctlvar: [netcdf] ID of "controle" variable
80! timevar: [netcdf] ID of "Time" variable
81integer :: latlen,lonlen,altlen,ctllen,timelen
82! latlen: # of elements of lat() array
83! lonlen: # of elements of lon() array
84! altlen: # of elements of alt() array
85! ctllen: # of elements of ctl() array
86! timelen: # of elemnets of time() array
87integer :: GCM_layers ! number of GCM atmospheric layers (may not be
88! same as altlen if file is an output of zrecast)
89integer :: nout,latdimout,londimout,altdimout,timedimout,timevarout
90! nout: [netcdf] output file ID
91! latdimout: [netcdf] output latitude (dimension) ID
92! londimout: [netcdf] output longitude (dimension) ID
93! altdimout: [netcdf] output altitude (dimension) ID
94! timedimout: [netcdf] output time (dimension) ID
95! timevarout: [netcdf] ID of output "Time" variable
96integer :: layerdimout ! NetCDF dimension ID for # of layers in GCM
97integer :: interlayerdimout ! dimension ID for # of interlayers in GCM
98integer :: reptime,rep,varidout
99! reptime: total length of concatenated time() arrays
100! rep: # number of elements of a time() array to write to the output file
101! varidout: [netcdf] variable ID # (of a variable to write to the output file)
102integer :: Nnotconcat,var_ok
103! Nnotconcat: # of (leading)variables that won't be concatenated
104! var_ok: flag (0 or 1)
105integer, dimension(4) :: corner,edges,dim
106! corner: [netcdf]
107! edges: [netcdf]
108! dim: [netcdf]
109real, dimension(:,:,:,:), allocatable :: var3d
110! var3D(,,,): 4D array to store a field
111real :: memotime
112! memotime: (cumulative) time value, in martian days (sols)
113real :: missing
114!PARAMETER(missing=1E+20)
115! missing: [netcdf] to handle "missing" values when reading/writing files
116real, dimension(2) :: valid_range
117! valid_range(2): [netcdf] interval in which a value is considered valid
118
119!==============================================================================
120! 1.1. Get input file name(s)
121!==============================================================================
122write(*,*)
123write(*,*) "-- Program written specifically for NetCDF 'diagfi' files from the martian GCM --"
124write(*,*)
125write(*,*) "which files do you want to use?"
126write(*,*) "<Enter> when list ok"
127
128nbfile=0
129read(*,'(a50)') tmpfile
130do While (len_trim(tmpfile).ne.0)
131   nbfile=nbfile+1
132   file(nbfile)=tmpfile
133   read(*,'(a50)') tmpfile
134enddo
135
136if(nbfile==0) then
137   write(*,*) "no file... game over"
138   stop ""
139endif
140
141!==============================================================================
142! 1.2. Ask for starting day value (memotime)
143!==============================================================================
144
145write(*,*)
146!write(*,*) "Beginning day of the first specified file?"
147write(*,*) "Starting day of the run stored in the first input file?"
148write(*,*) " (Obsolete if the controle field is present, answer any number)"
149write(*,*) "(e.g.: 100 if that run started at time=100 sols)"
150read(*,*) memotime
151
152!==============================================================================
153! 1.3. Open the first input file
154!==============================================================================
155
156ierr = NF_OPEN(file(1),NF_NOWRITE,nid)
157if (ierr.NE.NF_NOERR) then
158   write(*,*) 'ERROR: Pb opening file '//file(1)
159   stop ""
160endif
161
162ierr=NF_INQ_NVARS(nid,nbvarfile)
163! nbvarfile now set to be the (total) number of variables in file
164
165!==============================================================================
166! 1.4. Ask for (output) "Time" axis type
167!==============================================================================
168
169write(*,*) "Warning: to read the result with grads, choose sol"
170write(*,*) "Warning: use ferret to read the non linear scale ls"
171write(*,*) "Which time axis should be given in the output? (sol/ls)"
172read(*,*) axis
173! loop as long as axis is neither "sol" nor "ls"
174do while ((axis/="sol").AND.(axis/="ls"))
175   read(*,*) axis
176enddo
177
178! The following variables don't need to be concatenated
179notconcat(1)='Time'
180notconcat(2)='controle'
181notconcat(3)='rlonu'
182notconcat(4)='latitude'
183notconcat(5)='longitude'
184notconcat(6)='altitude'
185notconcat(7)='rlatv'
186notconcat(8)='aps'
187notconcat(9)='bps'
188notconcat(10)='ap'
189notconcat(11)='bp'
190notconcat(12)='cu'
191notconcat(13)='cv'
192notconcat(14)='aire'
193notconcat(15)='phisinit'
194
195!==============================================================================
196! 1.5. Get (and check) list of variables to concatenate
197!==============================================================================
198write(*,*)
199   Nnotconcat=0
200do i=1,nbvarfile
201   ierr=NF_INQ_VARNAME(nid,i,vartmp)
202   ! vartmp now contains the "name" of variable of ID # i
203   var_ok=0
204   do inter=1,15
205      if (vartmp.eq.notconcat(inter)) then
206         var_ok=1
207         Nnotconcat=Nnotconcat+1
208      endif
209   enddo       
210   if (var_ok.eq.0)  write(*,*) trim(vartmp)
211enddo
212
213! Nnotconcat: # of variables that won't be concatenated
214! nbvarfile: total # of variables in file
215allocate(var(nbvarfile-Nnotconcat))
216
217
218write(*,*)
219write(*,*) "which variables do you want to concatenate?"
220write(*,*) "all / list of <variables> (separated by <Enter>s)"
221write(*,*) "(an empty line , i.e: just <Enter>, implies end of list)"
222nbvar=0
223read(*,'(a50)') tmpvar
224do while ((tmpvar/=' ').AND.(trim(tmpvar)/='all'))
225   nbvar=nbvar+1
226   var(nbvar)=tmpvar
227   read(*,'(a50)') tmpvar
228enddo
229
230if (tmpvar=="all") then
231   if (axis=="ls") then
232!      write(*,*) "Do you want to keep the original file? (y/n)"
233!      read(*,*) ccopy
234!      if ((ccopy=="n").or.(ccopy=="N")) then
235!         do i=1,nbfile
236!            ierr=NF_CLOSE(nid)
237!            ierr = NF_OPEN(file(1),NF_WRITE,nid)
238!            call change_time_axis(nid,ierr)
239!            ierr=NF_CLOSE(nid)
240!            STOP ""
241!         enddo
242!      else
243         nbvar=nbvarfile-Nnotconcat
244         do j=Nnotconcat+1,nbvarfile
245            ierr=nf_inq_varname(nid,j,var(j-Nnotconcat))
246         enddo
247!      endif ! of if ((ccopy=="n").or.(ccopy=="N"))
248   endif ! of if (axis=="ls")
249! Variables names from the file are catched
250   nbvar=nbvarfile-Nnotconcat
251   do i=1,nbvar
252      ierr=nf_inq_varname(nid,i+Nnotconcat,var(i))
253      write(*,'(a9,1x,i2,1x,a1,1x,a50)') "variable ",i,":",var(i)
254   enddo
255else if(nbvar==0) then
256   write(*,*) "no variable... game over"
257   stop ""
258endif ! of if (tmpvar=="all")
259
260! Name of the new file
261!==========================================================
262!filename=var(1)
263!do i=2, nbvar
264!   filename=trim(adjustl(filename))//"_"//var(i)
265!enddo
266!filename=trim(adjustl(filename))//".nc"
267
268!==============================================================================
269! 1.6. Get output file name
270!==============================================================================
271filename="concat.nc"
272
273
274!==============================================================================
275! 2. Concatenate input file(s) into output file
276!==============================================================================
277
278reptime=0
279
280do i=1,nbfile
281
282!==============================================================================
283! 2.1. Open input file
284!==============================================================================
285
286   if (i/=1) then
287      write(*,*)
288      write(*,*) "opening "//trim(file(i))//"..."
289      ierr = NF_OPEN(file(i),NF_NOWRITE,nid)
290      if (ierr.NE.NF_NOERR) then
291         write(*,*) 'ERROR: Pb opening file '//file(i)
292         write(*,*) NF_STRERROR(ierr)
293         stop ""
294      endif
295   endif
296
297!==============================================================================
298! 2.2. Read (and check) dimensions of variables from input file
299!==============================================================================
300
301   ierr=NF_INQ_DIMID(nid,"latitude",latdim)
302   ierr=NF_INQ_VARID(nid,"latitude",latvar)
303   if (ierr.NE.NF_NOERR) then
304      write(*,*) 'ERROR: Field <latitude> is missing in file'//file(i)
305      stop "" 
306   endif
307   ierr=NF_INQ_DIMLEN(nid,latdim,latlen)
308!  write(*,*) "latlen: ",latlen
309
310   ierr=NF_INQ_DIMID(nid,"longitude",londim)
311   ierr=NF_INQ_VARID(nid,"longitude",lonvar)
312   if (ierr.NE.NF_NOERR) then
313      write(*,*) 'ERROR: Field <longitude> is missing in file'//file(i)
314      stop ""
315   endif
316   ierr=NF_INQ_DIMLEN(nid,londim,lonlen)
317!  write(*,*) "lonlen: ",lonlen
318
319   ierr=NF_INQ_DIMID(nid,"altitude",altdim)
320   ierr=NF_INQ_VARID(nid,"altitude",altvar)
321   if (ierr.NE.NF_NOERR) then
322      write(*,*) 'ERROR: Field <altitude> is missing in file'//file(i)
323      stop ""
324   endif
325   ierr=NF_INQ_DIMLEN(nid,altdim,altlen)
326!  write(*,*) "altlen: ",altlen
327
328   ierr=NF_INQ_DIMID(nid,"index",ctldim)
329   ierr=NF_INQ_VARID(nid,"controle",ctlvar)
330   if (ierr.NE.NF_NOERR) then
331      write(*,*) 'Field <controle> is missing in file'//file
332      ctllen=0
333      !stop ""
334   else
335      ierr=NF_INQ_DIMLEN(nid,ctldim,ctllen)
336   endif
337!  write(*,*) "controle: ",controle
338
339! load size of aps() or sigma() (in case it is not altlen)
340   ! default is that GCM_layers=altlen
341   ! but for outputs of zrecast, it may be a different value
342   ierr=NF_INQ_DIMID(nid,"GCM_layers",gcmlayerdim)
343   if (ierr.ne.NF_NOERR) then
344     ! didn't find a GCM_layers dimension; therefore we have:
345     GCM_layers=altlen
346   else
347     ! load value of GCM_layers
348     ierr=NF_INQ_DIMLEN(nid,gcmlayerdim,GCM_layers)
349   endif
350!   write(*,*) "GCM_layers=",GCM_layers
351
352!==============================================================================
353! 2.3. Read (and check compatibility of) dimensions of
354!       variables from input file
355!==============================================================================
356
357   if (i==1) then ! First call; initialize/allocate
358      memolatlen=latlen
359      memolonlen=lonlen
360      memoaltlen=altlen
361      allocate(lat(latlen))
362      allocate(lon(lonlen))
363      allocate(alt(altlen))
364      allocate(ctl(ctllen))
365#ifdef NC_DOUBLE
366      ierr = NF_GET_VAR_DOUBLE(nid,latvar,lat)
367      ierr = NF_GET_VAR_DOUBLE(nid,lonvar,lon)
368      ierr = NF_GET_VAR_DOUBLE(nid,altvar,alt)
369      if (ctllen .ne. -1) ierr = NF_GET_VAR_DOUBLE(nid,ctlvar,ctl)
370#else
371      ierr = NF_GET_VAR_REAL(nid,latvar,lat)
372      ierr = NF_GET_VAR_REAL(nid,lonvar,lon)
373      ierr = NF_GET_VAR_REAL(nid,altvar,alt)
374      if (ctllen .ne. -1) ierr = NF_GET_VAR_REAL(nid,ctlvar,ctl)
375#endif
376      if (ctllen .ne. -1) then
377         if (modulo(int(memotime),669)/=modulo(int(ctl(4)),669)) then
378           write(*,'(2(A,I4),A)') "WARNING: Starting day of the run is not ",&
379                                modulo(int(memotime),669)," but ",modulo(int(ctl(4)),669),"!!"
380           write(*,*) "Starting day of the run has been corrected."
381           memotime=float(modulo(int(ctl(4)),669))
382         endif
383      endif
384   ! Initialize output file's lat,lon,alt and time dimensions
385      call initiate (filename,lat,lon,alt,ctl,GCM_layers,nout,&
386       latdimout,londimout,altdimout,timedimout,&
387       layerdimout,interlayerdimout,timevarout)
388   ! Initialize output file's aps,bps,ap,bp and phisinit variables
389     call init2(nid,lonlen,latlen,altlen,GCM_layers,&
390                nout,londimout,latdimout,altdimout,&
391                layerdimout,interlayerdimout)
392   
393   else ! Not a first call,
394   ! Check that latitude,longitude and altitude of current input file
395   ! are identical to those of the output file
396      if (memolatlen/=latlen) then
397           write(*,*) "ERROR: Not the same latitude axis"
398           stop ""
399        else if (memolonlen/=lonlen) then
400           write(*,*) "ERROR: Not the same longitude axis"
401           stop ""
402             else if (memoaltlen/=altlen) then
403                write(*,*) "ERROR: Not the same altitude axis"
404                stop ""
405       endif
406   endif ! of if (i==1)
407
408!==============================================================================
409! 2.4. Handle "Time" dimension from input file
410!==============================================================================
411
412!==============================================================================
413! 2.4.1 Read "Time" dimension from input file
414!==============================================================================
415   ierr=NF_INQ_DIMID(nid,"Time",timedim)
416   if (ierr.NE.NF_NOERR) then
417      write(*,*) 'ERROR: Dimension <Time> is missing in file'//file(i)
418      stop ""
419   endif
420   ierr=NF_INQ_VARID(nid,"Time",timevar)
421   if (ierr.NE.NF_NOERR) then
422      write(*,*) 'ERROR: Field <Time> is missing in file'//file(i)
423      stop ""
424   endif
425   ierr=NF_INQ_DIMLEN(nid,timedim,timelen)
426!  write(*,*) "timelen: ",timelen
427
428   ! allocate time() array and fill it with values from input file
429   allocate(time(timelen))
430
431#ifdef NC_DOUBLE
432   ierr = NF_GET_VAR_DOUBLE(nid,timevar,time)
433#else
434   ierr = NF_GET_VAR_REAL(nid,timevar,time)
435#endif
436
437!==============================================================================
438! 2.4.2 Write/extend "Time" dimension/values in output file
439!==============================================================================
440
441   rep=0
442   write(*,*)
443   write(*,'(a3,1x,f6.1)') "Sol",memotime
444
445   ! Add (memotime) offset and write "concatenated" time values to output file
446   do k=reptime+1,reptime+timelen
447      rep=rep+1
448#ifdef NC_DOUBLE
449      ierr= NF_PUT_VARA_DOUBLE(nout,timevarout,k,1,memotime+time(rep))
450#else
451      ierr= NF_PUT_VARA_REAL(nout,timevarout,k,1,memotime+time(rep))
452#endif
453   enddo
454   ! Compute new time offset (for further concatenations)
455   memotime=memotime+time(timelen)
456
457!==============================================================================
458! 2.5 Read/write variables
459!==============================================================================
460
461   do j=1,nbvar ! loop on variables to read/write
462
463!==============================================================================
464! 2.5.1 Check that variable to be read existe in input file
465!==============================================================================
466
467      write(*,*) "variable ",var(j)
468      ierr=nf_inq_varid(nid,var(j),varid)
469      if (ierr.NE.NF_NOERR) then
470         write(*,*) 'ERROR: Field <',var(j),'> not found in file'//file(i)
471         stop ""
472      endif
473      ierr=nf_inq_varndims(nid,varid,ndim)
474
475!==============================================================================
476! 2.5.2 Prepare things in order to read/write the variable
477!==============================================================================
478
479      ! build dim(),corner() and edges() arrays
480      ! and allocate var3d() array
481      if (ndim==1) then
482         allocate(var3d(timelen,1,1,1))
483         dim(1)=timedimout
484
485         ! start indexes (where data values will be written)
486         corner(1)=reptime+1
487         corner(2)=1
488         corner(3)=1
489         corner(4)=1
490
491         ! length (along dimensions) of block of data to be written
492         edges(1)=timelen
493         edges(2)=1
494         edges(3)=1
495         edges(4)=1
496
497      else if (ndim==3) then
498         allocate(var3d(lonlen,latlen,timelen,1))
499         dim(1)=londimout
500         dim(2)=latdimout
501         dim(3)=timedimout
502
503         ! start indexes (where data values will be written)
504         corner(1)=1
505         corner(2)=1
506         corner(3)=reptime+1
507         corner(4)=1
508
509         ! length (along dimensions) of block of data to be written
510         edges(1)=lonlen
511         edges(2)=latlen
512         edges(3)=timelen
513         edges(4)=1
514   
515      else if (ndim==4) then
516         allocate(var3d(lonlen,latlen,altlen,timelen))
517         dim(1)=londimout
518         dim(2)=latdimout
519         dim(3)=altdimout
520         dim(4)=timedimout
521
522         ! start indexes (where data values will be written)
523         corner(1)=1
524         corner(2)=1
525         corner(3)=1
526         corner(4)=reptime+1
527
528         ! length (along dimensions) of block of data to be written
529         edges(1)=lonlen
530         edges(2)=latlen
531         edges(3)=altlen
532         edges(4)=timelen
533      endif
534
535      if (i==1) then ! First call: write some definitions to output file
536         units="                                                    "
537         title="                                                    "
538         ierr=nf_get_att_text(nid,varid,"title",title)
539         ierr=nf_get_att_text(nid,varid,"units",units)
540         call def_var(nout,var(j),title,units,ndim,dim,varidout,ierr)
541      else
542         ierr=NF_INQ_VARID(nout,var(j),varidout)
543      endif
544
545!==============================================================================
546! 2.5.3 Read from input file and write (append) to the output file
547!==============================================================================
548
549#ifdef NC_DOUBLE
550      ierr = NF_GET_VAR_DOUBLE(nid,varid,var3d)
551      ierr= NF_PUT_VARA_DOUBLE(nout,varidout,corner,edges,var3d)
552      miss=NF_GET_ATT_DOUBLE(nid,varid,"missing_value",missing)
553      miss=NF_GET_ATT_DOUBLE(nid,varid,"valid_range",valid_range)
554#else
555      ierr = NF_GET_VAR_REAL(nid,varid,var3d)
556      ierr= NF_PUT_VARA_REAL(nout,varidout,corner,edges,var3d)
557      miss=NF_GET_ATT_REAL(nid,varid,"missing_value",missing)
558      miss=NF_GET_ATT_REAL(nid,varid,"valid_range",valid_range)
559#endif
560
561      if (ierr.ne.NF_NOERR) then
562         write(*,*) 'PUT_VAR ERROR: ',NF_STRERROR(ierr)
563         stop ""
564      endif
565
566! In case there is a "valid_range" attribute
567      ! Write "valid_range" and "missing_value" attributes in output file
568      if (miss.eq.NF_NOERR) then
569         call missing_value(nout,varidout,valid_range,missing)
570      endif
571
572      ! free var3d() array
573      deallocate(var3d)
574
575   enddo ! of do j=1,nbvar
576
577   ! Free time() and compute/store array length (for further concatenations)
578   deallocate(time)
579   reptime=reptime+timelen
580
581   ! Close input file
582   ierr=nf_close(nid)
583
584enddo ! of i=1,nbfile
585
586!==============================================================================
587! 3. If required, change time axis (from sols to Ls)
588!==============================================================================
589
590if (axis=="ls") then
591   call change_time_axis(nout,ierr)
592endif
593
594! Close output file
595ierr=NF_CLOSE(nout)
596
597contains
598
599!******************************************************************************
600subroutine initiate (filename,lat,lon,alt,ctl,GCM_layers,nout,&
601         latdimout,londimout,altdimout,timedimout,&
602         layerdimout,interlayerdimout,timevarout)
603!==============================================================================
604! Purpose:
605! Create and initialize a data file (NetCDF format)
606!==============================================================================
607! Remarks:
608! The NetCDF file (created in this subroutine) remains open
609!==============================================================================
610
611implicit none
612
613include "netcdf.inc" ! NetCDF definitions
614
615!==============================================================================
616! Arguments:
617!==============================================================================
618character (len=*), intent(in):: filename
619! filename(): the file's name
620real, dimension(:), intent(in):: lat
621! lat(): latitude
622real, dimension(:), intent(in):: lon
623! lon(): longitude
624real, dimension(:), intent(in):: alt
625! alt(): altitude
626real, dimension(:), intent(in):: ctl
627! ctl(): controle
628integer,intent(in) :: GCM_layers ! number of GCM layers
629integer, intent(out):: nout
630! nout: [netcdf] file ID
631integer, intent(out):: latdimout
632! latdimout: [netcdf] lat() (i.e.: latitude)  ID
633integer, intent(out):: londimout
634! londimout: [netcdf] lon()  ID
635integer, intent(out):: altdimout
636! altdimout: [netcdf] alt()  ID
637integer, intent(out):: timedimout
638! timedimout: [netcdf] "Time"  ID
639integer,intent(out) :: layerdimout
640! layerdimout: [netcdf] "GCM_layers" ID
641integer,intent(out) :: interlayerdimout
642! layerdimout: [netcdf] "GCM_layers+1" ID
643integer, intent(out):: timevarout
644! timevarout: [netcdf] "Time" (considered as a variable) ID
645
646!==============================================================================
647! Local variables:
648!==============================================================================
649!integer :: latdim,londim,altdim,timedim
650integer :: nvarid,ierr
651integer :: ctldimout
652! nvarid: [netcdf] ID of a variable
653! ierr: [netcdf]  return error code (from called subroutines)
654
655!==============================================================================
656! 1. Create (and open) output file
657!==============================================================================
658write(*,*) "creating "//trim(adjustl(filename))//'...'
659ierr = NF_CREATE(filename,IOR(NF_CLOBBER,NF_64BIT_OFFSET),nout)
660! NB: setting NF_CLOBBER mode means that it's OK to overwrite an existing file
661if (ierr.NE.NF_NOERR) then
662   WRITE(*,*)'ERROR: Impossible to create the file.'
663   stop ""
664endif
665
666!==============================================================================
667! 2. Define/write "dimensions" and get their IDs
668!==============================================================================
669
670ierr = NF_DEF_DIM(nout, "latitude", size(lat), latdimout)
671ierr = NF_DEF_DIM(nout, "longitude", size(lon), londimout)
672ierr = NF_DEF_DIM(nout, "altitude", size(alt), altdimout)
673if (size(ctl).ne.0) ierr = NF_DEF_DIM(nout, "index", size(ctl), ctldimout)
674ierr = NF_DEF_DIM(nout, "Time", NF_UNLIMITED, timedimout)
675ierr = NF_DEF_DIM(nout, "GCM_layers", GCM_layers, layerdimout)
676ierr = NF_DEF_DIM(nout, "GCM_interlayers",GCM_layers+1,interlayerdimout)
677
678! End netcdf define mode
679ierr = NF_ENDDEF(nout)
680
681!==============================================================================
682! 3. Write "Time" and its attributes
683!==============================================================================
684
685call def_var(nout,"Time","Time","years since 0000-00-0 00:00:00",1,&
686             (/timedimout/),timevarout,ierr)
687
688!==============================================================================
689! 4. Write "latitude" (data and attributes)
690!==============================================================================
691
692call def_var(nout,"latitude","latitude","degrees_north",1,&
693             (/latdimout/),nvarid,ierr)
694
695#ifdef NC_DOUBLE
696ierr = NF_PUT_VAR_DOUBLE (nout,nvarid,lat)
697#else
698ierr = NF_PUT_VAR_REAL (nout,nvarid,lat)
699#endif
700
701!==============================================================================
702! 4. Write "longitude" (data and attributes)
703!==============================================================================
704
705call def_var(nout,"longitude","East longitude","degrees_east",1,&
706             (/londimout/),nvarid,ierr)
707
708#ifdef NC_DOUBLE
709ierr = NF_PUT_VAR_DOUBLE (nout,nvarid,lon)
710#else
711ierr = NF_PUT_VAR_REAL (nout,nvarid,lon)
712#endif
713
714!==============================================================================
715! 5. Write "altitude" (data and attributes)
716!==============================================================================
717
718! Switch to netcdf define mode
719ierr = NF_REDEF (nout)
720
721#ifdef NC_DOUBLE
722ierr = NF_DEF_VAR (nout,"altitude",NF_DOUBLE,1,altdimout,nvarid)
723#else
724ierr = NF_DEF_VAR (nout,"altitude",NF_FLOAT,1,altdimout,nvarid)
725#endif
726
727ierr = NF_PUT_ATT_TEXT (nout,nvarid,"long_name",8,"altitude")
728ierr = NF_PUT_ATT_TEXT (nout,nvarid,'units',2,"km")
729ierr = NF_PUT_ATT_TEXT (nout,nvarid,'positive',2,"up")
730
731! End netcdf define mode
732ierr = NF_ENDDEF(nout)
733
734#ifdef NC_DOUBLE
735ierr = NF_PUT_VAR_DOUBLE (nout,nvarid,alt)
736#else
737ierr = NF_PUT_VAR_REAL (nout,nvarid,alt)
738#endif
739
740!==============================================================================
741! 6. Write "controle" (data and attributes)
742!==============================================================================
743
744if (size(ctl).ne.0) then
745   ! Switch to netcdf define mode
746   ierr = NF_REDEF (nout)
747
748   #ifdef NC_DOUBLE
749   ierr = NF_DEF_VAR (nout,"controle",NF_DOUBLE,1,ctldimout,nvarid)
750   #else
751   ierr = NF_DEF_VAR (nout,"controle",NF_FLOAT,1,ctldimout,nvarid)
752   #endif
753
754   ierr = NF_PUT_ATT_TEXT (nout,nvarid,"title",18,"Control parameters")
755
756   ! End netcdf define mode
757   ierr = NF_ENDDEF(nout)
758
759   #ifdef NC_DOUBLE
760   ierr = NF_PUT_VAR_DOUBLE (nout,nvarid,ctl)
761   #else
762   ierr = NF_PUT_VAR_REAL (nout,nvarid,ctl)
763   #endif
764endif
765
766end Subroutine initiate
767!******************************************************************************
768subroutine init2(infid,lonlen,latlen,altlen,GCM_layers, &
769                 outfid,londimout,latdimout,altdimout, &
770                 layerdimout,interlayerdimout)
771!==============================================================================
772! Purpose:
773! Copy ap() , bp(), aps(), bps(), aire() and phisinit()
774! from input file to outpout file
775!==============================================================================
776! Remarks:
777! The NetCDF files must be open
778!==============================================================================
779
780implicit none
781
782include "netcdf.inc" ! NetCDF definitions
783
784!==============================================================================
785! Arguments:
786!==============================================================================
787integer, intent(in) :: infid  ! NetCDF output file ID
788integer, intent(in) :: lonlen ! # of grid points along longitude
789integer, intent(in) :: latlen ! # of grid points along latitude
790integer, intent(in) :: altlen ! # of grid points along latitude
791integer, intent(in) :: GCM_layers ! # of GCM atmospheric layers
792integer, intent(in) :: outfid ! NetCDF output file ID
793integer, intent(in) :: londimout ! longitude dimension ID
794integer, intent(in) :: latdimout ! latitude dimension ID
795integer, intent(in) :: altdimout ! altitude dimension ID
796integer, intent(in) :: layerdimout ! GCM_layers dimension ID
797integer, intent(in) :: interlayerdimout ! GCM_layers+1 dimension ID
798!==============================================================================
799! Local variables:
800!==============================================================================
801real,dimension(:),allocatable :: aps,bps ! hybrid vertical coordinates
802real,dimension(:),allocatable :: ap,bp ! hybrid vertical coordinates
803real,dimension(:),allocatable :: sigma ! sigma levels
804real,dimension(:,:),allocatable :: aire ! mesh areas
805real,dimension(:,:),allocatable :: phisinit ! Ground geopotential
806integer :: apsid,bpsid,sigmaid,phisinitid
807integer :: apid,bpid
808integer :: ierr
809integer :: tmpvarid ! temporary variable ID
810logical :: area ! is "aire" available ?
811logical :: phis ! is "phisinit" available ?
812logical :: hybrid ! are "aps" and "bps" available ?
813logical :: apbp ! are "ap" and "bp" available ?
814
815!==============================================================================
816! 1. Read data from input file
817!==============================================================================
818
819! hybrid coordinate aps
820!write(*,*) "aps: altlen=",altlen," GCM_layers=",GCM_layers
821allocate(aps(GCM_layers),stat=ierr)
822if (ierr.ne.0) then
823  write(*,*) "init2: failed to allocate aps!"
824  stop
825endif
826ierr=NF_INQ_VARID(infid,"aps",tmpvarid)
827if (ierr.ne.NF_NOERR) then
828  write(*,*) "Ooops. Failed to get aps ID. OK, will look for sigma coord."
829  hybrid=.false.
830else
831  ierr=NF_GET_VAR_REAL(infid,tmpvarid,aps)
832  hybrid=.true.
833  if (ierr.ne.NF_NOERR) then
834    stop "init2 Error: Failed reading aps"
835  endif
836
837  ! hybrid coordinate bps
838!  write(*,*) "bps: altlen=",altlen," GCM_layers=",GCM_layers
839  allocate(bps(GCM_layers),stat=ierr)
840  if (ierr.ne.0) then
841    write(*,*) "init2: failed to allocate bps!"
842    stop
843  endif
844  ierr=NF_INQ_VARID(infid,"bps",tmpvarid)
845  if (ierr.ne.NF_NOERR) then
846    stop "init2 Error: Failed to get bps ID."
847  endif
848  ierr=NF_GET_VAR_REAL(infid,tmpvarid,bps)
849  if (ierr.ne.NF_NOERR) then
850    stop "init2 Error: Failed reading bps"
851  endif
852endif
853
854! hybrid coordinate ap
855allocate(ap(GCM_layers+1),stat=ierr)
856if (ierr.ne.0) then
857  write(*,*) "init2: failed to allocate ap!"
858  stop
859else
860  ierr=NF_INQ_VARID(infid,"ap",tmpvarid)
861  if (ierr.ne.NF_NOERR) then
862    write(*,*) "Ooops. Failed to get ap ID. OK."
863    apbp=.false.
864  else
865    ierr=NF_GET_VAR_REAL(infid,tmpvarid,ap)
866    apbp=.true.
867    if (ierr.ne.NF_NOERR) then
868      stop "Error: Failed reading ap"
869    endif
870  endif
871endif
872
873! hybrid coordinate bp
874allocate(bp(GCM_layers+1),stat=ierr)
875if (ierr.ne.0) then
876  write(*,*) "init2: failed to allocate bp!"
877  stop
878else
879  ierr=NF_INQ_VARID(infid,"bp",tmpvarid)
880  if (ierr.ne.NF_NOERR) then
881    write(*,*) "Ooops. Failed to get bp ID. OK."
882    apbp=.false.
883  else
884    ierr=NF_GET_VAR_REAL(infid,tmpvarid,bp)
885    apbp=.true.
886    if (ierr.ne.NF_NOERR) then
887      stop "Error: Failed reading bp"
888    endif
889  endif
890endif
891
892! sigma levels (if any)
893if (.not.hybrid) then
894  allocate(sigma(GCM_layers),stat=ierr)
895  if (ierr.ne.0) then
896    write(*,*) "init2: failed to allocate sigma"
897    stop
898  endif
899  ierr=NF_INQ_VARID(infid,"sigma",tmpvarid)
900  ierr=NF_GET_VAR_REAL(infid,tmpvarid,sigma)
901  if (ierr.ne.NF_NOERR) then
902    stop "init2 Error: Failed reading sigma"
903  endif
904endif ! of if (.not.hybrid)
905
906! mesh area
907allocate(aire(lonlen,latlen),stat=ierr)
908if (ierr.ne.0) then
909  write(*,*) "init2: failed to allocate aire!"
910  stop
911endif
912ierr=NF_INQ_VARID(infid,"aire",tmpvarid)
913if (ierr.ne.NF_NOERR) then
914  write(*,*)"init2 warning: Failed to get aire ID."
915  area = .false.
916else
917  ierr=NF_GET_VAR_REAL(infid,tmpvarid,aire)
918  if (ierr.ne.NF_NOERR) then
919    stop "init2 Error: Failed reading aire"
920  endif
921  area = .true.
922endif
923
924! ground geopotential phisinit
925allocate(phisinit(lonlen,latlen),stat=ierr)
926if (ierr.ne.0) then
927  write(*,*) "init2: failed to allocate phisinit!"
928  stop
929endif
930ierr=NF_INQ_VARID(infid,"phisinit",tmpvarid)
931if (ierr.ne.NF_NOERR) then
932  write(*,*)"init2 warning: Failed to get phisinit ID."
933  phis = .false.
934else
935  ierr=NF_GET_VAR_REAL(infid,tmpvarid,phisinit)
936  if (ierr.ne.NF_NOERR) then
937    stop "init2 Error: Failed reading phisinit"
938  endif
939  phis = .true.
940endif
941
942!==============================================================================
943! 2. Write
944!==============================================================================
945
946!==============================================================================
947! 2.2. Hybrid coordinates ap() , bp(), aps() and bps()
948!==============================================================================
949if(hybrid) then
950! define aps
951  call def_var(nout,"aps","hybrid pressure at midlayers"," ",1,&
952             (/layerdimout/),apsid,ierr)
953  if (ierr.ne.NF_NOERR) then
954    stop "init2 Error: Failed to def_var aps"
955  endif
956
957! write aps
958#ifdef NC_DOUBLE
959  ierr=NF_PUT_VAR_DOUBLE(outfid,apsid,aps)
960#else
961  ierr=NF_PUT_VAR_REAL(outfid,apsid,aps)
962#endif
963  if (ierr.ne.NF_NOERR) then
964    stop "init2 Error: Failed to write aps"
965  endif
966
967! define bps
968  call def_var(nout,"bps","hybrid sigma at midlayers"," ",1,&
969             (/layerdimout/),bpsid,ierr)
970  if (ierr.ne.NF_NOERR) then
971    stop "init2 Error: Failed to def_var bps"
972  endif
973
974! write bps
975#ifdef NC_DOUBLE
976  ierr=NF_PUT_VAR_DOUBLE(outfid,bpsid,bps)
977#else
978  ierr=NF_PUT_VAR_REAL(outfid,bpsid,bps)
979#endif
980  if (ierr.ne.NF_NOERR) then
981    stop "init2 Error: Failed to write bps"
982  endif
983
984  if (apbp) then
985!   define ap
986    call def_var(nout,"ap","hybrid sigma at interlayers"," ",1,&
987             (/interlayerdimout/),apid,ierr)
988    if (ierr.ne.NF_NOERR) then
989      stop "Error: Failed to def_var ap"
990    endif
991
992! write ap
993#ifdef NC_DOUBLE
994    ierr=NF_PUT_VAR_DOUBLE(outfid,apid,ap)
995#else
996    ierr=NF_PUT_VAR_REAL(outfid,apid,ap)
997#endif
998    if (ierr.ne.NF_NOERR) then
999      stop "Error: Failed to write ap"
1000    endif
1001
1002! define bp
1003    call def_var(nout,"bp","hybrid sigma at interlayers"," ",1,&
1004             (/interlayerdimout/),bpid,ierr)
1005    if (ierr.ne.NF_NOERR) then
1006      stop "Error: Failed to def_var bp"
1007    endif
1008
1009!   write bp
1010#ifdef NC_DOUBLE
1011    ierr=NF_PUT_VAR_DOUBLE(outfid,bpid,bp)
1012#else
1013    ierr=NF_PUT_VAR_REAL(outfid,bpid,bp)
1014#endif
1015    if (ierr.ne.NF_NOERR) then
1016      stop "Error: Failed to write bp"
1017    endif
1018  endif ! of if (apbp)
1019
1020else
1021! define sigma
1022  call def_var(nout,"sigma","sigma at midlayers"," ",1,&
1023             (/layerdimout/),sigmaid,ierr)
1024  if (ierr.ne.NF_NOERR) then
1025    stop "init2 Error: Failed to def_var sigma"
1026  endif
1027! write sigma
1028#ifdef NC_DOUBLE
1029  ierr=NF_PUT_VAR_DOUBLE(outfid,sigmaid,sigma)
1030#else
1031  ierr=NF_PUT_VAR_REAL(outfid,sigmaid,sigma)
1032#endif
1033  if (ierr.ne.NF_NOERR) then
1034    stop "init2 Error: Failed to write sigma"
1035  endif
1036endif ! of if (hybrid)
1037
1038!==============================================================================
1039! 2.2. aire() and phisinit()
1040!==============================================================================
1041
1042if (area) then
1043  ! define aire
1044  call def_var(nout,"aire","Mesh area","m2",2,&
1045           (/londimout,latdimout/),tmpvarid,ierr)
1046  if (ierr.ne.NF_NOERR) then
1047     stop "init2 Error: Failed to def_var aire"
1048  endif
1049 
1050  ! write aire
1051#ifdef NC_DOUBLE
1052  ierr=NF_PUT_VAR_DOUBLE(outfid,tmpvarid,aire)
1053#else
1054  ierr=NF_PUT_VAR_REAL(outfid,tmpvarid,aire)
1055#endif
1056  if (ierr.ne.NF_NOERR) then
1057    stop "init2 Error: Failed to write aire"
1058  endif
1059endif ! of if (area)
1060
1061IF (phis) THEN
1062
1063  !define phisinit
1064   call def_var(nout,"phisinit","Ground level geopotential"," ",2,&
1065            (/londimout,latdimout/),phisinitid,ierr)
1066   if (ierr.ne.NF_NOERR) then
1067     stop "init2 Error: Failed to def_var phisinit"
1068   endif
1069
1070  ! write phisinit
1071#ifdef NC_DOUBLE
1072  ierr=NF_PUT_VAR_DOUBLE(outfid,phisinitid,phisinit)
1073#else
1074  ierr=NF_PUT_VAR_REAL(outfid,phisinitid,phisinit)
1075#endif
1076  if (ierr.ne.NF_NOERR) then
1077    stop "init2 Error: Failed to write phisinit"
1078  endif
1079
1080ENDIF ! of IF (phis)
1081
1082
1083! Cleanup
1084if (allocated(aps)) deallocate(aps)
1085if (allocated(bps)) deallocate(bps)
1086if (allocated(ap)) deallocate(ap)
1087if (allocated(bp)) deallocate(bp)
1088if (allocated(sigma)) deallocate(sigma)
1089if (allocated(phisinit)) deallocate(phisinit)
1090if (allocated(aire)) deallocate(aire)
1091
1092end subroutine init2
1093!******************************************************************************
1094subroutine def_var(nid,name,title,units,nbdim,dim,nvarid,ierr)
1095!==============================================================================
1096! Purpose: Write a variable (i.e: add a variable to a dataset)
1097! called "name"; along with its attributes "title", "units"...
1098! to a file (following the NetCDF format)
1099!==============================================================================
1100! Remarks:
1101! The NetCDF file must be open
1102!==============================================================================
1103
1104implicit none
1105
1106include "netcdf.inc" ! NetCDF definitions
1107
1108!==============================================================================
1109! Arguments:
1110!==============================================================================
1111integer, intent(in) :: nid
1112! nid: [netcdf] file ID #
1113character (len=*), intent(in) :: name
1114! name(): [netcdf] variable's name
1115character (len=*), intent(in) :: title
1116! title(): [netcdf] variable's "title" attribute
1117character (len=*), intent(in) :: units
1118! unit(): [netcdf] variable's "units" attribute
1119integer, intent(in) :: nbdim
1120! nbdim: number of dimensions of the variable
1121integer, dimension(nbdim), intent(in) :: dim
1122! dim(nbdim): [netcdf] dimension(s) ID(s)
1123integer, intent(out) :: nvarid
1124! nvarid: [netcdf] ID # of the variable
1125integer, intent(out) :: ierr
1126! ierr: [netcdf] subroutines returned error code
1127
1128! Switch to netcdf define mode
1129ierr=NF_REDEF(nid)
1130
1131! Insert the definition of the variable
1132#ifdef NC_DOUBLE
1133ierr=NF_DEF_VAR(nid,adjustl(name),NF_DOUBLE,nbdim,dim,nvarid)
1134#else
1135ierr=NF_DEF_VAR(nid,adjustl(name),NF_FLOAT,nbdim,dim,nvarid)
1136#endif
1137
1138! Write the attributes
1139ierr=NF_PUT_ATT_TEXT(nid,nvarid,"title",len_trim(adjustl(title)),adjustl(title))
1140ierr=NF_PUT_ATT_TEXT(nid,nvarid,"units",len_trim(adjustl(units)),adjustl(units))
1141
1142! End netcdf define mode
1143ierr=NF_ENDDEF(nid)
1144
1145end subroutine def_var
1146!******************************************************************************
1147subroutine change_time_axis(nid,ierr)
1148!==============================================================================
1149! Purpose:
1150! Read "time" variable from a dataset, convert it from "sol" (martian
1151! days) to "Ls" (solar longitude) and write the result back in the file
1152!==============================================================================
1153! Remarks:
1154! The NetCDF file must be opened before this subroutine is called
1155!==============================================================================
1156
1157implicit none
1158
1159include "netcdf.inc" ! NetCDF definitions
1160
1161!==============================================================================
1162! Arguments:
1163!==============================================================================
1164integer, intent(in) :: nid
1165! nid: [netcdf] file ID
1166integer, intent(out) :: ierr
1167! ierr: [netcdf]  return error code
1168
1169!==============================================================================
1170! Local variables:
1171!==============================================================================
1172integer :: nvarid
1173! nvarid: ID of the "Time" variable
1174integer :: timelen
1175! timelen: size of the arrays
1176integer :: timedim
1177! timedim: ID of the "Time" dimension
1178integer i
1179
1180real, dimension(:), allocatable :: time,ls
1181! time(): time, given in sols
1182! ls(): time, given in Ls (solar longitude)
1183
1184!==============================================================================
1185! 1. Read
1186!==============================================================================
1187
1188ierr=NF_INQ_DIMID(nid,"Time",timedim)
1189ierr=NF_INQ_VARID(nid,"Time",nvarid)
1190if (ierr.NE.NF_NOERR) then
1191   write(*,*) 'ERROR in change_time_axis: Field <Time> not found'
1192   print*, NF_STRERROR(ierr)
1193   stop ""
1194endif
1195
1196ierr=NF_INQ_DIMLEN(nid,timedim,timelen)
1197allocate(time(timelen),ls(timelen))
1198#ifdef NC_DOUBLE
1199ierr = NF_GET_VAR_DOUBLE(nid,nvarid,time)
1200#else
1201ierr = NF_GET_VAR_REAL(nid,nvarid,time)
1202#endif
1203if (ierr.ne.NF_NOERR) then
1204  write(*,*) "ERROR in change_time_axis: Failed to load Time"
1205  stop
1206endif
1207
1208!==============================================================================
1209! 2. Convert sols to Ls
1210!==============================================================================
1211
1212do i=1,timelen
1213   call sol2ls(time(i),ls(i))
1214enddo
1215
1216!==============================================================================
1217! 2.1 Check if there are not jumps in Ls (rounding problems in sol2ls)
1218!==============================================================================
1219
1220do i=1,timelen-1
1221   if ((ls(i+1)-ls(i)) > 350) then
1222       write(*,*) "+ 360 deg Ls jump solved:", ls(i), ls(i+1), "at timestep", i
1223      ls(i+1) = ls(i+1) - 360
1224       write(*,*) " corrected to now be:", ls(i), ls(i+1)
1225   else if ((ls(i)-ls(i+1)) > 350) then
1226       write(*,*) "- 360 deg Ls jump solved:", ls(i), ls(i+1), "at timestep", i
1227      ls(i+1) = ls(i+1) + 360
1228       write(*,*) " corrected to now be:", ls(i), ls(i+1)
1229   endif
1230enddo
1231
1232!==============================================================================
1233! 3. Write
1234!==============================================================================
1235
1236#ifdef NC_DOUBLE
1237ierr = NF_PUT_VAR_DOUBLE(nid,nvarid,ls)
1238#else
1239ierr = NF_PUT_VAR_REAL(nid,nvarid,ls)
1240#endif
1241if (ierr.ne.NF_NOERR) then
1242  write(*,*) "ERROR in change_time_axis: Failed to write Ls"
1243  stop
1244endif
1245
1246end subroutine change_time_axis
1247!******************************************************************************
1248subroutine sol2ls(sol,Ls)
1249!==============================================================================
1250! Purpose:
1251! Convert a date/time, given in sol (martian day),
1252! into solar longitude date/time, in Ls (in degrees),
1253! where sol=0 is (by definition) the northern hemisphere
1254!  spring equinox (where Ls=0).
1255!==============================================================================
1256! Notes:
1257! Even though "Ls" is cyclic, if "sol" is greater than N (martian) year,
1258! "Ls" will be increased by N*360
1259! Won't work as expected if sol is negative (then again,
1260! why would that ever happen?)
1261!==============================================================================
1262
1263implicit none
1264
1265!==============================================================================
1266! Arguments:
1267!==============================================================================
1268real,intent(in) :: sol
1269real,intent(out) :: Ls
1270
1271!==============================================================================
1272! Local variables:
1273!==============================================================================
1274real year_day,peri_day,timeperi,e_elips,twopi,degrad
1275data year_day /669./            ! # of sols in a martian year
1276data peri_day /485.0/           
1277data timeperi /1.9082314/
1278data e_elips  /0.093358/
1279data twopi       /6.2831853/    ! 2.*pi
1280data degrad   /57.2957795/      ! pi/180
1281
1282real zanom,xref,zx0,zdx,zteta,zz
1283
1284integer count_years
1285integer iter
1286
1287!==============================================================================
1288! 1. Compute Ls
1289!==============================================================================
1290
1291zz=(sol-peri_day)/year_day
1292zanom=twopi*(zz-nint(zz))
1293xref=abs(zanom)
1294
1295!  The equation zx0 - e * sin (zx0) = xref, solved by Newton
1296zx0=xref+e_elips*sin(xref)
1297do iter=1,20 ! typically, 2 or 3 iterations are enough
1298   zdx=-(zx0-e_elips*sin(zx0)-xref)/(1.-e_elips*cos(zx0))
1299   zx0=zx0+zdx
1300   if(abs(zdx).le.(1.e-7)) then
1301!      write(*,*)'iter:',iter,'     |zdx|:',abs(zdx)
1302      exit
1303   endif
1304enddo
1305
1306if(zanom.lt.0.) zx0=-zx0
1307
1308zteta=2.*atan(sqrt((1.+e_elips)/(1.-e_elips))*tan(zx0/2.))
1309Ls=zteta-timeperi
1310
1311if(Ls.lt.0.) then
1312   Ls=Ls+twopi
1313else
1314   if(Ls.gt.twopi) then
1315      Ls=Ls-twopi
1316   endif
1317endif
1318
1319Ls=degrad*Ls
1320! Ls is now in degrees
1321
1322!==============================================================================
1323! 1. Account for (eventual) years included in input date/time sol
1324!==============================================================================
1325
1326count_years=0 ! initialize
1327zz=sol  ! use "zz" to store (and work on) the value of sol
1328do while (zz.ge.year_day)
1329   count_years=count_years+1
1330   zz=zz-year_day
1331enddo
1332
1333! Add 360 degrees to Ls for every year
1334if (count_years.ne.0) then
1335   Ls=Ls+360.*count_years
1336endif
1337
1338
1339end subroutine sol2ls
1340!******************************************************************************
1341subroutine  missing_value(nout,nvarid,valid_range,missing)
1342!==============================================================================
1343! Purpose:
1344! Write "valid_range" and "missing_value" attributes (of a given
1345! variable) to a netcdf file
1346!==============================================================================
1347! Remarks:
1348! NetCDF file must be open
1349! Variable (nvarid) ID must be set
1350!==============================================================================
1351
1352implicit none
1353
1354include "netcdf.inc"  ! NetCDF definitions
1355
1356!==============================================================================
1357! Arguments:
1358!==============================================================================
1359integer, intent(in) :: nout
1360! nout: [netcdf] file ID #
1361integer, intent(in) :: nvarid
1362! varid: [netcdf] variable ID #
1363real, dimension(2), intent(in) :: valid_range
1364! valid_range(2): [netcdf] "valid_range" attribute (min and max)
1365real, intent(in) :: missing
1366! missing: [netcdf] "missing_value" attribute
1367
1368!==============================================================================
1369! Local variables:
1370!==============================================================================
1371integer :: ierr
1372! ierr: [netcdf] subroutine returned error code
1373!      INTEGER nout,nvarid,ierr
1374!      REAL missing
1375!      REAL valid_range(2)
1376
1377! Switch to netcdf dataset define mode
1378ierr = NF_REDEF (nout)
1379if (ierr.ne.NF_NOERR) then
1380   print*,'missing_value: '
1381   print*, NF_STRERROR(ierr)
1382endif
1383
1384! Write valid_range() attribute
1385#ifdef NC_DOUBLE
1386ierr=NF_PUT_ATT_DOUBLE(nout,nvarid,'valid_range',NF_DOUBLE,2,valid_range)
1387#else
1388ierr=NF_PUT_ATT_REAL(nout,nvarid,'valid_range',NF_FLOAT,2,valid_range)
1389#endif
1390
1391if (ierr.ne.NF_NOERR) then
1392   print*,'missing_value: valid_range attribution failed'
1393   print*, NF_STRERROR(ierr)
1394   !write(*,*) 'NF_NOERR', NF_NOERR
1395   !CALL abort
1396   stop ""
1397endif
1398
1399! Write "missing_value" attribute
1400#ifdef NC_DOUBLE
1401ierr= NF_PUT_ATT_DOUBLE(nout,nvarid,'missing_value',NF_DOUBLE,1,missing)
1402#else
1403ierr= NF_PUT_ATT_REAL(nout,nvarid,'missing_value',NF_FLOAT,1,missing)
1404#endif
1405
1406if (ierr.NE.NF_NOERR) then
1407   print*, 'missing_value: missing value attribution failed'
1408   print*, NF_STRERROR(ierr)
1409!    WRITE(*,*) 'NF_NOERR', NF_NOERR
1410!    CALL abort
1411   stop ""
1412endif
1413
1414! End netcdf dataset define mode
1415ierr = NF_ENDDEF(nout)
1416
1417end subroutine  missing_value
1418!******************************************************************************
1419
1420end program concatnc
Note: See TracBrowser for help on using the repository browser.