source: CPL/oasis3-mct/branches/OASIS3-MCT_2.0_branch/examples/tutorial/model1.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: 11.4 KB
Line 
1!------------------------------------------------------------------------
2! Copyright 2010, CERFACS, Toulouse, France.
3! All rights reserved. Use is subject to OASIS3 license terms.
4!=============================================================================
5!
6!
7PROGRAM model1
8  !
9  ! Use for netCDF library
10  USE netcdf
11  ! Use for OASIS communication library
12  USE mod_oasis
13  !
14  IMPLICIT NONE
15
16  INCLUDE 'mpif.h'
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_model1.nc'
29  ! Component name (6 characters) same as in the namcouple
30  CHARACTER(len=6)   :: comp_name = 'model1'
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
39  INTEGER :: indi_beg, indi_end, indj_beg, indj_end
40  !
41  DOUBLE PRECISION, DIMENSION(:,:), POINTER   :: globalgrid_lon,globalgrid_lat ! lon, lat of the points
42  DOUBLE PRECISION, DIMENSION(:,:,:), POINTER :: globalgrid_clo,globalgrid_cla ! lon, lat of the corners
43  DOUBLE PRECISION, DIMENSION(:,:), POINTER   :: globalgrid_srf ! surface of the grid meshes
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 = 'FSENDOCN' ! 8 characters field sent by model1 to model2
57  CHARACTER(len=8), PARAMETER :: var_name2 = 'FRECVOCN' ! 8 characters field received by model1 from model2
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 = 6 ! number of time steps
68  INTEGER, PARAMETER    ::  delta_t = 3600       ! time step
69  !
70  !
71  INTEGER                 :: il_flag  ! Flag for grid writing by proc 0
72  !
73  INTEGER                 :: itap_sec ! Time used in oasis_put/get
74  !
75  ! Grid parameters definition
76  INTEGER                 :: part_id  ! use to connect the partition to the variables
77                                      ! in oasis_def_var
78  INTEGER                 :: var_actual_shape(4) ! local dimensions of the arrays to the pe
79                                                 ! 2 x field rank (= 4 because fields are of rank = 2)
80  !
81  ! Exchanged local fields arrays
82  ! used in routines oasis_put and oasis_get
83  REAL (kind=wp), POINTER :: field1_send(:,:)
84  REAL (kind=wp), POINTER :: field2_recv(:,:)
85  !
86  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
87  !   INITIALISATION
88  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
89  !
90  CALL MPI_Init(ierror)
91  !!!!!!!!!!!!!!!!! OASIS_INIT !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
92  !
93  ! TOCOMPLETE - Put here OASIS initialisation call !
94  !
95  !
96  ! Unit for output messages : one file for each process
97  CALL MPI_Comm_Rank ( MPI_COMM_WORLD, rank, ierror )
98  IF (ierror /= 0) THEN
99      WRITE(0,*) 'MPI_Comm_Rank abort by model1 compid ',comp_id
100      CALL oasis_abort(comp_id,comp_name,'Problem at line 103')
101  ENDIF
102  !
103  w_unit = 100 + rank
104  WRITE(chout,'(I3)') w_unit
105  comp_out=comp_name//'.out_'//chout
106  !
107  OPEN(w_unit,file=TRIM(comp_out),form='formatted')
108  WRITE (w_unit,*) '-----------------------------------------------------------'
109  WRITE (w_unit,*) TRIM(comp_name), ' Running with reals compiled as kind =',wp
110  WRITE (w_unit,*) 'I am component ', TRIM(comp_name), ' rank :',rank
111  WRITE (w_unit,*) '----------------------------------------------------------'
112  CALL flush(w_unit)
113  !
114  !!!!!!!!!!!!!!!!! OASIS_GET_LOCALCOMM !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
115  !
116  localComm = MPI_COMM_WORLD
117  ! TOCOMPLETE - Put here OASIS call to get local MPI communicator !
118  !
119  ! Get MPI size and rank
120  CALL MPI_Comm_Size ( localComm, npes, ierror )
121  IF (ierror /= 0) THEN
122      WRITE(w_unit,*) 'MPI_comm_size abort by model1 compid ',comp_id
123      CALL oasis_abort(comp_id,comp_name,'Problem at line 126')
124  ENDIF
125  !
126  CALL MPI_Comm_Rank ( localComm, mype, ierror )
127  IF (ierror /= 0) THEN
128      WRITE (w_unit,*) 'MPI_Comm_Rank abort by model1 compid ',comp_id
129      CALL oasis_abort(comp_id,comp_name,'Problem at line 132')
130  ENDIF
131  !
132  WRITE(w_unit,*) 'I am the ', TRIM(comp_name), 'local rank', mype
133  WRITE (w_unit,*) 'Number of processors :',npes
134  CALL flush(w_unit)
135  !
136  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
137  !  GRID DEFINITION
138  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
139  !
140  ! Reading global grid netcdf file
141  !
142  ! Reading dimensions of the global grid
143  CALL read_dimgrid(nlon,nlat,data_filename,w_unit)
144  nc=4
145  !
146  ! Allocation
147  ALLOCATE(globalgrid_lon(nlon,nlat), STAT=ierror )
148  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating globalgrid_lon'
149  ALLOCATE(globalgrid_lat(nlon,nlat), STAT=ierror )
150  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating globalgrid_lat'
151  ALLOCATE(globalgrid_clo(nlon,nlat,nc), STAT=ierror )
152  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating globalgrid_clo'
153  ALLOCATE(globalgrid_cla(nlon,nlat,nc), STAT=ierror )
154  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating globalgrid_cla'
155  ALLOCATE(globalgrid_srf(nlon,nlat), STAT=ierror )
156  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating globalgrid_srf'
157  ALLOCATE(indice_mask(nlon,nlat), STAT=ierror )
158  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating indice_mask'
159  !
160  ! Reading of the longitudes, latitudes, longitude and latitudes of the corners, mask of the global grid
161  CALL read_grid(nlon,nlat,nc, data_filename, w_unit, &
162                 globalgrid_lon,globalgrid_lat, &
163                 globalgrid_clo,globalgrid_cla, &
164                 globalgrid_srf, &
165                 indice_mask)
166  !
167  ! (Global) grid definition for OASIS
168  ! Writing of the file grids.nc and masks.nc by the processor 0 from the grid read in
169  !
170  IF (mype == 0) THEN
171      !
172      ! Mask inversion to follow (historical) OASIS convention (0=not masked;1=masked)
173      WHERE(indice_mask == 1) 
174          indice_mask=0
175      ELSEWHERE
176          indice_mask=1
177      END WHERE
178      !
179      ! TOCOMPLETE - Put here OASIS grid, corner, areas and mask writing calls !
180      !
181  ENDIF
182  !
183  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
184  !  PARTITION DEFINITION
185  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ !
186  !
187  ! Definition of the partition of the grid (calling oasis_def_partition)
188  ntot=nlon*nlat
189#ifdef DECOMP_APPLE
190  il_paral_size = 3
191#elif defined DECOMP_BOX
192  il_paral_size = 5
193#endif
194  ALLOCATE(il_paral(il_paral_size))
195  WRITE(w_unit,*) 'After allocate il_paral, il_paral_size', il_paral_size
196  call flush(w_unit)
197  !
198  CALL decomp_def (il_paral,il_paral_size,nlon,nlat,mype,npes,w_unit)
199  WRITE(w_unit,*) 'After decomp_def, il_paral = ', il_paral(:)
200  call flush(w_unit)
201  !
202  ! TOCOMPLETE - Put here OASIS call to define local partition !
203  ! The data are exchanged in the global grid so you do not need to pass
204  ! isize to oasis_def_partition
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  !
227  ! Declaration of the field associated with the partition
228  !
229  ! TOCOMPLETE - Put here OASIS call to declare the coupling fields
230  !              FRECVOCN, FSENDOCN
231  ! var_name1 = 'FSENDOCN'
232  ! var_name2 = 'FRECVOCN'
233  !
234  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
235  !         TERMINATION OF DEFINITION PHASE
236  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
237  !  All processes involved in the coupling must call oasis_enddef;
238  !  here all processes are involved in coupling
239  !
240  !!!!!!!!!!!!!!!!!! OASIS_ENDDEF !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
241  !
242  ! TOCOMPLETE - Put here the OASIS call to end the definition phase
243  !
244  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
245  ! SEND AND RECEIVE ARRAYS
246  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
247  !
248  ! Allocate the fields send and received by the model
249  !
250  !
251  ALLOCATE(field1_send(var_actual_shape(2), var_actual_shape(4)), STAT=ierror )
252  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating field1_send'
253  !
254  ALLOCATE(field2_recv(var_actual_shape(2), var_actual_shape(4)), STAT=ierror )
255  IF ( ierror /= 0 ) WRITE(w_unit,*) 'Error allocating field2_recv'
256  !
257  DEALLOCATE(il_paral)
258  !
259  !!!!!!!!!!!!!!!!!!!!!!!!OASIS_PUT/OASIS_GET !!!!!!!!!!!!!!!!!!!!!!
260  !
261  indi_beg=1 ; indi_end=nlon
262  indj_beg=((nlat/npes)*mype)+1 
263  !
264  IF (mype .LT. npes - 1) THEN
265      indj_end = (nlat/npes)*(mype+1)
266  ELSE
267      indj_end = nlat 
268  ENDIF
269  !
270  ! Data exchange
271  !
272  ! Time loop
273  DO ib=1, il_nb_time_steps
274    itap_sec = delta_t * (ib-1) ! Time
275    !
276    ! Get FRECVOCN
277    ! TOCOMPLETE - Put here the OASIS call to receive FRECVOCN (field2_recv)
278    ! Let's suppose here that FRECVOCN 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                                field1_send,ib)
288    !
289    ! Send FSENDOCN
290    ! TOCOMPLETE - Put here the OASIS call to send FSENDOCN (field1_send)
291    ! to the atmosphere and to the file
292    !
293    !
294  ENDDO
295  !
296  WRITE (w_unit,*) 'End of the program'
297  CALL flush(w_unit)
298  CLOSE (w_unit)
299  !
300  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
301  !         TERMINATION
302  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
303  !
304  !!!!!!!!!!!!!!!!!! OASIS_TERMINATE !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
305  !
306  ! Collective call to terminate the coupling exchanges
307  !
308  ! TOCOMPLETE - Put here the OASIS call to terminate the coupling
309  !
310  CALL mpi_finalize(ierror)
311END PROGRAM MODEL1
312!
Note: See TracBrowser for help on using the repository browser.