source: CPL/oasis3-mct/branches/OASIS3-MCT_2.0_branch/lib/psmile/src/mod_oasis_grid.F90 @ 4775

Last change on this file since 4775 was 4775, checked in by aclsce, 5 years ago
  • Imported oasis3-mct from Cerfacs svn server (not suppotred anymore).

The version has been extracted from https://oasis3mct.cerfacs.fr/svn/branches/OASIS3-MCT_2.0_branch/oasis3-mct@1818

File size: 25.0 KB
Line 
1MODULE mod_oasis_grid
2!-----------------------------------------------------------------------
3! BOP
4!
5! !MODULE:  mod_prism_grid
6! !REMARKS:
7!
8! **********************
9! THIS SHOULD BE CALLED BY A SINGLE PE ACCORDING TO THE OASIS3
10! STANDARD.  THE DATA IS GLOBAL.
11! **********************
12!
13! !REVISION HISTORY:
14!
15!
16! !PUBLIC MEMBER FUNCTIONS:
17!
18!      subroutine oasis_start_grids_writing(iwrite)
19!             This subroutine initializes grid writing by receiving a
20!             starting command from OASIS.
21!
22!      subroutine oasis_write_grid(cgrid, nx, ny, lon, lat)
23!             This subroutine writes longitudes and latitudes for a model
24!             grid.
25!
26!      subroutine oasis_write_corner(cgrid, nx, ny, nc, clon, clat)
27!             This subroutine writes the longitudes and latitudes of the
28!             grid cell corners.
29!
30!      subroutine oasis_write_mask(cgrid, nx, ny, mask)
31!             This subroutine writes the mask for a model grid
32!
33!      subroutine oasis_write_area(cgrid, nx, ny, area)
34!             This subroutine writes the grid cell areas for a model grid.
35!
36!      subroutine oasis_terminate_grids_writing()
37!             This subroutine terminates grid writing by sending a flag
38!             to OASIS, stating the all needed grid information was written.
39!       
40
41! !USES:
42  use mod_oasis_data
43  use mod_oasis_io
44  use mod_oasis_sys
45 
46  implicit none
47
48  private
49
50  public oasis_start_grids_writing
51  public oasis_write_grid
52  public oasis_write_angle
53  public oasis_write_corner
54  public oasis_write_mask
55  public oasis_write_area   
56  public oasis_terminate_grids_writing 
57  public oasis_write2files
58
59  interface oasis_write_grid
60#ifndef __NO_4BYTE_REALS
61     module procedure oasis_write_grid_r4
62#endif
63     module procedure oasis_write_grid_r8
64  end interface
65
66  interface oasis_write_angle
67#ifndef __NO_4BYTE_REALS
68     module procedure oasis_write_angle_r4
69#endif
70     module procedure oasis_write_angle_r8
71  end interface
72
73  interface oasis_write_corner
74#ifndef __NO_4BYTE_REALS
75     module procedure oasis_write_corner_r4
76#endif
77     module procedure oasis_write_corner_r8
78  end interface
79
80  interface oasis_write_area
81#ifndef __NO_4BYTE_REALS
82     module procedure oasis_write_area_r4
83#endif
84     module procedure oasis_write_area_r8
85  end interface
86
87  !--- datatypes ---
88  public :: prism_grid_type
89
90  integer(kind=ip_intwp_p),parameter :: mgrid = 100
91
92  type prism_grid_type
93     character(len=ic_med)  :: gridname
94     integer(kind=ip_i4_p)  :: nx
95     integer(kind=ip_i4_p)  :: ny
96     integer(kind=ip_i4_p)  :: nc
97     logical                :: grid_set
98     logical                :: corner_set
99     logical                :: angle_set
100     logical                :: area_set
101     logical                :: mask_set
102     logical                :: written
103     logical                :: terminated
104     real(kind=ip_realwp_p),allocatable :: lon(:,:)     ! longitudes
105     real(kind=ip_realwp_p),allocatable :: lat(:,:)     ! latitudes
106     real(kind=ip_realwp_p),allocatable :: clon(:,:,:)  ! corner longitudes
107     real(kind=ip_realwp_p),allocatable :: clat(:,:,:)  ! corner latitudes
108     real(kind=ip_realwp_p),allocatable :: angle(:,:)   ! angle
109     real(kind=ip_realwp_p),allocatable :: area(:,:)    ! area
110     integer(kind=ip_i4_p) ,allocatable :: mask(:,:)    ! mask
111  end type prism_grid_type
112
113  integer(kind=ip_intwp_p),public,save :: prism_ngrid = 0
114  type(prism_grid_type),public,save :: prism_grid(mgrid)
115
116
117#ifdef use_netCDF
118#include <netcdf.inc>
119#endif
120
121!---------------------------------------------------------------------------
122
123CONTAINS
124
125!--------------------------------------------------------------------------
126    SUBROUTINE oasis_start_grids_writing(iwrite)
127
128    !-------------------------------------------------
129    ! Routine to start the grids writing. To syncronize access to the
130    ! grids file all component models have to wait for the starting
131    ! message from OASIS (via MPI; see prism_init_comp_proto)
132    !-------------------------------------------------
133
134    implicit none
135 
136    integer(kind=ip_intwp_p), intent (OUT) :: iwrite ! flag to state whether
137                                            ! grids file needs to be written
138    !-------------------------------------------------
139    character(len=*),parameter :: subname = 'oasis_start_grids_writing'
140    !-------------------------------------------------
141
142    call oasis_debug_enter(subname)
143
144    if (mpi_rank_local /= mpi_root_local) then
145       write(nulprt,*) subname,' ERROR subroutine call by non root processor'
146       WRITE(nulprt,*) subname,' abort by model :',compid,' proc :',mpi_rank_local
147       CALL oasis_flush(nulprt)
148       call oasis_abort_noarg()
149    endif
150
151    if (prism_ngrid == 0) then  ! first call
152       prism_grid(:)%grid_set   = .false.
153       prism_grid(:)%corner_set = .false.
154       prism_grid(:)%angle_set  = .false.
155       prism_grid(:)%area_set   = .false.
156       prism_grid(:)%mask_set   = .false.
157       prism_grid(:)%written    = .false.
158    endif
159    iwrite = 1   ! just set grids are needed always
160
161    call oasis_debug_exit(subname)
162
163  END SUBROUTINE oasis_start_grids_writing
164
165!--------------------------------------------------------------------------
166
167    SUBROUTINE oasis_write_grid_r8(cgrid, nx, ny, lon, lat)
168
169    !-------------------------------------------------
170    ! Routine to create a new grids file or to add a grid description to an
171    ! existing grids file.
172    !-------------------------------------------------
173
174    implicit none
175
176    character(len=*),         intent (in) :: cgrid      ! grid acronym
177    integer(kind=ip_intwp_p), intent (in) :: nx         ! number of longitudes
178    integer(kind=ip_intwp_p), intent (in) :: ny         ! number of latitudes
179    real(kind=ip_double_p),   intent (in) :: lon(nx,ny) ! longitudes
180    real(kind=ip_double_p),   intent (in) :: lat(nx,ny) ! latitudes
181    !-------------------------------------------------
182    integer(kind=ip_intwp_p) :: GRIDID
183    integer(kind=ip_intwp_p) :: ierror
184    character(len=*),parameter :: subname = 'oasis_write_grid_r8'
185    !-------------------------------------------------
186
187    call oasis_debug_enter(subname)
188
189    if (mpi_rank_local /= mpi_root_local) then
190       write(nulprt,*) subname,' ERROR subroutine call by non root processor'
191       WRITE(nulprt,*) subname,' abort by model :',compid,' proc :',mpi_rank_local
192       CALL oasis_flush(nulprt)
193       call oasis_abort_noarg()
194    endif
195
196    call oasis_findgrid(cgrid,nx,ny,gridID)
197
198    allocate(prism_grid(gridID)%lon(nx,ny),stat=ierror)
199    IF (ierror /= 0) WRITE(nulprt,*) subname,' model :',compid,' proc :',&
200                                     mpi_rank_local,' WARNING lon alloc'
201    allocate(prism_grid(gridID)%lat(nx,ny),stat=ierror)
202    if (ierror /= 0) write(nulprt,*) subname,' model :',compid,' proc :',&
203                                     mpi_rank_local,' WARNING lat alloc'
204    prism_grid(gridID)%lon = lon
205    prism_grid(gridID)%lat = lat
206    prism_grid(gridID)%grid_set = .true.
207
208    call oasis_debug_exit(subname)
209
210  END SUBROUTINE oasis_write_grid_r8
211
212!--------------------------------------------------------------------------
213
214    SUBROUTINE oasis_write_grid_r4(cgrid, nx, ny, lon, lat)
215
216    !-------------------------------------------------
217    ! Routine to create a new grids file or to add a grid description to an
218    ! existing grids file.
219    !-------------------------------------------------
220
221    implicit none
222
223    character(len=*),         intent (in) :: cgrid      ! grid acronym
224    integer(kind=ip_intwp_p), intent (in) :: nx         ! number of longitudes
225    integer(kind=ip_intwp_p), intent (in) :: ny         ! number of latitudes
226    real(kind=ip_single_p),   intent (in) :: lon(nx,ny) ! longitudes
227    real(kind=ip_single_p),   intent (in) :: lat(nx,ny) ! latitudes
228    !-------------------------------------------------
229    real(kind=ip_double_p), allocatable :: lon8(:,:)
230    real(kind=ip_double_p), allocatable :: lat8(:,:)
231    integer(kind=ip_intwp_p) :: ierror
232    character(len=*),parameter :: subname = 'oasis_write_grid_r4'
233    !-------------------------------------------------
234
235    call oasis_debug_enter(subname)
236
237    allocate(lon8(nx,ny),stat=ierror)
238    IF (ierror /= 0) WRITE(nulprt,*) subname,' model :',compid,' proc :',&
239                                     mpi_rank_local,' WARNING lon alloc'
240    allocate(lat8(nx,ny),stat=ierror)
241    if (ierror /= 0) write(nulprt,*) subname,' model :',compid,' proc :',&
242                                     mpi_rank_local,' WARNING lat alloc'
243
244    lon8 = lon
245    lat8 = lat
246    call oasis_write_grid_r8(cgrid,nx,ny,lon8,lat8)
247    deallocate(lon8)
248    deallocate(lat8)
249
250    call oasis_debug_exit(subname)
251
252  END SUBROUTINE oasis_write_grid_r4
253
254!--------------------------------------------------------------------------
255    SUBROUTINE oasis_write_angle_r8(cgrid, nx, ny, angle)
256
257    !-------------------------------------------------
258    ! Routine to add angles to an existing grid file.
259    !-------------------------------------------------
260
261    implicit none
262
263    character(len=*),         intent (in) :: cgrid       ! grid acronym
264    integer(kind=ip_intwp_p), intent (in) :: nx          ! number of longitudes
265    integer(kind=ip_intwp_p), intent (in) :: ny          ! number of latitudes
266    real(kind=ip_double_p),   intent (in) :: angle(nx,ny) ! angles
267    !-------------------------------------------------
268    integer(kind=ip_intwp_p) :: GRIDID
269    integer(kind=ip_intwp_p) :: ierror
270    character(len=*),parameter :: subname = 'oasis_write_angle_r8'
271    !-------------------------------------------------
272
273    call oasis_debug_enter(subname)
274
275    if (mpi_rank_local /= mpi_root_local) then
276       write(nulprt,*) subname,' ERROR subroutine call by non root processor'
277       WRITE(nulprt,*) subname,' abort by model :',compid,' proc :',mpi_rank_local
278       CALL oasis_flush(nulprt)
279       call oasis_abort_noarg()
280    endif
281
282    call oasis_findgrid(cgrid,nx,ny,gridID)
283
284    allocate(prism_grid(gridID)%angle(nx,ny),stat=ierror)
285    if (ierror /= 0) write(nulprt,*) subname,' model :',compid,' proc :',&
286                                     mpi_rank_local,' WARNING angle alloc'
287    prism_grid(gridID)%angle = angle
288    prism_grid(gridID)%angle_set = .true.
289
290    call oasis_debug_exit(subname)
291
292  END SUBROUTINE oasis_write_angle_r8
293
294!--------------------------------------------------------------------------
295    SUBROUTINE oasis_write_angle_r4(cgrid, nx, ny, angle)
296
297    !-------------------------------------------------
298    ! Routine to add angles to an existing grid file.
299    !-------------------------------------------------
300
301    implicit none
302
303    character(len=*),         intent (in) :: cgrid       ! grid acronym
304    integer(kind=ip_intwp_p), intent (in) :: nx          ! number of longitudes
305    integer(kind=ip_intwp_p), intent (in) :: ny          ! number of latitudes
306    real(kind=ip_single_p),   intent (in) :: angle(nx,ny) ! angles
307    !-------------------------------------------------
308    real(kind=ip_double_p),allocatable :: angle8(:,:)
309    integer(kind=ip_intwp_p) :: ierror
310    character(len=*),parameter :: subname = 'oasis_write_angle_r4'
311    !-------------------------------------------------
312
313    call oasis_debug_enter(subname)
314
315    allocate(angle8(nx,ny),stat=ierror)
316    if (ierror /= 0) write(nulprt,*) subname,' model :',compid,' proc :',&
317                                     mpi_rank_local,' WARNING angle8 alloc'
318
319    angle8 = angle
320    call oasis_write_angle_r8(cgrid,nx,ny,angle8)
321
322    deallocate(angle8)
323
324    call oasis_debug_exit(subname)
325
326  END SUBROUTINE oasis_write_angle_r4
327
328!--------------------------------------------------------------------------
329    SUBROUTINE oasis_write_corner_r8(cgrid, nx, ny, nc, clon, clat)
330
331    !-------------------------------------------------
332    ! Routine to add longitudes and latitudes of grid cell corners to an
333    ! existing grids file.
334    !-------------------------------------------------
335
336    implicit none
337
338    character(len=*),         intent (in) :: cgrid  ! grid acronym
339    integer(kind=ip_intwp_p), intent (in) :: nx     ! number of longitudes
340    integer(kind=ip_intwp_p), intent (in) :: ny     ! number of latitudes
341    integer(kind=ip_intwp_p), intent (in) :: nc     ! number of corners per cell
342    real(kind=ip_double_p),   intent (in) :: clon(nx,ny,nc) ! longitudes
343    real(kind=ip_double_p),   intent (in) :: clat(nx,ny,nc) ! latitudes
344    !-------------------------------------------------
345    integer(kind=ip_intwp_p) :: GRIDID
346    integer(kind=ip_intwp_p) :: ierror
347    character(len=*),parameter :: subname = 'oasis_write_corner_r8'
348    !-------------------------------------------------
349
350    call oasis_debug_enter(subname)
351
352    if (mpi_rank_local /= mpi_root_local) then
353       write(nulprt,*) subname,' ERROR subroutine call by non root processor'
354       WRITE(nulprt,*) subname,' abort by model :',compid,' proc :',mpi_rank_local
355       call oasis_abort_noarg()
356    endif
357
358    call oasis_findgrid(cgrid,nx,ny,gridID)
359
360    allocate(prism_grid(gridID)%clon(nx,ny,nc),stat=ierror)
361    if (ierror /= 0) write(nulprt,*) subname,' model :',compid,' proc :',&
362                                     mpi_rank_local,' WARNING clon alloc'
363    allocate(prism_grid(gridID)%clat(nx,ny,nc),stat=ierror)
364    if (ierror /= 0) write(nulprt,*) subname,' model :',compid,' proc :',&
365                                     mpi_rank_local,' WARNING clat alloc'
366    prism_grid(gridID)%nc = nc
367    prism_grid(gridID)%clon = clon
368    prism_grid(gridID)%clat = clat
369    prism_grid(gridID)%corner_set = .true.
370
371    call oasis_debug_exit(subname)
372
373  END SUBROUTINE oasis_write_corner_r8
374
375!--------------------------------------------------------------------------
376    SUBROUTINE oasis_write_corner_r4(cgrid, nx, ny, nc, clon, clat)
377
378    !-------------------------------------------------
379    ! Routine to add longitudes and latitudes of grid cell corners to an
380    ! existing grids file.
381    !-------------------------------------------------
382
383    implicit none
384
385    character(len=*),         intent (in) :: cgrid  ! grid acronym
386    integer(kind=ip_intwp_p), intent (in) :: nx     ! number of longitudes
387    integer(kind=ip_intwp_p), intent (in) :: ny     ! number of latitudes
388    integer(kind=ip_intwp_p), intent (in) :: nc     ! number of corners per cell
389    real(kind=ip_single_p),   intent (in) :: clon(nx,ny,nc) ! longitudes
390    real(kind=ip_single_p),   intent (in) :: clat(nx,ny,nc) ! latitudes
391    !-------------------------------------------------
392    real(kind=ip_double_p), allocatable :: clon8(:,:,:),clat8(:,:,:)
393    integer(kind=ip_intwp_p) :: ierror
394    character(len=*),parameter :: subname = 'oasis_write_corner_r4'
395    !-------------------------------------------------
396
397    call oasis_debug_enter(subname)
398
399    allocate(clon8(nx,ny,nc),stat=ierror)
400    if (ierror /= 0) write(nulprt,*) subname,' model :',compid,' proc :',&
401                                     mpi_rank_local,' WARNING clon8 alloc'
402    allocate(clat8(nx,ny,nc),stat=ierror)
403    if (ierror /= 0) write(nulprt,*) subname,' model :',compid,' proc :',&
404                                     mpi_rank_local,' WARNING clat8 alloc'
405
406    clon8 = clon
407    clat8 = clat
408    call oasis_write_corner_r8(cgrid,nx,ny,nc,clon8,clat8)
409
410    deallocate(clon8)
411    deallocate(clat8)
412
413    call oasis_debug_exit(subname)
414
415  END SUBROUTINE oasis_write_corner_r4
416
417!--------------------------------------------------------------------------
418    SUBROUTINE oasis_write_mask(cgrid, nx, ny, mask)
419
420    !-------------------------------------------------
421    ! Routine to create a new masks file or to add a land see mask to an
422    ! existing masks file.
423    !-------------------------------------------------
424
425    implicit none
426
427    character(len=*),         intent (in) :: cgrid       ! grid acronym
428    integer(kind=ip_intwp_p), intent (in) :: nx          ! number of longitudes
429    integer(kind=ip_intwp_p), intent (in) :: ny          ! number of latitudes
430    integer(kind=ip_intwp_p), intent (in) :: mask(nx,ny) ! mask
431    !-------------------------------------------------
432    integer(kind=ip_intwp_p) :: GRIDID
433    integer(kind=ip_intwp_p) :: ierror
434    character(len=*),parameter :: subname = 'oasis_write_mask'
435    !-------------------------------------------------
436
437    call oasis_debug_enter(subname)
438
439    if (mpi_rank_local /= mpi_root_local) then
440       write(nulprt,*) subname,' ERROR subroutine call by non root processor'
441       WRITE(nulprt,*) subname,' abort by model :',compid,' proc :',mpi_rank_local
442       CALL oasis_flush(nulprt)
443       call oasis_abort_noarg()
444    endif
445
446    call oasis_findgrid(cgrid,nx,ny,gridID)
447
448    allocate(prism_grid(gridID)%mask(nx,ny),stat=ierror)
449    if (ierror /= 0) write(nulprt,*) subname,' model :',compid,' proc :',&
450                                     mpi_rank_local,' WARNING mask alloc'
451    prism_grid(gridID)%mask = mask
452    prism_grid(gridID)%mask_set = .true.
453
454    call oasis_debug_exit(subname)
455
456  END SUBROUTINE oasis_write_mask
457
458!--------------------------------------------------------------------------
459    SUBROUTINE oasis_write_area_r8(cgrid, nx, ny, area)
460
461    !-------------------------------------------------
462    ! Routine to create a new areas file or to add areas of a grid to an
463    ! existing areas file.
464    !-------------------------------------------------
465
466    implicit none
467
468    character(len=*),         intent (in) :: cgrid       ! grid acronym
469    integer(kind=ip_intwp_p), intent (in) :: nx          ! number of longitudes
470    integer(kind=ip_intwp_p), intent (in) :: ny          ! number of latitudes
471    real(kind=ip_double_p),   intent (in) :: area(nx,ny) ! areas
472    !-------------------------------------------------
473    integer(kind=ip_intwp_p) :: GRIDID
474    integer(kind=ip_intwp_p) :: ierror
475    character(len=*),parameter :: subname = 'oasis_write_area_r8'
476    !-------------------------------------------------
477
478    call oasis_debug_enter(subname)
479
480    if (mpi_rank_local /= mpi_root_local) then
481       write(nulprt,*) subname,' ERROR subroutine call by non root processor'
482       WRITE(nulprt,*) subname,' abort by model :',compid,' proc :',mpi_rank_local
483       CALL oasis_flush(nulprt)
484       call oasis_abort_noarg()
485    endif
486
487    call oasis_findgrid(cgrid,nx,ny,gridID)
488
489    allocate(prism_grid(gridID)%area(nx,ny),stat=ierror)
490    if (ierror /= 0) write(nulprt,*) subname,' model :',compid,' proc :',&
491                                     mpi_rank_local,' WARNING area alloc'
492    prism_grid(gridID)%area = area
493    prism_grid(gridID)%area_set = .true.
494
495    call oasis_debug_exit(subname)
496
497  END SUBROUTINE oasis_write_area_r8
498
499!--------------------------------------------------------------------------
500    SUBROUTINE oasis_write_area_r4(cgrid, nx, ny, area)
501
502    !-------------------------------------------------
503    ! Routine to create a new areas file or to add areas of a grid to an
504    ! existing areas file.
505    !-------------------------------------------------
506
507    implicit none
508
509    character(len=*),         intent (in) :: cgrid       ! grid acronym
510    integer(kind=ip_intwp_p), intent (in) :: nx          ! number of longitudes
511    integer(kind=ip_intwp_p), intent (in) :: ny          ! number of latitudes
512    real(kind=ip_single_p),   intent (in) :: area(nx,ny) ! areas
513    !-------------------------------------------------
514    real(kind=ip_double_p), allocatable :: area8(:,:)
515    integer(kind=ip_intwp_p) :: ierror
516    character(len=*),parameter :: subname = 'oasis_write_area_r4'
517    !-------------------------------------------------
518
519    call oasis_debug_enter(subname)
520
521    allocate(area8(nx,ny),stat=ierror)
522    if (ierror /= 0) write(nulprt,*) subname,' model :',compid,' proc :',&
523                                     mpi_rank_local,' WARNING area8 alloc'
524
525    area8 = area
526    call oasis_write_area_r8(cgrid,nx,ny,area8)
527
528    deallocate(area8)
529
530    call oasis_debug_exit(subname)
531
532  END SUBROUTINE oasis_write_area_r4
533
534!--------------------------------------------------------------------------
535    SUBROUTINE oasis_terminate_grids_writing()
536    !-------------------------------------------------
537    ! Routine to terminate the grids writing.
538    !-------------------------------------------------
539
540    implicit none
541    integer(kind=ip_i4_p) :: n
542    character(len=*),parameter :: subname = 'oasis_terminate_grids_writing'
543
544    call oasis_debug_enter(subname)
545
546    if (mpi_rank_local /= mpi_root_local) then
547       write(nulprt,*) subname,' ERROR subroutine call by non root processor'
548       WRITE(nulprt,*) subname,' abort by model :',compid,' proc :',mpi_rank_local
549       CALL oasis_flush(nulprt)
550       call oasis_abort_noarg()
551    endif
552
553    do n = 1,prism_ngrid
554       prism_grid(n)%terminated = .true.
555    enddo
556
557! moved to prism_method_enddef for synchronization
558!    call oasis_write2files()
559
560    call oasis_debug_exit(subname)
561
562  END SUBROUTINE oasis_terminate_grids_writing
563
564!--------------------------------------------------------------------------
565    SUBROUTINE oasis_write2files()
566
567    !-------------------------------------------------
568    ! Write fields to grid files.
569    ! Only write fields that have been buffered and
570    ! if prism_grid_terminate_grids_writing has been called
571    !-------------------------------------------------
572
573    implicit none
574
575    !-------------------------------------------------
576    character(len=ic_med) :: filename  ! grid filename
577    character(len=ic_med) :: fldname   ! full field name
578    character(len=ic_med) :: cgrid     ! grid name
579    logical :: exists                  ! check if file exists
580    integer(kind=ip_i4_p) :: n         ! counter
581    integer(kind=ip_i4_p) :: nx,ny,nc  ! grid size
582    character(len=*),parameter :: subname = 'oasis_write2files'
583    !-------------------------------------------------
584
585    call oasis_debug_enter(subname)
586
587    do n = 1,prism_ngrid
588    if (prism_grid(n)%terminated) then
589       cgrid = trim(prism_grid(n)%gridname)
590       prism_grid(n)%written = .true.
591
592       nx = prism_grid(n)%nx
593       ny = prism_grid(n)%ny
594       nc = prism_grid(n)%nc
595
596       if (prism_grid(n)%grid_set) then
597          filename = 'grids.nc'
598          fldname  = trim(cgrid)//'.lon'
599          call oasis_io_write_2dgridfld_fromroot(filename,fldname,prism_grid(n)%lon,nx,ny)
600          fldname  = trim(cgrid)//'.lat'
601          call oasis_io_write_2dgridfld_fromroot(filename,fldname,prism_grid(n)%lat,nx,ny)
602       endif
603
604       if (prism_grid(n)%corner_set) then
605          filename = 'grids.nc'
606          fldname  = trim(cgrid)//'.clo'
607          call oasis_io_write_3dgridfld_fromroot(filename,fldname,prism_grid(n)%clon,nx,ny,nc)
608          fldname  = trim(cgrid)//'.cla'
609          call oasis_io_write_3dgridfld_fromroot(filename,fldname,prism_grid(n)%clat,nx,ny,nc)
610       endif
611
612       if (prism_grid(n)%area_set) then
613          filename = 'areas.nc'
614          fldname  = trim(cgrid)//'.srf'
615          call oasis_io_write_2dgridfld_fromroot(filename,fldname,prism_grid(n)%area,nx,ny)
616       endif
617
618       if (prism_grid(n)%angle_set) then
619          filename = 'grids.nc'
620          fldname  = trim(cgrid)//'.ang'
621          call oasis_io_write_2dgridfld_fromroot(filename,fldname,prism_grid(n)%angle,nx,ny)
622       endif
623
624       if (prism_grid(n)%mask_set) then
625          filename = 'masks.nc'
626          fldname  = trim(cgrid)//'.msk'
627          call oasis_io_write_2dgridint_fromroot(filename,fldname,prism_grid(n)%mask,nx,ny)
628       endif
629
630    endif  ! terminated
631    enddo
632
633    call oasis_debug_exit(subname)
634
635  END SUBROUTINE oasis_write2files
636!--------------------------------------------------------------------------
637
638    SUBROUTINE oasis_findgrid(cgrid,nx,ny,gridID)
639    !-------------------------------------------------
640    ! Routine that sets gridID, identifies existing
641    ! grid with cgrid name or starts a new one
642    !-------------------------------------------------
643    implicit none
644
645    character(len=*),         intent (in) :: cgrid       ! grid acronym
646    integer(kind=ip_intwp_p), intent (in) :: nx          ! number of longitudes
647    integer(kind=ip_intwp_p), intent (in) :: ny          ! number of latitudes
648    integer(kind=ip_intwp_p), intent(out) :: gridID      ! gridID matching cgrid
649    !-------------------------------------------------
650    integer(kind=ip_intwp_p) :: n
651    character(len=*),parameter :: subname = 'oasis_findgrid'
652    !-------------------------------------------------
653
654    call oasis_debug_enter(subname)
655
656    gridID = -1
657    do n = 1,prism_ngrid
658       if (trim(cgrid) == trim(prism_grid(n)%gridname)) then
659          gridID = n
660          ! since grid is defined before, make sure nx,ny match
661          if (nx /= prism_grid(gridID)%nx .or. ny /= prism_grid(gridID)%ny) then
662             write(nulprt,*) subname,' ERROR in predefined grid size',nx,ny, &
663                prism_grid(gridID)%nx,prism_grid(gridID)%ny
664             WRITE(nulprt,*) subname,' abort by model :',compid,' proc :',mpi_rank_local
665             CALL oasis_flush(nulprt)
666             call oasis_abort_noarg()
667          endif
668       endif
669    enddo
670
671    if (gridID < 1) then
672       prism_ngrid = prism_ngrid+1
673       gridID = prism_ngrid
674    endif
675
676    prism_grid(gridID)%gridname = trim(cgrid)
677    prism_grid(gridID)%nx = nx
678    prism_grid(gridID)%ny = ny
679
680    call oasis_debug_exit(subname)
681
682  END SUBROUTINE oasis_findgrid
683!--------------------------------------------------------------------------
684END MODULE mod_oasis_grid
685!--------------------------------------------------------------------------
686
687
688     
Note: See TracBrowser for help on using the repository browser.