source: trunk/LMDZ.MARS/libf/phymars/read_dust_scenario.F90 @ 1112

Last change on this file since 1112 was 1047, checked in by emillour, 11 years ago

Mars GCM:

  • IMPORTANT CHANGE: Removed all reference/use of ngridmx (dimphys.h) in routines (necessary prerequisite to using parallel dynamics); in most cases this just means adding 'ngrid' as routine argument, and making local saved variables allocatable (and allocated at first call). In the process, had to convert many *.h files to equivalent modules: yomaer.h => yomaer_h.F90 , surfdat.h => surfdat_h.F90 , comsaison.h => comsaison_h.F90 , yomlw.h => yomlw_h.F90 , comdiurn.h => comdiurn_h.F90 , dimradmars.h => dimradmars_mod.F90 , comgeomfi.h => comgeomfi_h.F90, comsoil.h => comsoil_h.F90 , slope.h => slope_mod.F90
  • Also updated EOF routines, everything is now in eofdump_mod.F90
  • Removed unused routine lectfux.F (in dyn3d)

EM

File size: 9.4 KB
Line 
1subroutine read_dust_scenario(ngrid,nlayer,zday,pplev,tauref)
2
3! Reading of the dust scenario file
4
5use netcdf
6use comgeomfi_h, only: lati, long
7implicit none
8
9#include "dimensions.h"
10#include "dimphys.h"
11!#include "comgeomfi.h"
12#include "datafile.h"
13#include "callkeys.h"
14
15integer, intent(in) :: ngrid,nlayer
16real, intent(in) :: zday ! date in martian days
17real, dimension(ngrid,nlayer+1), intent(in) :: pplev
18real, dimension(ngrid), intent(out) :: tauref
19
20! Local variables
21
22real :: realday
23integer nid,nvarid,ierr
24integer ltloop,lsloop,iloop,jloop,varloop,ig
25real, dimension(2) :: taubuf
26real tau1(4),tau
27real alt(4)
28integer latp(4),lonp(4)
29integer yinf,ysup,xinf,xsup,tinf,tsup
30real latinf,latsup,loninf,lonsup
31real latintmp,lonintmp,latdeg,londeg
32real colat,dlat,dlon,colattmp
33logical, save :: firstcall=.true.
34logical :: timeflag
35real,save :: radeg,pi
36integer :: timedim,londim,latdim
37real, dimension(:), allocatable, save :: lat,lon,time
38real, dimension(:,:,:), allocatable, save :: tautes
39integer, save :: timelen,lonlen,latlen
40character(len=33),save :: filename
41
42realday=mod(zday,669.)
43
44if (firstcall) then
45   firstcall=.false.
46
47   pi=acos(-1.)
48   radeg=180/pi
49   
50   ! assimilated dust file: (NB: iaervar is a common in "callkeys.h")
51   ! iaervar=4 means read dust_tes.nc file
52   ! iaervar=6 means read dust_cold.nc file
53   ! iaervar=7 means read dust_warm.nc file
54   ! iaervar=24 means read dust_MY24.nc file
55   ! iaervar=25 means read dust_MY25.nc file
56   ! iaervar=26 means read dust_MY26.nc file, etc.
57   if (iaervar.eq.4) then
58   ! NB: 4: old TES assimilated MY24 dust scenarios (at 700Pa ref pressure!)
59     filename="dust_tes.nc"
60   else if (iaervar.eq.6) then
61     filename="dust_cold.nc"
62   else if (iaervar.eq.7) then
63     filename="dust_warm.nc"
64   else if (iaervar.eq.24) then
65     filename="dust_MY24.nc"
66   else if (iaervar.eq.25) then
67     filename="dust_MY25.nc"
68   else if (iaervar.eq.26) then
69     filename="dust_MY26.nc"
70   else if (iaervar.eq.27) then
71     filename="dust_MY27.nc"
72   else if (iaervar.eq.28) then
73     filename="dust_MY28.nc"
74   else if (iaervar.eq.29) then
75     filename="dust_MY29.nc"   
76   else if (iaervar.eq.30) then
77     filename="dust_MY30.nc"   
78   ! 124,125,126: old TES assimilated dust scenarios (at 700Pa ref pressure!)
79   else if  (iaervar.eq.124) then
80     filename="dust_tes_MY24.nc"
81   else if (iaervar.eq.125) then
82     filename="dust_tes_MY25.nc"
83   else if (iaervar.eq.126) then
84     filename="dust_tes_MY26.nc"
85   endif
86   
87   ! Note: datafile() is defined in "datafile.h"
88   !ierr=NF_OPEN(trim(datafile)//"/"//trim(filename),NF_NOWRITE,nid)
89   ierr=nf90_open(trim(datafile)//"/"//trim(filename),NF90_NOWRITE,nid)
90   IF (ierr.NE.nf90_noerr) THEN
91     write(*,*)'Problem opening ',trim(filename),' (in phymars/read_dust_scenario.F90)'
92     write(*,*)'It should be in :',trim(datafile),'/'
93     write(*,*)'1) You can change this directory address in callfis.def with'
94     write(*,*)'   datadir=/path/to/datafiles'
95     write(*,*)'2) If necessary, dust*.nc (and other datafiles)'
96     write(*,*)'   can be obtained online on:'
97     write(*,*)'   http://www.lmd.jussieu.fr/~forget/datagcm/datafile'
98     CALL ABORT
99   ENDIF
100
101   ierr=nf90_inq_dimid(nid,"Time",timedim)
102   if (ierr.ne.nf90_noerr) then
103    ! 'Time' dimension not found, look for 'time'
104    ierr=nf90_inq_dimid(nid,"time",timedim)
105    if (ierr.ne.nf90_noerr) then
106      write(*,*)"Error: read_dust_scenario <time> not found"
107    endif
108   endif
109   ierr=nf90_inquire_dimension(nid,timedim,len=timelen)
110   ierr=nf90_inq_dimid(nid,"latitude",latdim)
111   ierr=nf90_inquire_dimension(nid,latdim,len=latlen)
112   ierr=nf90_inq_dimid(nid,"longitude",londim)
113   ierr=nf90_inquire_dimension(nid,londim,len=lonlen)
114
115
116   allocate(tautes(lonlen,latlen,timelen))
117   allocate(lat(latlen), lon(lonlen), time(timelen))
118
119   ierr=nf90_inq_varid(nid,"dustop",nvarid)
120   ierr=nf90_get_var(nid,nvarid,tautes)
121   IF (ierr .NE. nf90_noerr) THEN
122      PRINT*, "Error: read_dust_scenario <dustop> not found"
123      write(*,*)trim(nf90_strerror(ierr))
124      stop
125   ENDIF
126
127   ierr=nf90_inq_varid(nid,"Time",nvarid)
128   ierr=nf90_get_var(nid,nvarid,time)
129   IF (ierr .NE. nf90_noerr) THEN
130      PRINT*, "Error: read_dust_scenario <Time> not found"
131      write(*,*)trim(nf90_strerror(ierr))
132      stop
133   ENDIF
134
135   ierr=nf90_inq_varid(nid,"latitude",nvarid)
136   ierr=nf90_get_var(nid,nvarid,lat)
137   IF (ierr .NE. nf90_noerr) THEN
138      PRINT*, "Error: read_dust_scenario <latitude> not found"
139      write(*,*)trim(nf90_strerror(ierr))
140      stop
141   ENDIF
142
143   ierr=nf90_inq_varid(nid,"longitude",nvarid)
144   ierr=nf90_get_var(nid,nvarid,lon)
145   IF (ierr .NE. nf90_noerr) THEN
146      PRINT*, "Error: read_dust_scenario <longitude> not found"
147      write(*,*)trim(nf90_strerror(ierr))
148      stop
149   ENDIF
150
151   ierr=nf90_close(nid)
152
153endif ! of if (firstcall)
154
155do ig=1,ngrid
156
157! Find the four nearest points, arranged as follows:
158!                               1 2
159!                               3 4
160
161   latdeg=lati(ig)*radeg  ! latitude, in degrees
162   londeg=long(ig)*radeg  ! longitude, in degrees east
163   colat=90-latdeg        ! colatitude, in degrees
164
165! Ehouarn: rounding effects and/or specific compiler issues
166!          sometime cause londeg to be sligthly below -180 ...
167  if (londeg.lt.-180) then
168    ! check if it is by a large amount
169    if ((londeg+180).lt.-1.e-3) then
170      write(*,*) 'reattesassim: error!!'
171      write(*,*) ' ig=',ig,' londeg=',londeg
172      stop
173    else
174      londeg=-180
175    endif
176  endif
177
178 ! Find encompassing latitudes
179   if (colat<(90-lat(1))) then ! between north pole and lat(1)
180      ysup=1
181      yinf=1
182   else if (colat>=90-(lat(latlen))) then ! between south pole and lat(laten)
183      ysup=latlen
184      yinf=latlen
185   else ! general case
186      do iloop=2,latlen
187         if(colat<(90-lat(iloop))) then
188           ysup=iloop-1
189           yinf=iloop
190           exit
191         endif
192      enddo
193   endif
194
195   latinf=lat(yinf)
196   latsup=lat(ysup)
197
198
199 ! Find encompassing longitudes
200   ! Note: in input file, lon(1)=-180.
201   if (londeg>lon(lonlen)) then
202      xsup=1
203      xinf=lonlen
204      loninf=lon(xsup)
205      lonsup=180.0 ! since lon(1)=-180.0
206   else
207      do iloop=2,lonlen
208         if(londeg<lon(iloop)) then
209              xsup=iloop
210              xinf=iloop-1
211              exit
212         endif
213      enddo
214      loninf=lon(xinf)
215      lonsup=lon(xsup)
216   endif
217
218   if ((xsup.gt.lonlen).OR.(yinf.gt.latlen).OR.(xinf.lt.1)&
219     .OR.(ysup.lt.1)) then
220      write (*,*) "read_dust_scenario: SYSTEM ERROR on x or y in ts_gcm"
221      write (*,*) "xinf: ",xinf
222      write (*,*) "xsup: ",xsup
223      write (*,*) "yinf: ",yinf
224      write (*,*) "ysup: ",ysup
225      stop
226   endif
227
228!   loninf=lon(xinf)
229!   lonsup=lon(xsup)
230!   latinf=lat(yinf)
231!   latsup=lat(ysup)
232
233! The four neighbouring points are arranged as follows:
234!                               1 2
235!                               3 4
236
237   latp(1)=ysup
238   latp(2)=ysup
239   latp(3)=yinf
240   latp(4)=yinf
241
242   lonp(1)=xinf
243   lonp(2)=xsup
244   lonp(3)=xinf
245   lonp(4)=xsup
246
247! Linear interpolation on time, for all four neighbouring points
248
249   if ((realday<time(1)).or.(realday>time(timelen))) then
250      tinf=timelen
251      tsup=1
252      timeflag=.true.
253   else
254      timeflag=.false.
255      do iloop=2,timelen
256         if (realday<time(iloop)) then
257            tinf=iloop-1
258            tsup=iloop
259            exit
260         endif
261      enddo
262   endif
263
264! Bilinear interpolation on the four nearest points
265
266   if ((colat<(90-lat(1))).OR.(colat>(90-lat(latlen))).OR.(latsup==latinf)) then
267      dlat=0
268   else
269      dlat=((90-latinf)-colat)/((90-latinf)-(90-latsup))
270   endif
271
272   if (lonsup==loninf) then
273      dlon=0
274   else
275      dlon=(londeg-loninf)/(lonsup-loninf)
276   endif
277
278   do iloop=1,4
279      taubuf(1)=tautes(lonp(iloop),latp(iloop),tinf)
280      taubuf(2)=tautes(lonp(iloop),latp(iloop),tsup)
281      if (timeflag) then
282         if (realday>time(timelen)) then
283            tau1(iloop)=taubuf(1)+(taubuf(2)-taubuf(1))*(realday-time(tinf))/(time(tsup)+(669-time(tinf)))
284         else
285            tau1(iloop)=taubuf(1)+(taubuf(2)-taubuf(1))*realday/(time(tsup)+(669-time(tinf)))
286         endif
287      else
288         tau1(iloop)=taubuf(1)+(taubuf(2)-taubuf(1))*(realday-time(tinf))/(time(tsup)-time(tinf))
289      endif
290      if (tau1(iloop)<0) then
291          write (*,*) "read_dust_scenario: SYSTEM ERROR on tau"
292          write (*,*) "utime ",realday
293          write (*,*) "time(tinf) ",time(tinf)
294          write (*,*) "time(tsup) ",time(tsup)
295          write (*,*) "tau1 ",taubuf(1)
296          write (*,*) "tau2 ",taubuf(2)
297          write (*,*) "tau ",tau1(iloop)
298          stop
299      endif
300   enddo
301
302   if ((dlat>1).OR.(dlon>1) .OR. (dlat<0) .OR. (dlon<0)) then
303      write (*,*) "read_dust_scenario: SYSTEM ERROR on dlat or dlon in ts_gcm"
304      write (*,*) "dlat: ",dlat
305      write (*,*) "lat: ",latdeg
306      write (*,*) "dlon: ",dlon
307      write (*,*) "lon: ",londeg
308      stop
309   endif
310
311   tau= dlat*(dlon*(tau1(2)+tau1(3)-tau1(1)-tau1(4))+tau1(1)-tau1(3)) +dlon*(tau1(4)-tau1(3))+tau1(3)
312
313   tauref(ig)=tau
314!
315enddo ! of ig=1,ngrid
316
317if (filename(1:8)=="dust_tes") then
318  ! when using old TES files, correction for:
319  ! - the reference pressure was 700Pa (unlike 610Pa now)
320  ! - the 1.3 conversion factor from IR absorbtion opacity to
321  !   IR extinction opacity
322  tauref(:)=tauref(:)*1.3*(610./700.)
323endif
324
325if (swrtype.eq.1) then ! Fouquart (NB: swrtype is set in callkeys.h)
326 ! when using old radiative transfer (like in MCD 4.x)
327 ! needed to decrease opacity (*0.825) to compensate overestimation of
328 ! heating rates
329  tauref(:)=tauref(:)*0.825/1.3
330endif
331
332end
Note: See TracBrowser for help on using the repository browser.