source: CPL/oasis3-mct/branches/OASIS3-MCT_2.0_branch/examples/tutorial/model2.F90 @ 4775

Last change on this file since 4775 was 4775, checked in by aclsce, 4 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: 11.4 KB
Line 
1!------------------------------------------------------------------------
2! Copyright 2010, CERFACS, Toulouse, France.
3! All rights reserved. Use is subject to OASIS3 license terms.
4!=============================================================================
5!
6PROGRAM model2
7  !
8  ! Use for netCDF library
9  USE netcdf
10  ! Use for OASIS communication library
11  USE mod_oasis
12  !
13  IMPLICIT NONE
14
15  INCLUDE 'mpif.h'
16
17  !
18  ! By default OASIS3 exchanges data in double precision.
19  ! To exchange data in single precision with OASIS3,
20  ! the coupler has to be compiled with CPP key "use_realtype_single"
21  ! and the model with CPP key "NO_USE_DOUBLE_PRECISION"
22#ifdef NO_USE_DOUBLE_PRECISION
23  INTEGER, PARAMETER :: wp = SELECTED_REAL_KIND(6,37)   ! real
24#elif USE_DOUBLE_PRECISION
25  INTEGER, PARAMETER :: wp = SELECTED_REAL_KIND(12,307) ! double
26#endif
27  !
28  CHARACTER(len=30), PARAMETER :: data_filename='grid_model2.nc'
29  ! Component name (6 characters) same as in the namcouple
30  CHARACTER(len=6)   :: comp_name = 'model2'
31  CHARACTER(len=128) :: comp_out ! name of the output log file
32  CHARACTER(len=3)   :: chout
33  !
34  ! Global grid parameters :
35  INTEGER :: nlon, nlat     ! dimensions in the 2 directions of space
36  INTEGER :: ntot           ! total dimension
37  INTEGER :: il_paral_size
38  INTEGER :: nc ! number of corners in the (i,j) plan
39  INTEGER :: indi_beg, indi_end, indj_beg, indj_end
40  !
41  DOUBLE PRECISION, DIMENSION(:,:), POINTER   :: globalgrid_lon,globalgrid_lat
42  DOUBLE PRECISION, DIMENSION(:,:,:), POINTER :: globalgrid_clo,globalgrid_cla
43  DOUBLE PRECISION, DIMENSION(:,:), POINTER   :: globalgrid_srf
44  INTEGER, DIMENSION(:,:), POINTER            :: indice_mask ! mask, 0 == valid point, 1 == masked point
45  !
46  INTEGER :: mype, npes ! rank and number of pe
47  INTEGER :: localComm  ! local MPI communicator and Initialized
48  INTEGER :: comp_id    ! component identification
49  !
50  INTEGER, DIMENSION(:), ALLOCATABLE :: il_paral ! Decomposition for each proc
51  !
52  INTEGER :: ierror, rank, w_unit
53  INTEGER :: i, j
54  !
55  ! Names of exchanged Fields
56  CHARACTER(len=8), PARAMETER :: var_name1 = 'FRECVATM' ! 8 characters field received by the atmosphere from the ocean
57  CHARACTER(len=8), PARAMETER :: var_name2 = 'FSENDATM' ! 8 characters field sent by the atmosphere to the ocean
58  !
59  ! Used in oasis_def_var and oasis_def_var
60  INTEGER                   :: var_id(2) 
61  INTEGER                   :: var_nodims(2) 
62  INTEGER                   :: var_type
63  !
64  REAL (kind=wp), PARAMETER :: field_ini = -1. ! initialisation of received fields
65  !
66  INTEGER               ::  ib
67  INTEGER, PARAMETER    ::  il_nb_time_steps = 12 ! number of time steps
68  INTEGER, PARAMETER    ::  delta_t = 1800       ! time step
69  !
70  INTEGER                :: il_flag          ! Flag for grid writing
71  !
72  INTEGER                :: itap_sec ! Time
73  !
74  ! Grid parameter definition
75  INTEGER                :: part_id  ! use to connect the partition to the variables
76                                     ! in oasis_def_var
77  INTEGER                :: var_actual_shape(4) ! local dimensions of the arrays to the pe
78                                                ! 2 x field rank (= 4 because fields are of rank = 2)
79  !
80  ! Exchanged local fields arrays
81  ! used in routines oasis_put and oasis_get
82  REAL (kind=wp), POINTER :: field1_recv(:,:)
83  REAL (kind=wp), POINTER :: field2_send(:,:)
84  !
85  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
86  !   INITIALISATION
87  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
88  !
89  CALL MPI_Init(ierror)
90  !!!!!!!!!!!!!!!!! OASIS_INIT !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
91  !
92  ! TOCOMPLETE - Put here OASIS initialisation call !
93  !
94  !
95  ! Unit for output messages : one file for each process
96  CALL MPI_Comm_Rank ( MPI_COMM_WORLD, rank, ierror )
97  IF (ierror /= 0) THEN
98      WRITE(0,*) 'MPI_Comm_Rank abort by model2 compid ',comp_id
99      CALL oasis_abort(comp_id,comp_name,'Problem at line 102')
100  ENDIF
101  !
102  w_unit=100+rank
103  WRITE(chout,'(I3)') w_unit
104  comp_out=comp_name//'.out_'//chout
105  !
106  OPEN(w_unit,file=TRIM(comp_out),form='formatted')
107  WRITE (w_unit,*) '-----------------------------------------------------------'
108  WRITE (w_unit,*) TRIM(comp_name), ' Running with reals compiled as kind =',wp
109  WRITE (w_unit,*) 'I am component ', TRIM(comp_name), ' rank :',rank
110  WRITE (w_unit,*) '----------------------------------------------------------'
111  CALL flush(w_unit)
112  !
113  !!!!!!!!!!!!!!!!! OASIS_GET_LOCALCOMM !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
114  !
115  localComm = MPI_COMM_WORLD
116  ! TOCOMPLETE - Put here OASIS call to get local MPI communicator !
117  !
118  ! Get MPI size and rank
119  CALL MPI_Comm_Size ( localComm, npes, ierror )
120  IF (ierror /= 0) THEN
121      WRITE(w_unit,*) 'MPI_comm_size abort by model2 compid ',comp_id
122      CALL oasis_abort(comp_id,comp_name,'Problem at line 127')
123  ENDIF
124  !
125  CALL MPI_Comm_Rank ( localComm, mype, ierror )
126  IF (ierror /= 0) THEN
127      WRITE (w_unit,*) 'MPI_Comm_Rank abort by model2 compid ',comp_id
128      CALL oasis_abort(comp_id,comp_name,'Problem at line 133')
129  ENDIF
130  !
131  WRITE(w_unit,*) 'I am the ', TRIM(comp_name), ' local rank ', mype
132  WRITE (w_unit,*) 'Number of processors :',npes
133  CALL flush(w_unit)
134  !
135  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
136  !  GRID DEFINITION
137  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
138  !
139  ! Reading netcdf file with pre-defined variable names
140  !
141  ! Reading dimensions of the grid
142  CALL read_dimgrid(nlon,nlat,data_filename,w_unit)
143  nc=4
144  !
145  ! Allocation
146  ALLOCATE(globalgrid_lon(nlon,nlat), STAT=ierror )
147  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating globalgrid_lon'
148  ALLOCATE(globalgrid_lat(nlon,nlat), STAT=ierror )
149  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating globalgrid_lat'
150  ALLOCATE(globalgrid_clo(nlon,nlat,nc), STAT=ierror )
151  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating globalgrid_clo'
152  ALLOCATE(globalgrid_cla(nlon,nlat,nc), STAT=ierror )
153  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating globalgrid_cla'
154  ALLOCATE(globalgrid_srf(nlon,nlat), STAT=ierror )
155  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating globalgrid_srf'
156  ALLOCATE(indice_mask(nlon,nlat), STAT=ierror )
157  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating indice_mask'
158  !
159  ! Reading of the longitudes, latitudes, longitude and latitudes of the corners, mask of the grid
160  CALL read_grid(nlon,nlat,nc,data_filename,w_unit, &
161                 globalgrid_lon,globalgrid_lat, &
162                 globalgrid_clo,globalgrid_cla, &
163                 globalgrid_srf, &
164                 indice_mask)
165  !
166  ! (Global) grid definition for OASIS
167  ! Writing of the file grids.nc and masks.nc by the processor 0 from the grid read in
168  !
169  IF (mype == 0) THEN
170      !
171      ! Mask inversion to follow (historical) OASIS convention (0=not masked;1=masked)
172      WHERE(indice_mask == 1) 
173          indice_mask=0
174      ELSEWHERE
175          indice_mask=1
176      END WHERE
177      !
178      ! TOCOMPLETE - Put here OASIS grid, corner, areas and mask writing calls !
179      !
180  ENDIF
181  !
182  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
183  !  PARTITION DEFINITION
184  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ !
185  !
186  ! Definition of the partition of the grid (calling oasis_def_partition)
187  ntot=nlon*nlat
188#ifdef DECOMP_APPLE
189  il_paral_size = 3
190#elif defined DECOMP_BOX
191  il_paral_size = 5
192#endif
193  ALLOCATE(il_paral(il_paral_size))
194  WRITE(w_unit,*) 'After allocate il_paral, il_paral_size', il_paral_size
195  call flush(w_unit)
196  !
197  CALL decomp_def (il_paral,il_paral_size,nlon,nlat,mype,npes,w_unit)
198  WRITE(w_unit,*) 'After decomp_def, il_paral = ', il_paral(:)
199  call flush(w_unit)
200  !
201  ! TOCOMPLETE - Put here OASIS call to define local partition !
202  ! The data are exchanged in the global grid so you do not need to pass
203  ! isize to oasis_def_partition
204  !
205  !
206  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
207  ! DEFINITION OF THE LOCAL FIELDS 
208  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
209  !
210  !!!!!!!!!!!!!!!!!! OASIS_DEF_VAR !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
211  !
212  ! Define transient variables
213  !
214  var_nodims(1) = 2    ! Rank of the field array is 2
215  var_nodims(2) = 1    ! Bundles always 1 for OASIS3
216  var_type = OASIS_Real
217  !
218  var_actual_shape(1) = 1
219  var_actual_shape(2) = il_paral(3)
220  var_actual_shape(3) = 1 
221#ifdef DECOMP_APPLE
222  var_actual_shape(4) = 1
223#elif defined DECOMP_BOX
224  var_actual_shape(4) = il_paral(4)
225#endif
226  ! Declaration of the field associated with the partition of the grid
227  !
228  ! TOCOMPLETE - Put here OASIS call to declare the 2 coupling field
229  !              FRECVATM, FSENDATM !
230  ! var_name1 = 'FRECVATM'
231  ! var_name2 = 'FSENDATM'
232  !
233  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
234  !         TERMINATION OF DEFINITION PHASE
235  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
236  !  All processes involved in the coupling must call oasis_enddef;
237  !  here all processes are involved in coupling
238  !
239  !!!!!!!!!!!!!!!!!! OASIS_ENDDEF !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
240  !
241  ! TOCOMPLETE - Put here the OASIS call to end the definition phase
242  !
243  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
244  ! SEND AND RECEIVE ARRAYS
245  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
246  !
247  ! Allocate the fields send and received by the model
248  !
249  ALLOCATE(field1_recv(var_actual_shape(2), var_actual_shape(4)), STAT=ierror )
250  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating field1_recv'
251  !
252  ALLOCATE(field2_send(var_actual_shape(2), var_actual_shape(4)),STAT=ierror )
253  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating field2_send'
254  !
255  DEALLOCATE(il_paral)
256  !
257  !!!!!!!!!!!!!!!!!!!!!!!!!!!!OASIS_PUT/OASIS_GET !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
258  !
259  indi_beg=1 ; indi_end=nlon
260  indj_beg=((nlat/npes)*mype)+1 
261  !
262  IF (mype .LT. npes - 1) THEN
263      indj_end = (nlat/npes)*(mype+1)
264  ELSE
265      indj_end = nlat 
266  ENDIF
267  !
268  ! Data exchange
269  !
270  ! Time loop
271  DO ib=1, il_nb_time_steps
272    itap_sec = delta_t * (ib-1) ! Time
273    !
274    !
275    ! Get the field FRECVATM
276    field1_recv=field_ini
277    ! TOCOMPLETE - Put here the OASIS call to receive FRECVATM (field1_recv)
278    ! Let's suppose here that FRECVATM contains BC needed for the timestep
279    !
280    ! Here the model computes its timestep
281    !
282    CALL function_sent(var_actual_shape(2), var_actual_shape(4), &
283                       RESHAPE(globalgrid_lon(indi_beg:indi_end,indj_beg:indj_end),&
284                               (/ var_actual_shape(2), var_actual_shape(4) /)), &
285                       RESHAPE(globalgrid_lat(indi_beg:indi_end,indj_beg:indj_end),&
286                               (/ var_actual_shape(2), var_actual_shape(4) /)), &
287                                field2_send,ib)
288    !
289    ! Send the field FSENDATM
290    ! TOCOMPLETE - Put here the OASIS call to send FSENDATM (field2_send)
291    !
292    !
293  ENDDO
294  !
295  WRITE (w_unit,*) 'End of the program'
296  CALL flush(w_unit)
297  CLOSE(w_unit)
298  !
299  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
300  !         TERMINATION
301  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
302  !
303  !!!!!!!!!!!!!!!!!! OASIS_TERMINATE !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
304  !
305  ! Collective call to terminate the coupling exchanges
306  !
307  ! TOCOMPLETE - Put here the OASIS call to terminate the coupling
308  !
309  !
310  call mpi_finalize(ierror)
311END PROGRAM MODEL2
312!
Note: See TracBrowser for help on using the repository browser.