source: trunk/LMDZ.MARS/libf/dynphy_lonlat/phymars/datareadnc.F @ 2878

Last change on this file since 2878 was 2082, checked in by mvals, 6 years ago

Mars GCM:

  • follow-up of the last change in datareadnc.F

MV

File size: 14.3 KB
Line 
1c=======================================================================
2      SUBROUTINE datareadnc(relief,phisinit,alb,ith,z0,
3     &                    zmea,zstd,zsig,zgam,zthe,
4     &                    hmons,summit,base,zavg)
5c=======================================================================
6c
7c
8c   Author: F. Hourdin      01/1997
9c   -------
10c
11c   Object: To read data from Martian surface to use in a GCM
12c   ------                from NetCDF file "surface.nc"
13c
14c
15c   Arguments:
16c   ----------
17c
18c     Inputs:
19c     ------
20c
21c     Outputs:
22c     --------
23c
24c=======================================================================
25c   donnees ALBEDO, INERTIE THERMIQUE, RELIEF:
26c
27c       Ces donnees sont au format NetCDF dans le fichier "surface.nc"
28c
29c   360 valeurs en longitude (de -179.5 a 179.5)
30c   180 valeurs en latitudes (de 89.5 a -89.5)
31c
32c   Pour les passer au format de la grille, on utilise "interp_horiz.F"
33c
34c   Il faut donc que ces donnees soient au format grille scalaire
35c               (imold+1 jmold+1)
36c       avec passage des coordonnees de la "boite" (rlonu, rlatv)
37c
38c   On prend imd (d pour donnees!)
39c           imd = 360 avec copie de la 1ere valeur sur la imd+1
40c                   (rlonud de -179 a -181)
41c           jmd = 179
42c                   (rlatvd de 89 a -89)
43c=======================================================================
44
45! to use  'getin'
46      use ioipsl_getincom, only: getin
47      use comconst_mod, only: g,pi
48      use datafile_mod, only: datadir
49      use avg_horiz_mod, only: avg_horiz
50      use mvc_horiz_mod, only: mvc_horiz
51
52      implicit none
53
54      include "dimensions.h"
55      include "paramet.h"
56      include "comgeom.h"
57      include "netcdf.inc"
58
59c=======================================================================
60c   Declarations:
61C=======================================================================
62
63      INTEGER    imd,jmd,imdp1,jmdp1
64      parameter    (imd=360,jmd=179,imdp1=361,jmdp1=180)
65
66      INTEGER    iimp1
67      parameter    (iimp1=iim+1-1/iim)
68
69! Arguments:
70      CHARACTER(len=3),intent(inout) :: relief
71      REAL,intent(out) :: phisinit(iimp1*jjp1)
72      REAL,intent(out) :: alb(iimp1*jjp1)
73      REAL,intent(out) :: ith(iimp1*jjp1)
74      REAL,intent(out) :: z0(iimp1*jjp1)
75      REAL,intent(out) :: zmea(imdp1*jmdp1)
76      REAL,intent(out) :: zstd(imdp1*jmdp1)
77      REAL,intent(out) :: zsig(imdp1*jmdp1)
78      REAL,intent(out) :: zgam(imdp1*jmdp1)
79      REAL,intent(out) :: zthe(imdp1*jmdp1)
80      REAL,intent(out) :: hmons(imdp1*jmdp1) !CW17,361*180 hmons
81      REAL,intent(out) :: summit(imdp1*jmdp1)
82      REAL,intent(out) :: base(imdp1*jmdp1)
83      REAL,intent(out) :: zavg(imdp1*jmdp1)
84     
85! Local variables:
86      REAL        zdata(imd*jmdp1)
87      REAL        zdataS(imdp1*jmdp1)
88      REAL        pfield(iimp1*jjp1)
89
90      INTEGER     ierr
91
92      INTEGER   unit,nvarid
93
94      INTEGER    i,j,k
95
96      INTEGER klatdat,ngridmxgdat
97      PARAMETER (klatdat=180,ngridmxgdat=360)
98
99c    on passe une grille en rlonu rlatv et im+1 jm a interp_horiz)
100
101      REAL longitude(imd),latitude(jmdp1) ! Pour lecture des donnees
102      REAL rlonud(imdp1),rlatvd(jmd)
103
104      CHARACTER*20 string
105      DIMENSION string(0:7)
106
107
108!#include "lmdstd.h"
109!#include "fxyprim.h"
110
111      pi=2.*ASIN(1.)
112
113c=======================================================================
114c    rlonud, rlatvd
115c=======================================================================
116
117c-----------------------------------------------------------------------
118c    Lecture NetCDF des donnees latitude et longitude
119c-----------------------------------------------------------------------
120      write(*,*) 'datareadnc: opening file surface.nc'
121
122      datadir="/u/lmdz/WWW/planets/mars/datadir" ! default path to surface.nc
123      call getin("datadir",datadir) ! but users may specify another path
124     
125      ierr = NF_OPEN (trim(datadir)//'/surface.nc',
126     &  NF_NOWRITE,unit)
127      IF (ierr.NE.NF_NOERR) THEN
128        write(*,*)'Error : cannot open file surface.nc '
129        write(*,*)'(in phymars/datareadnc.F)'
130        write(*,*)'It should be in :',trim(datadir),'/'
131        write(*,*)'1) You can set this path in the
132     & callphys.def file:'
133        write(*,*)'   datadir=/path/to/the/datafiles'
134        write(*,*)'2) If necessary, surface.nc (and other datafiles)'
135        write(*,*)'   can be obtained online on:'
136        write(*,*)'http://www.lmd.jussieu.fr/~lmdz/planets/mars/datadir'
137        CALL ABORT
138      ENDIF
139
140c
141c Lecture des latitudes (coordonnees):
142c
143      ierr = NF_INQ_VARID (unit, "latitude", nvarid)
144#ifdef NC_DOUBLE
145      ierr = NF_GET_VAR_DOUBLE(unit, nvarid, latitude)
146#else
147      ierr = NF_GET_VAR_REAL(unit, nvarid, latitude)
148#endif
149c
150c Lecture des longitudes (coordonnees):
151c
152      ierr = NF_INQ_VARID (unit, "longitude", nvarid)
153#ifdef NC_DOUBLE
154      ierr = NF_GET_VAR_DOUBLE(unit, nvarid, longitude)
155#else
156      ierr = NF_GET_VAR_REAL(unit, nvarid, longitude)
157#endif
158
159c-----------------------------------------------------------------------
160c    Passage au format boites scalaires
161c-----------------------------------------------------------------------
162
163c-----------------------------------------------------------------------
164c       longitude(imd)        -->      rlonud(imdp1)
165c-----------------------------------------------------------------------
166
167c Passage en coordonnees boites scalaires et en radian
168      do i=1,imd
169          rlonud(i)=(longitude(i)+.5)*pi/180.
170      enddo
171
172c Repetition de la valeur im+1
173      rlonud(imdp1)=rlonud(1) + 2*pi
174
175c-----------------------------------------------------------------------
176c        latitude(jmdp1)         -->        rlonvd(jmd)
177c-----------------------------------------------------------------------
178
179c Passage en coordonnees boites scalaires et en radian
180      do j=1,jmd
181          rlatvd(j)=(latitude(j)-.5)*pi/180.
182      enddo
183
184c=======================================================================
185c   lecture NetCDF de albedo, thermal, relief, zdtm (pour francois Lott)
186c=======================================================================
187
188      string(0) = 'z0'
189      string(1) = 'albedo'
190      string(2) = 'thermal'
191      if (relief.ne.'pla') then
192        write(*,*) ' MOLA topography'
193        relief = 'MOL'
194          string(3) = 'z'//relief
195      else
196          string(3) = 'zMOL'  ! pour qu''il lise qqchose sur le fichier
197                            ! remise a 0 derriere
198      endif
199      string(4) = 'zMOL'    ! lecture pour calcul topog. sous-maille
200 
201
202      DO k=0,4
203          write(*,*) 'string',k,string(k)
204         
205c-----------------------------------------------------------------------
206c    initialisation
207c-----------------------------------------------------------------------
208      call initial0(iimp1*jjp1,pfield)
209      call initial0(imd*jmdp1,zdata)
210      call initial0(imdp1*jmdp1,zdataS)
211
212c-----------------------------------------------------------------------
213c    Lecture NetCDF 
214c-----------------------------------------------------------------------
215
216      ierr = NF_INQ_VARID (unit, string(k), nvarid)
217      if (ierr.ne.nf_noerr) then
218        write(*,*) 'datareadnc error, cannot find ',trim(string(k))
219        write(*,*) ' in file ',trim(datadir),'/surface.nc'
220        stop
221      endif
222#ifdef NC_DOUBLE
223      ierr = NF_GET_VAR_DOUBLE(unit, nvarid, zdata)
224#else
225      ierr = NF_GET_VAR_REAL(unit, nvarid, zdata)
226#endif
227      if (ierr.ne.nf_noerr) then
228        write(*,*) 'datareadnc: error failed loading ',trim(string(k))
229        stop
230      endif
231
232c-----------------------------------------------------------------------
233c        Cas particulier "Francois Lott" ( k=4 ) (relief sous-maille)
234c-----------------------------------------------------------------------
235      if (k.eq.4) then
236
237          zdata(:)=1000.*zdata(:)
238          longitude(:)=(pi/180.)*longitude(:)
239          latitude(:)=(pi/180.)*latitude(:)
240
241          call grid_noro1(360, 180, longitude, latitude, zdata,
242     .         iim, jjp1, rlonv, rlatu, zmea,zstd,zsig,zgam,zthe)
243     
244          !CW17
245          call avg_horiz(imd,jmdp1,iim,jjm,longitude,
246     .                latitude,rlonv,rlatu,zdata,pfield)
247
248          do j=1,jjp1 !CW17 49, iimp1=65, the last column = first column
249             pfield(iimp1*j) =  pfield(1+iimp1*(j-1))
250          enddo
251          do i=1,iimp1*jjp1
252c             if (pfield(i) .ne. -999999.) then
253                zavg(i) = pfield(i)
254c             else
255c               zavg(i)=-999999.
256c             endif
257          enddo
258
259      endif
260
261c-----------------------------------------------------------------------
262c   Passage de zdata en grille (imdp1 jmdp1)
263c-----------------------------------------------------------------------
264      do j=1,jmdp1
265          do i=1,imd
266              zdataS(i+imdp1*(j-1)) = zdata(i+ngridmxgdat*(j-1))
267          enddo
268          zdataS(imdp1+imdp1*(j-1)) = zdata(1+ngridmxgdat*(j-1))
269      enddo
270
271c-----------------------------------------------------------------------
272c    Interpolation
273c-----------------------------------------------------------------------
274      call interp_horiz(zdataS,pfield,imd,jmd,
275     .    iim, jjm,1,rlonud,rlatvd,rlonu,rlatv)
276
277c-----------------------------------------------------------------------
278c    Periodicite   
279c-----------------------------------------------------------------------
280
281      do j=1,jjp1
282         pfield(iimp1*j) =  pfield(1+iimp1*(j-1))
283      enddo
284 
285c-----------------------------------------------------------------------
286c    Sauvegarde des champs   
287c-----------------------------------------------------------------------
288
289      if (k.eq.0) then                    ! z0
290         z0(1:iimp1*jjp1)=pfield(1:iimp1*jjp1)*.01
291         ! multiplied by 0.01 to have z0 in m
292      elseif (k.eq.1) then                    ! albedo
293         do i=1,iimp1*jjp1
294              alb(i) = pfield(i)
295          enddo
296      elseif (k.eq.2) then                ! thermal
297         do i=1,iimp1*jjp1
298              ith(i) = pfield(i)
299          enddo
300      elseif (k.eq.3) then                ! relief
301        if (relief.eq.'pla') then
302              call initial0(iimp1*jjp1,phisinit)
303        else
304             do i=1,iimp1*jjp1
305                  phisinit(i) = pfield(i)
306              enddo
307        endif
308      endif
309
310      ENDDO
311
312c-----------------------------------------------------------------------
313c    Traitement Phisinit
314c-----------------------------------------------------------------------
315
316      phisinit(1:iimp1*jjp1)=1000.*phisinit(1:iimp1*jjp1)
317      phisinit(:)=g*phisinit(:)
318
319c-----------------------------------------------------------------------
320c    FIN
321c-----------------------------------------------------------------------
322 
323c=======================================================================
324c<<<<<<<<<<<<<<<<<<<<<<<add new dataset>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
325      ! name of dataset
326      string(5) = 'hmons' !subgrid hmons
327c     the following data could be useful in future, but currently,
328c     we don't need to put them into restartfi.nc
329      string(6) = 'summit' !subgrid summit
330      string(7) = 'base'   !base of summit (not subgrid)
331c     string(8) = 'bottom' !subgrid base
332      do k=5,7
333          write(*,*) 'string',k,string(k) 
334c-----------------------------------------------------------------------
335c    Lecture NetCDF 
336c-----------------------------------------------------------------------
337
338          ierr = NF_INQ_VARID (unit, string(k), nvarid)
339          if (ierr.ne.nf_noerr) then
340            write(*,*) 'datareadnc error, cannot find ',trim(string(k))
341            write(*,*) ' in file ',trim(datadir),'/surface.nc'
342            stop
343          endif
344
345c-----------------------------------------------------------------------
346c    initialisation
347c-----------------------------------------------------------------------
348          call initial0(iimp1*jjp1,pfield)
349          call initial0(imd*jmdp1,zdata)
350          call initial0(imdp1*jmdp1,zdataS)
351
352#ifdef NC_DOUBLE
353          ierr = NF_GET_VAR_DOUBLE(unit, nvarid, zdata)
354#else
355          ierr = NF_GET_VAR_REAL(unit, nvarid, zdata)
356#endif
357          if (ierr.ne.nf_noerr) then
358            write(*,*) 'datareadnc: error failed loading ',
359     .                  trim(string(k))
360            stop
361          endif
362
363c-----------------------------------------------------------------------
364c   Passage de zdata en grille (imdp1 jmdp1)
365c-----------------------------------------------------------------------
366          do j=1,jmdp1     !  180
367              do i=1,imd   !  360
368                  !copy zdata to zdataS, line by line
369                  !      i+ 361 *(j-1)          i+  360*(j-1)
370                  zdataS(i+imdp1*(j-1)) = zdata(i+ngridmxgdat*(j-1))
371              enddo
372              ! the last column = the first column of zdata
373              zdataS(imdp1+imdp1*(j-1)) = zdata(1+ngridmxgdat*(j-1))
374          enddo
375
376          if (k .eq. 5 .or. k .eq. 6 .or. k .eq. 7) then
377              ! hmons, summit, keep the maximum of subgrids
378              call mvc_horiz(imd,jmdp1,iim,jjm,longitude,
379     .                latitude,rlonv,rlatu,zdata,pfield)
380          endif
381
382
383c-----------------------------------------------------------------------
384c    Periodicite   
385c-----------------------------------------------------------------------
386
387          do j=1,jjp1 ! 49, iimp1=65, the last column = first column
388             pfield(iimp1*j) =  pfield(1+iimp1*(j-1))
389          enddo
390 
391c-----------------------------------------------------------------------
392c    Sauvegarde des champs   
393c-----------------------------------------------------------------------
394
395          if (k.eq.5) then ! hmons
396             do i=1,iimp1*jjp1
397                  if (pfield(i) .ne. -999999.) then
398                    hmons(i) = pfield(i)
399                  else
400                    hmons(i)=0.
401                  endif
402             enddo
403          endif
404         
405          if (k.eq.6) then  ! summit
406             do i=1,iimp1*jjp1
407                  if (pfield(i) .ne. -999999.) then             
408                    summit(i) = pfield(i)
409                  else
410                    summit(i)=0.
411                  endif
412             enddo
413          endif
414
415          if (k.eq.7) then  ! base
416             do i=1,iimp1*jjp1
417                  if (pfield(i) .ne. -999999.) then             
418                    base(i) = pfield(i)
419                  else
420                    base(i)=0.
421                  endif
422             enddo
423          endif
424
425      enddo
426c<<<<<<<<<<<<<<<<<<<<<<<<<done add new dataset>>>>>>>>>>>>>>>>>>>>>>>>>>
427c=======================================================================
428      END
Note: See TracBrowser for help on using the repository browser.