source: CPL/oasis3-mct/branches/OASIS3-MCT_5.0_branch/examples/spoc/spoc_communication/ocean.F90_oa @ 6331

Last change on this file since 6331 was 6331, checked in by aclsce, 17 months ago

Moved oasis-mct_5.0 in oasis3-mct/branches directory.

File size: 8.8 KB
Line 
1PROGRAM ocean
2  !
3  ! Use for netCDF library
4  USE netcdf
5  !
6  USE def_parallel_decomposition
7  !!!!!!!!!!!!!!!!! USE mod_oasis !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
8  USE mod_oasis
9  !
10  IMPLICIT NONE
11  !
12  INCLUDE 'mpif.h'   ! Include for MPI
13  !
14  INTEGER :: mype, npes ! rank and number of pe
15  INTEGER :: local_comm  ! local communicator for ocean processes
16  CHARACTER(len=128) :: comp_out_ocean ! name of the output log file
17  CHARACTER(len=3)   :: chout
18  INTEGER :: ierror, w_unit
19  INTEGER :: info
20  !
21  ! Global grid parameters
22  INTEGER, PARAMETER :: nlon_ocean = 182, nlat_ocean = 149    ! dimensions in the 2 spatial directions
23  INTEGER, PARAMETER :: nc_ocean = 4 ! number of grid cell vertices in the (i,j) plan
24  !
25  ! Local grid dimensions and arrays
26  INTEGER :: il_extentx, il_extenty, il_offsetx, il_offsety
27  INTEGER :: il_size, il_offset
28  DOUBLE PRECISION, DIMENSION(:,:),   POINTER   :: grid_lon_ocean, grid_lat_ocean ! lon, lat of the cell centers
29  DOUBLE PRECISION, DIMENSION(:,:,:), POINTER   :: grid_clo_ocean, grid_cla_ocean ! lon, lat of the cell corners
30  DOUBLE PRECISION, DIMENSION(:,:),   POINTER   :: grid_srf_ocean ! surface of the grid meshes
31  INTEGER, DIMENSION(:,:),            POINTER   :: grid_msk_ocean ! mask, 0 == valid point, 1 == masked point
32  !
33  ! For time step loop
34  INTEGER               ::  ib
35  INTEGER, PARAMETER    ::  il_nb_time_steps = 4 ! number of time steps
36  INTEGER, PARAMETER    ::  delta_t = 3600       ! time step
37  INTEGER               ::  itap_sec ! time in seconds
38  DOUBLE PRECISION, PARAMETER    :: dp_pi=3.14159265359
39  DOUBLE PRECISION, PARAMETER    :: dp_length= 1.2*dp_pi
40  !
41  ! Local coupling fields arrays exchanged via oasis_get and oasis_put
42  DOUBLE PRECISION, POINTER :: field_recv_ocean(:,:)
43  DOUBLE PRECISION, POINTER :: field_send_ocean(:,:)
44  !
45  ! Used in OASIS3-MCT definition calls
46  INTEGER               :: compid
47  INTEGER               :: il_part_id
48  INTEGER               :: ig_paral_size
49  INTEGER, DIMENSION(:), ALLOCATABLE :: ig_paral
50  INTEGER               :: flag          ! Flag for grid writing
51  INTEGER               :: var_id(2)
52  INTEGER               :: var_nodims(2)
53  INTEGER               :: var_actual_shape(1)
54  INTEGER               :: var_type
55  !
56  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
57  !  INITIALISATION
58  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
59  !
60  call MPI_Init(ierror)
61  !
62  local_comm =  MPI_COMM_WORLD
63  !
64  !!!!!!!!!!!!!!!!! OASIS_INIT_COMP !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
65  CALL oasis_init_comp (compid,'ocean_component',ierror)
66  !
67  !!!!!!!!!!!!!!!!! OASIS_GET_LOCALCOMM !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
68  CALL oasis_get_localcomm ( local_comm, ierror )
69  !
70  ! Get rank in local communicator
71  CALL MPI_Comm_Size ( local_comm, npes, ierror )
72  CALL MPI_Comm_Rank ( local_comm, mype, ierror )
73  !
74  ! Unit for output messages : one file for each process
75  w_unit = 100 + mype
76  WRITE(chout,'(I3)') w_unit
77  comp_out_ocean='ocean.out_'//chout
78  !
79  OPEN(w_unit,file=TRIM(comp_out_ocean),form='formatted')
80  WRITE (w_unit,*) '-----------------------------------------------------------'
81  WRITE (w_unit,*) 'I am ocean process with rank :',mype
82  WRITE (w_unit,*) 'in my local communicator gathering ', npes, 'processes'
83  WRITE (w_unit,*) '----------------------------------------------------------'
84  CALL flush(w_unit)
85  !
86  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
87  !  PARTITION DEFINITION
88  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ !
89  !
90  ! Definition of the local partition
91  call def_local_partition(nlon_ocean, nlat_ocean, npes, mype, &
92                         il_extentx, il_extenty, il_size, il_offsetx, il_offsety, il_offset)
93  WRITE(w_unit,*) 'Local partition definition'
94  WRITE(w_unit,*) 'il_extentx, il_extenty, il_size, il_offsetx, il_offsety, il_offset = ', &
95                   il_extentx, il_extenty, il_size, il_offsetx, il_offsety, il_offset
96  !
97  !!!!!!!!!!!!!!!!! OASIS_DEF_PARTITION !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
98  call def_paral_size (ig_paral_size)
99  ALLOCATE(ig_paral(ig_paral_size))
100  call def_paral (il_offset, il_size, il_extentx, il_extenty, nlon_ocean, ig_paral_size, ig_paral)
101  WRITE(w_unit,*) 'ig_paral = ', ig_paral(:)
102  call flush(w_unit)
103  CALL oasis_def_partition (il_part_id, ig_paral, ierror)
104  DEALLOCATE(ig_paral)
105  !
106  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
107  !  GRID DEFINITION
108  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
109  !
110  ! Allocation of local grid arrays
111  ALLOCATE(grid_lon_ocean(il_extentx, il_extenty), STAT=ierror )
112  ALLOCATE(grid_lat_ocean(il_extentx, il_extenty), STAT=ierror )
113  ALLOCATE(grid_clo_ocean(il_extentx, il_extenty, nc_ocean), STAT=ierror )
114  ALLOCATE(grid_cla_ocean(il_extentx, il_extenty, nc_ocean), STAT=ierror )
115  ALLOCATE(grid_srf_ocean(il_extentx, il_extenty), STAT=ierror )
116  ALLOCATE(grid_msk_ocean(il_extentx, il_extenty), STAT=ierror )
117  !
118  ! Reading local grid arrays from input file ocean_mesh.nc
119  CALL read_grid(nlon_ocean, nlat_ocean, nc_ocean, il_offsetx+1, il_offsety+1, il_extentx, il_extenty, &
120                'ocean_mesh.nc', w_unit, grid_lon_ocean, grid_lat_ocean, grid_clo_ocean, &
121                grid_cla_ocean, grid_srf_ocean, grid_msk_ocean)
122  !
123  !!!!!!!!!!!!!!!!! OASIS_WRITE_GRID  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
124  CALL oasis_start_grids_writing(flag)
125  CALL oasis_write_grid('torc', nlon_ocean, nlat_ocean, grid_lon_ocean, grid_lat_ocean, il_part_id)
126  CALL oasis_write_corner('torc', nlon_ocean, nlat_ocean, 4, grid_clo_ocean, grid_cla_ocean, il_part_id)
127  CALL oasis_write_mask('torc', nlon_ocean, nlat_ocean, grid_msk_ocean(:,:), il_part_id)
128  CALL oasis_terminate_grids_writing()
129  WRITE(w_unit,*) 'grid_lat_ocean maximum and minimum', MAXVAL(grid_lat_ocean), MINVAL(grid_lat_ocean)
130  call flush(w_unit)
131  !
132  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
133  !  DEFINITION OF THE LOCAL FIELDS 
134  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
135  !
136  ! Allocate local coupling fields
137  ALLOCATE(field_send_ocean(il_extentx, il_extenty), STAT=ierror )
138  ALLOCATE(field_recv_ocean(il_extentx, il_extenty), STAT=ierror )
139  !
140  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
141  !  DECLARATION OF THE COUPLING FIELDS 
142  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
143  !
144  !!!!!!!!!!!!!!!!!! OASIS_DEF_VAR !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
145  var_nodims(1) = 2    ! Rank of the field array ; not used anymore in OASIS3-MCT
146  var_nodims(2) = 1    ! Number of bundle fields
147  var_actual_shape(1) = 1 ! Not used anymore in OASIS3-MCT
148  var_type = OASIS_Real
149  !
150  ! Declaration of the coupling fields
151  CALL oasis_def_var (var_id(1),'FIELD_RECV_OCN', il_part_id, var_nodims, OASIS_In, var_actual_shape, var_type, ierror)
152  CALL oasis_def_var (var_id(2),'FIELD_SEND_OCN', il_part_id, var_nodims, OASIS_Out, var_actual_shape, var_type, ierror)
153  WRITE(w_unit,*)'var_id FRECVOCN, var_id FSENDOCN', var_id(1), var_id(2)
154  call flush(w_unit)
155  !
156  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
157  !         TERMINATION OF DEFINITION PHASE
158  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
159  !
160  WRITE(w_unit,*) 'End of initialisation phase'
161  call flush(w_unit)
162  !
163  !!!!!!!!!!!!!!!!!! OASIS_ENDDEF !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
164  CALL oasis_enddef (ierror)
165  !
166  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
167  !  TIME STEP LOOP
168  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
169  !
170  write(w_unit,*) 'Timestep, field min and max value'
171  call flush(w_unit)
172  DO ib = 1,il_nb_time_steps
173    !
174    itap_sec = delta_t * (ib-1) ! time in seconds
175    field_recv_ocean=-1.0
176    !
177    !!!!!!!!!!!!!!!!!!!!!!!! OASIS_GET !!!!!!!!!!!!!!!!!!!!!!
178    CALL oasis_get(var_id(1),itap_sec, field_recv_ocean, info)
179    write(w_unit,*) itap_sec,minval(field_recv_ocean),maxval(field_recv_ocean)
180    !
181    ! Definition of field produced by the component
182    field_send_ocean(:,:) =  ib*(2.-COS(dp_pi*(ACOS(COS(grid_lat_ocean(:,:)*dp_pi/180.)* &
183                           COS(grid_lon_ocean(:,:)*dp_pi/180.))/dp_length)))
184    !write(w_unit,*) itap_sec,minval(field_send_ocean),maxval(field_send_ocean)
185    !
186    !!!!!!!!!!!!!!!!!!!!!!!! OASIS_PUT !!!!!!!!!!!!!!!!!!!!!!
187    CALL oasis_put(var_id(2),itap_sec, field_send_ocean, info)
188    !
189  ENDDO
190  !
191  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
192  !         TERMINATION
193  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
194  !
195  !!!!!!!!!!!!!!!!!! OASIS_TERMINATE !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
196  CALL oasis_terminate (ierror)
197  !
198  WRITE (w_unit,*) 'End of the program'
199  CALL flush(w_unit)
200  CLOSE(w_unit)
201  !
202  CALL MPI_Finalize(ierror)
203  !
204END PROGRAM ocean
205!
Note: See TracBrowser for help on using the repository browser.