source: CPL/oasis3-mct/branches/OASIS3-MCT_5.0_branch/examples/tutorial_communication/atmos.F90 @ 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: 6.5 KB
Line 
1PROGRAM atmos
2  !
3  ! Use for netCDF library
4  USE netcdf
5  !
6  USE def_parallel_decomposition
7  !
8  IMPLICIT NONE
9  !
10  INCLUDE 'mpif.h'   ! Include for MPI
11  !
12  INTEGER :: mype, npes ! rank and number of pe
13  INTEGER :: local_comm  ! local communicator for atmos processes
14  CHARACTER(len=128) :: comp_out_atmos ! name of the output log file
15  CHARACTER(len=3)   :: chout
16  INTEGER :: ierror, w_unit
17  !
18  ! Global grid parameters
19  INTEGER, PARAMETER :: nlon_atmos = 96, nlat_atmos = 72    ! dimensions in the 2 spatial directions
20  INTEGER, PARAMETER :: nc_atmos = 4 ! number of grid cell vertices in the (i,j) plan
21  !
22  ! Local grid dimensions and arrays
23  INTEGER :: il_extentx, il_extenty, il_offsetx, il_offsety
24  INTEGER :: il_size, il_offset
25  DOUBLE PRECISION, DIMENSION(:,:),   POINTER   :: grid_lon_atmos, grid_lat_atmos ! lon, lat of the cell centers
26  DOUBLE PRECISION, DIMENSION(:,:,:), POINTER   :: grid_clo_atmos, grid_cla_atmos ! lon, lat of the cell corners
27  DOUBLE PRECISION, DIMENSION(:,:),   POINTER   :: grid_srf_atmos ! surface of the grid meshes
28  INTEGER, DIMENSION(:,:),            POINTER   :: grid_msk_atmos ! mask, 0 == valid point, 1 == masked point
29  !
30  ! For time step loop
31  INTEGER               ::  ib
32  INTEGER, PARAMETER    ::  il_nb_time_steps = 8 ! number of time steps
33  INTEGER, PARAMETER    ::  delta_t = 1800       ! time step
34  INTEGER               ::  itap_sec ! time in seconds
35  DOUBLE PRECISION, PARAMETER    :: dp_pi=3.14159265359
36  DOUBLE PRECISION, PARAMETER    :: dp_length= 1.2*dp_pi
37  !
38  ! Local coupling fields arrays exchanged via oasis_get and oasis_put
39  DOUBLE PRECISION, POINTER :: field_recv_atmos(:,:)
40  DOUBLE PRECISION, POINTER :: field_send_atmos(:,:)
41  !
42  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
43  !  INITIALISATION
44  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
45  !
46  call MPI_Init(ierror)
47  !
48  local_comm =  MPI_COMM_WORLD
49  !
50  !!!!!!!!!!!!!!!!! OASIS_INIT_COMP !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
51  !
52  !!!!!!!!!!!!!!!!! OASIS_GET_LOCALCOMM !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
53  !
54  ! Get rank in local communicator
55  CALL MPI_Comm_Size ( local_comm, npes, ierror )
56  CALL MPI_Comm_Rank ( local_comm, mype, ierror )
57 
58  ! Unit for output messages : one file for each process
59  w_unit = 100 + mype
60  WRITE(chout,'(I3)') w_unit
61  comp_out_atmos='atmos.out_'//chout
62  !
63  OPEN(w_unit,file=TRIM(comp_out_atmos),form='formatted')
64  WRITE (w_unit,*) '-----------------------------------------------------------'
65  WRITE (w_unit,*) 'I am atmos process with rank :', mype
66  WRITE (w_unit,*) 'in my local communicator gathering ', npes, 'processes'
67  WRITE (w_unit,*) '----------------------------------------------------------'
68  CALL flush(w_unit)
69  !
70  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
71  !  PARTITION DEFINITION
72  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ !
73  !
74  ! Definition of the local partition
75  call def_local_partition(nlon_atmos, nlat_atmos, npes, mype, &
76                         il_extentx, il_extenty, il_size, il_offsetx, il_offsety, il_offset)
77  WRITE(w_unit,*) 'Local partition definition'
78  WRITE(w_unit,*) 'il_extentx, il_extenty, il_size, il_offsetx, il_offsety, il_offset = ', &
79                   il_extentx, il_extenty, il_size, il_offsetx, il_offsety, il_offset
80  !
81  !!!!!!!!!!!!!!!!! OASIS_DEF_PARTITION !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
82  !
83  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
84  !  GRID DEFINITION
85  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
86  !
87  ! Allocation of local grid arrays
88  ALLOCATE(grid_lon_atmos(il_extentx, il_extenty), STAT=ierror )
89  ALLOCATE(grid_lat_atmos(il_extentx, il_extenty), STAT=ierror )
90  ALLOCATE(grid_clo_atmos(il_extentx, il_extenty, nc_atmos), STAT=ierror )
91  ALLOCATE(grid_cla_atmos(il_extentx, il_extenty, nc_atmos), STAT=ierror )
92  ALLOCATE(grid_srf_atmos(il_extentx, il_extenty), STAT=ierror )
93  ALLOCATE(grid_msk_atmos(il_extentx, il_extenty), STAT=ierror )
94  !
95  ! Reading local grid arrays from input file atmos_mesh.nc
96  CALL read_grid(nlon_atmos, nlat_atmos, nc_atmos, il_offsetx+1, il_offsety+1, il_extentx, il_extenty, &
97                'atmos_mesh.nc', w_unit, grid_lon_atmos, grid_lat_atmos, grid_clo_atmos, &
98                 grid_cla_atmos, grid_srf_atmos, grid_msk_atmos)
99  !
100  !!!!!!!!!!!!!!!!! OASIS_WRITE_GRID  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
101  !
102  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
103  !  DEFINITION OF THE LOCAL FIELDS 
104  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
105  !
106  ! Allocate local coupling fields
107  ALLOCATE(field_send_atmos(il_extentx, il_extenty), STAT=ierror )
108  ALLOCATE(field_recv_atmos(il_extentx, il_extenty), STAT=ierror )
109  !
110  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
111  !  DECLARATION OF THE COUPLING FIELDS 
112  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
113  !
114  !!!!!!!!!!!!!!!!!! OASIS_DEF_VAR !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
115  !
116  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
117  !         TERMINATION OF DEFINITION PHASE
118  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
119  !
120  WRITE(w_unit,*) 'End of initialisation phase'
121  call flush(w_unit)
122  !
123  !!!!!!!!!!!!!!!!!! OASIS_ENDDEF !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
124  !
125  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
126  !  TIME STEP LOOP
127  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
128  !
129  write(w_unit,*) 'Timestep, field min and max value'
130  call flush(w_unit)
131  DO ib = 1,il_nb_time_steps
132    !
133    itap_sec = delta_t * (ib-1) ! time in seconds
134    field_recv_atmos=-1.0
135    !
136    !!!!!!!!!!!!!!!!!!!!!!!! OASIS_GET !!!!!!!!!!!!!!!!!!!!!!
137    !
138    ! Definition of field produced by the component
139    field_send_atmos(:,:) =  ib*(2.-COS(dp_pi*(ACOS(COS(grid_lat_atmos(:,:)*dp_pi/90.)* &
140                           COS(grid_lon_atmos(:,:)*dp_pi/90.))/dp_length)))
141    write(w_unit,*) itap_sec,minval(field_send_atmos),maxval(field_send_atmos)
142    !
143    !!!!!!!!!!!!!!!!!!!!!!!! OASIS_PUT !!!!!!!!!!!!!!!!!!!!!!
144    !
145  ENDDO
146  !
147  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
148  !         TERMINATION
149  !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
150  !
151  !!!!!!!!!!!!!!!!!! OASIS_TERMINATE !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
152  !
153  WRITE (w_unit,*) 'End of the program'
154  CALL flush(w_unit)
155  CLOSE(w_unit)
156  !
157  CALL MPI_Finalize(ierror)
158  !
159END PROGRAM atmos
160!
Note: See TracBrowser for help on using the repository browser.