source: CONFIG_DEVT/IPSLCM6.5_work_ENSEMBLES/oasis3-mct/examples/spoc/spoc_communication/atmos.F90_oa @ 5725

Last change on this file since 5725 was 5725, checked in by aclsce, 3 years ago

Added new oasis3-MCT version to be used to handle ensembles simulations with XIOS.

File size: 8.8 KB
Line 
1PROGRAM atmos
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 atmos processes
16  CHARACTER(len=128) :: comp_out_atmos ! 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_atmos = 96, nlat_atmos = 72    ! dimensions in the 2 spatial directions
23  INTEGER, PARAMETER :: nc_atmos = 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_atmos, grid_lat_atmos ! lon, lat of the cell centers
29  DOUBLE PRECISION, DIMENSION(:,:,:), POINTER   :: grid_clo_atmos, grid_cla_atmos ! lon, lat of the cell corners
30  DOUBLE PRECISION, DIMENSION(:,:),   POINTER   :: grid_srf_atmos ! surface of the grid meshes
31  INTEGER, DIMENSION(:,:),            POINTER   :: grid_msk_atmos ! mask, 0 == valid point, 1 == masked point
32  !
33  ! For time step loop
34  INTEGER               ::  ib
35  INTEGER, PARAMETER    ::  il_nb_time_steps = 8 ! number of time steps
36  INTEGER, PARAMETER    ::  delta_t = 1800       ! 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_atmos(:,:)
43  DOUBLE PRECISION, POINTER :: field_send_atmos(:,:)
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) ! not used anymore in OASIS3-MCT
54  INTEGER               :: var_type
55  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
56  !  INITIALISATION
57  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
58  !
59  call MPI_Init(ierror)
60  !
61  local_comm =  MPI_COMM_WORLD
62  !
63  !!!!!!!!!!!!!!!!! OASIS_INIT_COMP !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
64  CALL oasis_init_comp (compid,'atmos_component',ierror)
65  !
66  !!!!!!!!!!!!!!!!! OASIS_GET_LOCALCOMM !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
67  CALL oasis_get_localcomm ( local_comm, ierror )
68  !
69  ! Get rank in local communicator
70  CALL MPI_Comm_Size ( local_comm, npes, ierror )
71  CALL MPI_Comm_Rank ( local_comm, mype, ierror )
72  ! 
73  ! Unit for output messages : one file for each process
74  w_unit = 100 + mype
75  WRITE(chout,'(I3)') w_unit
76  comp_out_atmos='atmos.out_'//chout
77  !
78  OPEN(w_unit,file=TRIM(comp_out_atmos),form='formatted')
79  WRITE (w_unit,*) '-----------------------------------------------------------'
80  WRITE (w_unit,*) 'I am atmos process with rank :', mype
81  WRITE (w_unit,*) 'in my local communicator gathering ', npes, 'processes'
82  WRITE (w_unit,*) '----------------------------------------------------------'
83  CALL flush(w_unit)
84  !
85  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
86  !  PARTITION DEFINITION
87  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ !
88  !
89  ! Definition of the local partition
90  call def_local_partition(nlon_atmos, nlat_atmos, npes, mype, &
91                         il_extentx, il_extenty, il_size, il_offsetx, il_offsety, il_offset)
92  WRITE(w_unit,*) 'Local partition definition'
93  WRITE(w_unit,*) 'il_extentx, il_extenty, il_size, il_offsetx, il_offsety, il_offset = ', &
94                   il_extentx, il_extenty, il_size, il_offsetx, il_offsety, il_offset
95  !
96  !!!!!!!!!!!!!!!!! OASIS_DEF_PARTITION !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
97  call def_paral_size (ig_paral_size)
98  ALLOCATE(ig_paral(ig_paral_size))
99  call def_paral (il_offset, il_size, il_extentx, il_extenty, nlon_atmos, ig_paral_size, ig_paral)
100  WRITE(w_unit,*) 'ig_paral = ', ig_paral(:)
101  call flush(w_unit)
102  CALL oasis_def_partition (il_part_id, ig_paral, ierror)
103  DEALLOCATE(ig_paral)
104  !
105  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
106  !  GRID DEFINITION
107  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
108  !
109  ! Allocation of local grid arrays
110  ALLOCATE(grid_lon_atmos(il_extentx, il_extenty), STAT=ierror )
111  ALLOCATE(grid_lat_atmos(il_extentx, il_extenty), STAT=ierror )
112  ALLOCATE(grid_clo_atmos(il_extentx, il_extenty, nc_atmos), STAT=ierror )
113  ALLOCATE(grid_cla_atmos(il_extentx, il_extenty, nc_atmos), STAT=ierror )
114  ALLOCATE(grid_srf_atmos(il_extentx, il_extenty), STAT=ierror )
115  ALLOCATE(grid_msk_atmos(il_extentx, il_extenty), STAT=ierror )
116  !
117  ! Reading local grid arrays from input file ocean_mesh.nc
118  CALL read_grid(nlon_atmos, nlat_atmos, nc_atmos, il_offsetx+1, il_offsety+1, il_extentx, il_extenty, &
119                'atmos_mesh.nc', w_unit, grid_lon_atmos, grid_lat_atmos, grid_clo_atmos, &
120                grid_cla_atmos, grid_srf_atmos, grid_msk_atmos)
121  !
122  !!!!!!!!!!!!!!!!! OASIS_WRITE_GRID  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
123  CALL oasis_start_grids_writing(flag)
124  CALL oasis_write_grid('lmdz', nlon_atmos, nlat_atmos, grid_lon_atmos, grid_lat_atmos, il_part_id)
125  CALL oasis_write_corner('lmdz', nlon_atmos, nlat_atmos, 4, grid_clo_atmos, grid_cla_atmos, il_part_id)
126  CALL oasis_write_mask('lmdz', nlon_atmos, nlat_atmos, grid_msk_atmos(:,:), il_part_id)
127  CALL oasis_terminate_grids_writing()
128  WRITE(w_unit,*) 'grid_lat_atmos maximum and minimum', MAXVAL(grid_lat_atmos), MINVAL(grid_lat_atmos)
129  call flush(w_unit)
130  !
131  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
132  !  DEFINITION OF THE LOCAL FIELDS 
133  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
134  !
135  ! Allocate local coupling fields
136  ALLOCATE(field_send_atmos(il_extentx, il_extenty), STAT=ierror )
137  ALLOCATE(field_recv_atmos(il_extentx, il_extenty), STAT=ierror )
138  !
139  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
140  !  DECLARATION OF THE COUPLING FIELDS 
141  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
142  !
143  !!!!!!!!!!!!!!!!!! OASIS_DEF_VAR !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
144  !
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_ATM', il_part_id, var_nodims, OASIS_In, var_actual_shape, var_type, ierror)
152  CALL oasis_def_var (var_id(2),'FIELD_SEND_ATM', il_part_id, var_nodims, OASIS_Out, var_actual_shape, var_type, ierror)
153  WRITE(w_unit,*)'var_id FRECVATM, var_id FSENDATM', 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_atmos=-1.0
176    !
177    !!!!!!!!!!!!!!!!!!!!!!!! OASIS_GET !!!!!!!!!!!!!!!!!!!!!!
178    CALL oasis_get(var_id(1),itap_sec, field_recv_atmos, info)
179    write(w_unit,*) itap_sec,minval(field_recv_atmos),maxval(field_recv_atmos)
180    !
181    ! Definition of field produced by the component
182    field_send_atmos(:,:) =  ib*(2.-COS(dp_pi*(ACOS(COS(grid_lat_atmos(:,:)*dp_pi/90.)* &
183                           COS(grid_lon_atmos(:,:)*dp_pi/90.))/dp_length)))
184    !write(w_unit,*) itap_sec,minval(field_send_atmos),maxval(field_send_atmos)
185    !
186    !!!!!!!!!!!!!!!!!!!!!!!! OASIS_PUT !!!!!!!!!!!!!!!!!!!!!!
187    CALL oasis_put(var_id(2),itap_sec, field_send_atmos, 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 atmos
205!
Note: See TracBrowser for help on using the repository browser.