source: TOOLS/MOSAIX/src/MOSAIX/interpol.f90 @ 3623

Last change on this file since 3623 was 3623, checked in by omamce, 6 years ago

O.M.: add SVN properties

  • Property svn:keywords set to Date Revision HeadURL Author Id
File size: 7.7 KB
Line 
1! -*- Mode: f90 -*-
2PROGRAM interpol
3!!!
4!!! Generates interpolation weights from source (src) grid to destination (dst) grid
5!!! Most of the configuration is done by the xml file
6!!!
7   USE xios
8   USE mod_wait
9   USE mpi
10   IMPLICIT NONE
11   ! INCLUDE "mpif.h"
12   INTEGER, PARAMETER :: rl = SELECTED_REAL_KIND(15,307) !< Default real precision (double)
13   INTEGER :: ierr, comm, rank
14
15   TYPE (xios_context) :: ctx_hdl
16   INTEGER :: ni_src, nj_src !< Dimensions of the source grid
17   INTEGER :: ni_dst, nj_dst !< Dimensions of the source grid
18   REAL (kind=rl), ALLOCATABLE :: imask_src (:,:), imask_dst (:,:)
19   REAL (kind=rl), ALLOCATABLE :: lon_src(:,:), lat_src(:,:), field_src(:,:)
20   LOGICAL, ALLOCATABLE :: lmask_src (:,:), lmask_dst (:,:)
21   INTEGER :: nout = 0, jf
22   CHARACTER (LEN=20) :: nchar, type_src, type_dst
23   LOGICAL :: l_mask_src = .TRUE. , l_mask_dst = .TRUE.
24   !
25   REAL (kind=rl), PARAMETER :: rpi = ACOS ( -1.0_rl)
26   REAL (kind=rl), PARAMETER :: rad = rpi / 180.0_rl
27   !
28   INTEGER :: narg, ja !< To handle command line arguments
29   CHARACTER (LEN=80) :: cmd_arg
30   !
31   !! SVN information
32   CHARACTER (LEN=80) :: SVN_Author   = "$Author$"
33   CHARACTER (LEN=80) :: SVN_Date     = "$Date$"
34   CHARACTER (LEN=80) :: SVN_Revision = "$Revision$"
35   CHARACTER (LEN=80) :: SVN_Id       = "$Id$"
36   CHARACTER (LEN=80) :: SVN_Log      = "$Log: $"
37
38   !!
39   !< Initialisation
40   WRITE (UNIT=nout, FMT="('-- start interpol')" ) 
41   CALL MPI_INIT (ierr)
42
43   CALL init_wait
44   CALL xios_initialize ("interpol", return_comm=comm)
45
46   CALL MPI_COMM_RANK (comm, rank, ierr)
47   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- mpi_comm_rank')" ) rank
48   !CALL MPI_COMM_SIZE (comm, size, ierr)
49
50   !< Read command line
51   narg = iargc ()
52   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- narg : ', 1I3)" ) rank, narg
53
54   !< Read arguments on command line
55   DO ja = 1, narg
56      CALL getarg ( ja, cmd_arg )
57      SELECT CASE ( TRIM (cmd_arg) )
58      CASE ( '--mask_src=yes' ) ; l_mask_src = .TRUE.
59      CASE ( '--mask_src=no'  ) ; l_mask_src = .FALSE.
60      CASE ( '--mask_dst=yes' ) ; l_mask_dst = .TRUE.
61      CASE ( '--mask_dst=no'  ) ; l_mask_dst = .FALSE.
62      END SELECT
63   END DO
64
65   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- mask_src : ', 1L)" ) rank, l_mask_src
66   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- mask_dst : ', 1L)" ) rank, l_mask_dst
67
68   !< Context interpol_read : read masks
69   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- debut interpol_read')" ) rank
70   CALL xios_context_initialize  ("interpol_read", comm)
71   CALL xios_get_handle          ("interpol_read", ctx_hdl)
72   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- set current context interpol_read')" ) rank
73   CALL xios_set_current_context (ctx_hdl)
74   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- close context definition interpol_read')" ) rank
75   CALL xios_close_context_definition ()
76
77   !< Read characteristics of the source grid
78   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- lecture domain_src')" ) rank
79   CALL xios_get_domain_attr ("domain_src", ni=ni_src, nj=nj_src)
80   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- lecture domain_src ', 6I9)") rank, ni_src, nj_src
81   ALLOCATE ( lon_src (ni_src, nj_src), lat_src (ni_src, nj_src) )
82   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- lecture lon lat src ', 6I9)") rank, SIZE (lon_src), SHAPE (lon_src), SIZE (lat_src), SHAPE (lat_src)
83   !!
84   !
85   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- lecture type src ', 6I9)") rank
86   CALL xios_get_domain_attr ("domain_src", TYPE=type_src )
87   SELECT CASE ( TRIM (type_src))
88   CASE ( "rectilinear" )
89      WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- lecture lon lat src rectilinear', 6I9)") rank
90      CALL xios_get_domain_attr ("domain_src", lonvalue_1d=lon_src(:,1), latvalue_1d=lat_src(1,:) )
91      lon_src (:,:) = SPREAD ( lon_src(:,1), DIM=2, ncopies=nj_src)
92      lat_src (:,:) = SPREAD ( lat_src(1,:), DIM=1, ncopies=nj_src)
93   CASE default
94      IF ( nj_src == 1 ) THEN
95         WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- lecture lon lat src 1D ', 6I9)") rank
96         CALL xios_get_domain_attr ("domain_src", lonvalue_1d=lon_src(:,1), latvalue_1d=lat_src(:,1) )
97      ELSE
98         WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- lecture lon lat src 2D ', 6I9)") rank
99         CALL xios_get_domain_attr ("domain_src", lonvalue_2d=lon_src(:,:), latvalue_2d=lat_src(:,:) )
100      ENDIF
101   END SELECT
102   !< Read mask on the source grid
103   ALLOCATE ( imask_src (ni_src, nj_src), lmask_src (ni_src, nj_src) )
104   IF ( l_mask_src ) THEN
105      WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- receive field mask_src')" ) rank
106      CALL xios_recv_field ("mask_src", imask_src)
107      lmask_src = .FALSE.
108      WHERE (imask_src>0) lmask_src = .TRUE.
109   ELSE
110      imask_src (:,:) = 1 ; lmask_src (:,:) = .TRUE.
111   ENDIF
112   
113   !< Read mask on the destination grid
114   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- lecture domain_dst')" ) rank
115   CALL xios_get_domain_attr ("domain_dst", ni=ni_dst, nj=nj_dst)
116   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- lecture domain_dst ', 6I7)") rank, ni_dst, nj_dst
117   ALLOCATE ( imask_dst (ni_dst, nj_dst), lmask_dst (ni_dst, nj_dst) )
118   IF ( l_mask_dst ) THEN
119      WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- receive field mask_dst')" ) rank 
120      CALL xios_recv_field ("mask_dst", imask_dst)
121      lmask_dst = .FALSE.
122      WHERE (imask_dst>0) lmask_dst = .TRUE.
123   ELSE
124      imask_dst (:,:) = 1 ; lmask_dst (:,:) = .TRUE.
125   ENDIF
126
127   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- fin interpol_read (1)')") rank
128   CALL xios_context_finalize ()
129   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- fin interpol_read (2)')") rank
130   
131   !< Context interpol run : generates weights, interpolate mask from source to destination
132   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- debut interpol_run')" ) rank
133   CALL xios_context_initialize  ("interpol_run", comm)
134   CALL xios_get_handle          ("interpol_run", ctx_hdl)
135   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- set context interpol_run')" ) rank
136   CALL xios_set_current_context (ctx_hdl)
137
138   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- get attributes domain_src')" ) rank
139   IF ( l_mask_src ) CALL xios_set_domain_attr ("domain_src", mask_2d=lmask_src)
140   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- get attributes domain_src')" ) rank
141   IF ( l_mask_dst ) CALL xios_set_domain_attr ("domain_dst", mask_2d=lmask_dst)
142
143   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- close context definition')" ) rank
144   CALL xios_close_context_definition ()
145
146   CALL xios_update_calendar (1)
147   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- send field mask_src')" ) rank
148   CALL xios_send_field ("mask_src", imask_src)
149
150   !!< Creates analytic fields and interpolate
151   ALLOCATE ( field_src (ni_src, nj_src) )
152
153   DO jf = 1, 6
154      WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- working on test case ', 1I2.2)" ) rank, jf
155      SELECT CASE ( jf)
156      CASE ( 1) ; field_src (:,:) = REAL ( imask_src, kind=rl)
157      CASE ( 2) ; field_src (:,:) = SIN ( rad * lat_src(:,:) )
158      CASE ( 3) ; field_src (:,:) = COS ( rad * lat_src(:,:) )
159      CASE ( 4) ; field_src (:,:) = COS ( rad * lat_src(:,:) ) * COS ( rad * lon_src(:,:) )
160      CASE ( 5) ; field_src (:,:) = SIN ( rad * lon_src(:,:) )
161      CASE ( 6) ; field_src (:,:) = SIN ( rad * lon_src(:,:) + rpi/2.0_rl )
162      END SELECT
163      WRITE (UNIT=nchar, FMT='("field", 1I2.2, "_src")' ) jf
164      CALL xios_send_field ( TRIM(nchar), field_src )
165   END DO
166   
167   !!<
168   
169   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- fin interpol_run')" ) rank
170   CALL xios_context_finalize ()
171
172   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- mpi_comm_free')" ) rank
173   CALL MPI_COMM_FREE (comm, ierr)
174
175   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- xios finalize')" ) rank
176   CALL xios_finalize ()
177
178   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- mpi finalize')" ) rank
179   CALL MPI_FINALIZE (ierr)
180
181   WRITE (UNIT=nout, FMT="('-- ', 1I4.4, ' -- fini')" ) rank
182
183END PROGRAM interpol
184
185
186
187
188
Note: See TracBrowser for help on using the repository browser.