SURFEX v8.1
General documentation of Surfex
trip_master.F90
Go to the documentation of this file.
1 !###################################################################
2 PROGRAM trip_master
3 !###################################################################
4 !
5 !
6 !!**** *TRIP_MASTER*
7 !!
8 !! PURPOSE
9 !! -------
10 !!
11 !! Driver for TRIP from CNRM
12 !!
13 !! REFERENCE
14 !! ---------
15 !!
16 !! AUTHOR
17 !! ------
18 !! B. Decharme
19 !!
20 !! MODIFICATIONS
21 !! -------------
22 !! Original 06/08
23 !! S.Sénési 08/11/16 : interface to XIOS
24 !-------------------------------------------------------------------------------
25 !
26 !* 0. DECLARATIONS
27 ! ------------
28 !
31 !
33 !
34 USE modn_trip_run, ONLY : lrestart, lprint, lwr_diag, &
36 !
37 USE modd_trip_par, ONLY : xundef, nundef, xday
38 !
39 USE mode_rw_trip
40 !
41 USE modi_read_nam_trip_run
42 USE modi_read_nam_trip
43 USE modi_read_nam_trip_grid
44 !
45 USE modi_abort_trip
46 USE modi_get_trip_grid_conf
47 !
48 USE modi_init_trip
49 USE modi_init_trip_par
50 USE modi_trip_run_conf
51 USE modi_trip_restart
52 USE modi_trip_diag_run
53 USE modi_trip_run
54 !
55 USE modi_trip_oasis_init
56 USE modi_trip_oasis_read_nam
57 USE modi_trip_oasis_define
58 USE modi_trip_oasis_end
59 !
60 USE modi_trip_xios_init
61 !
62 #ifdef SFX_MPI
63 #ifdef SFX_MPL
65 #endif
66 #endif
67 USE yomhook ,ONLY : lhook, dr_hook
68 USE parkind1 ,ONLY : jprb
69 !
70 IMPLICIT NONE
71 !
72 #if defined CPLOASIS || defined WXIOS
73 include 'mpif.h'
74 #endif
75 !
76 INTEGER :: IYEAR ! current year (UTC)
77 INTEGER :: IMONTH ! current month (UTC)
78 INTEGER :: IDAY ! current day (UTC)
79 REAL :: ZTIME ! current time (s)
80 REAL :: ZRUNTIME ! total simulated time (s)
81 !
82 INTEGER :: INB_TSTEP_RUN ! number of time step in the run
83 INTEGER :: ILON ! Number of longitude
84 INTEGER :: ILAT ! Number of latittude
85 !
86 INTEGER :: INB_OL ! number of time step if forcing offline
87 INTEGER :: ILON_OL ! Number of longitude if forcing offline
88 INTEGER :: ILAT_OL ! Number of latittude if forcing offline
89 !
90 INTEGER :: IERR ! Error value
91 INTEGER :: INPROC ! Number of processes
92 INTEGER :: IRANK ! Local process number
93 INTEGER :: ILOCAL_COMM ! Local communicator
94 LOGICAL :: GOASIS ! OASIS used(default=.false.)
95 LOGICAL :: GXIOS ! XIOS used(default=.false.)
96 !
97 REAL(KIND=JPRB) :: ZHOOK_HANDLE
98 !
99 ! --------------------------------------------------------------------------------------
100 ! * 0. MPI and OASIS must be initialized before any DR_HOOK call
101 ! --------------------------------------------------------------------------------------
102 !
103  CALL trip_oasis_init(goasis,gxios,ilocal_comm,pruntime=zruntime)
104 !
105 #ifdef SFX_MPI
106 #ifdef SFX_MPL
107 IF (ilocal_comm/=0) THEN
108  lmplusercomm = .true.
109  mplusercomm = ilocal_comm
110 ENDIF
111 #endif
112 #endif
113 !
114 ! --------------------------------------------------------------------------------------
115 ! * 1. Alloc trip variables and open listing
116 ! --------------------------------------------------------------------------------------
117 !
118 IF (lhook) CALL dr_hook('TRIP_MASTER',0,zhook_handle)
119 !
120  CALL trip_alloc_list(1)
121 !
122  CALL init_trip_par
123 !
124 OPEN(unit=nlisting,file=clisting,form='FORMATTED',action='WRITE')
125 !
126 ! --------------------------------------------------------------------------------------
127 ! * 2. Check run attributes
128 ! --------------------------------------------------------------------------------------
129 !
130 !Inquire if trip is parallel or not: TRIP is only a monoprocess model for now
131 !
132 inproc = nundef
133 irank = nundef
134 !
135 #ifdef CPLOASIS || WXIOS
136 IF (ilocal_comm==0) THEN
137  ilocal_comm = mpi_comm_world
138 ENDIF
139  CALL mpi_comm_size(ilocal_comm,inproc,ierr)
140  CALL mpi_comm_rank(ilocal_comm,irank,ierr)
141 !
142 IF(inproc==nundef.OR.irank==nundef)THEN
143  WRITE(nlisting,*)'TRIP_MASTER: PROBLEM WITH MPI, INPROC = ',inproc
144  WRITE(nlisting,*)'TRIP_MASTER: PROBLEM WITH MPI, IRANK = ',irank
145  CALL abort_trip('TRIP_MASTER: PROBLEM WITH MPI')
146 ENDIF
147 #endif
148 !
149 IF(inproc>1.AND.inproc<nundef)THEN
150  WRITE(nlisting,*)'TRIP_MASTER: TRIP NOT YET PARALLELIZED, NPROC SHOULD BE 1'
151  CALL abort_trip('TRIP_MASTER: TRIP NOT YET PARALLELIZED')
152 ENDIF
153 !
154 IF(goasis)THEN
155  WRITE(nlisting,*) '!!!!!!!!!!!!!!!!!!!!!!!'
156  WRITE(nlisting,*) ' OASIS is used '
157  WRITE(nlisting,*) ' '
158  WRITE(nlisting,*) 'Number of processes :', inproc
159  WRITE(nlisting,*) 'Local process number :', irank
160  WRITE(nlisting,*) 'Local communicator :', ilocal_comm
161  WRITE(nlisting,*) '!!!!!!!!!!!!!!!!!!!!!!!'
162  WRITE(nlisting,*) ' '
163 ELSE
164  WRITE(nlisting,*) '!!!!!!!!!!!!!!!!!!!!!!!'
165  WRITE(nlisting,*) ' TRIP run offline '
166  WRITE(nlisting,*) '!!!!!!!!!!!!!!!!!!!!!!!'
167  WRITE(nlisting,*) ' '
168 ENDIF
169 !
170 ! --------------------------------------------------------------------------------------
171 ! * 3. read namelists
172 ! --------------------------------------------------------------------------------------
173 !
175 !
176  CALL read_nam_trip(nlisting)
177 !
178 IF(goasis)THEN
179  CALL trip_oasis_read_nam(nlisting,zruntime)
180 ENDIF
181 !
182 ! --------------------------------------------------------------------------------------
183 ! * 4. TRIP initializations
184 ! --------------------------------------------------------------------------------------
185 !
186 ytrip_cur => ytrip_list(1)
187 !
189 !
190  CALL init_trip(ytrip_cur%TPDG, ytrip_cur%TP, ytrip_cur%TPG, &
191  iyear,imonth,iday,ztime,ilon,ilat,xtstep_run, &
192  xtstep_diag,lrestart,gxios)
193 !
194 ! --------------------------------------------------------------------------------------
195 ! * 5. TRIP - OASIS grid, partitions and local field definitions
196 ! --------------------------------------------------------------------------------------
197 !
198 IF(goasis)THEN
199  CALL trip_oasis_define(nlisting,ilon,ilat)
200 ENDIF
201 !
202 ! --------------------------------------------------------------------------------------
203 ! * 5.2 XIOS init
204 ! --------------------------------------------------------------------------------------
205 !
206 #ifdef WXIOS
207 IF (gxios) THEN
208  CALL trip_xios_init(ytrip_cur%TPG,ilocal_comm,ilon,ilat,&
209  iyear,imonth,iday,ztime)
210 ENDIF
211 #endif
212 !
213 ! --------------------------------------------------------------------------------------
214 ! * 6. Get run configuration
215 ! --------------------------------------------------------------------------------------
216 !
217  CALL trip_run_conf(nlisting,goasis,iyear,imonth,iday,ztime, &
218  ilon,ilat,inb_tstep_run,zruntime )
219 !
220 IF(goasis)THEN
221  inb_ol = 0
222  ilon_ol = 0
223  ilat_ol = 0
224 ELSE
225  inb_ol = inb_tstep_run
226  ilon_ol = ilon
227  ilat_ol = ilat
228 ENDIF
229 !
230 ! --------------------------------------------------------------------------------------
231 ! * 7. Read and prepare drainage and runoff if offline
232 ! --------------------------------------------------------------------------------------
233 !
234  CALL trip_run(ytrip_cur%TPDG, ytrip_cur%TP, ytrip_cur%TPG, &
235  goasis,gxios, &
236  nlisting,ilon,ilat,inb_tstep_run, &
237  zruntime,ilon_ol,ilat_ol,inb_ol, &
238  iyear,imonth,iday,ztime )
239 !
240 !-------------------------------------------------------------------------------
241 ! * 9. Store run mean diagnostic and write restart
242 !-------------------------------------------------------------------------------
243 !
244 IF (gxios) THEN
245  CALL write_trip(nlisting,'dummy.nc','areacellr',ytrip_cur%TPG%GMASK,ytrip_cur%TPG%XAREA,oxios=.true.)
246 ELSEIF(lwr_diag)THEN
247  CALL trip_diag_run(ytrip_cur%TPDG, ytrip_cur%TPG, &
248  nlisting,ilon,ilat,zruntime)
249 ENDIF
250 !
251 IF(lrestart)THEN
252  CALL trip_restart(ytrip_cur%TP, ytrip_cur%TPG, &
253  nlisting,iyear,imonth,iday,ztime,ilon,ilat)
254 ENDIF
255 !
256 ! --------------------------------------------------------------------------------------
257 ! * 10. End of run
258 ! --------------------------------------------------------------------------------------
259 !
260  CLOSE(nlisting)
261 !
262 WRITE(*,*) ' '
263 WRITE(*,*) ' ------------------------------'
264 WRITE(*,*) ' | TRIP MASTER ENDS CORRECTLY |'
265 WRITE(*,*) ' ------------------------------'
266 WRITE(*,*) ' '
267 !
268  CALL trip_deallo_list
269 !
270 IF (lhook) CALL dr_hook('TRIP_MASTER',1,zhook_handle)
271 !
272 ! --------------------------------------------------------------------------------------
273 ! * 11. MPI and OASIS must be finalized after the last DR_HOOK call
274 ! --------------------------------------------------------------------------------------
275 !
276  CALL trip_oasis_end(goasis,gxios)
277 !
278 !-------------------------------------------------------------------------------
279 END PROGRAM trip_master
subroutine trip_oasis_end(OOASIS, OXIOS)
integer(kind=jpim) mplusercomm
integer, save nundef
subroutine init_trip_par
subroutine trip_alloc_list(KMODEL)
subroutine trip_run(TPDG, TP, TPG, OOASIS, OXIOS, KLISTING, KLON, KLAT, KNB_TSTEP_RUN, PRUNTIME, KLON_OL, KLAT_OL, KNB_OL, KYEAR, KMONTH, KDAY, PTIME)
Definition: trip_run.F90:6
real, save xday
type(trip_model_t), pointer ytrip_cur
subroutine trip_deallo_list
subroutine trip_oasis_define(KLISTING, KLON, KLAT)
subroutine read_nam_trip_grid(TPG, KLISTING)
subroutine trip_xios_init(TPG, KLOCAL_COMM, KLON, KLAT, KYEAR, KMONTH, KDAY, PTIME)
subroutine trip_oasis_init(OOASIS, OXIOS, KLOCAL_COMM, PRUNTIME, LPREP)
subroutine read_nam_trip(KLISTING)
subroutine trip_oasis_read_nam(KLISTING, PRUNTIME)
integer, parameter jprb
Definition: parkind1.F90:32
subroutine init_trip(TPDG, TP, TPG, KYEAR, KMONTH, KDAY, PTIME, KLON, KLAT, PTSTEP_RUN, PTSTEP_DIAG, ORESTART, OXIOS)
Definition: init_trip.F90:5
subroutine trip_diag_run(TPDG, TPG, KLISTING, KLON, KLAT, PRUNTIME)
logical lhook
Definition: yomhook.F90:15
program trip_master
Definition: trip_master.F90:2
subroutine read_nam_trip_run(KLISTING)
subroutine trip_run_conf(KLISTING, OOASIS, KYEAR, KMONTH, KDAY, PTIME, KLON, KLAT, KNB_TSTEP_RUN, PRUNTIME)
character(len=28) clisting
subroutine abort_trip(YTEXT)
Definition: abort_trip.F90:3
type(trip_model_t), dimension(:), allocatable, target, save ytrip_list
subroutine trip_restart(TP, TPG, KLISTING, KYEAR, KMONTH, KDAY, PTIME, KLON, KLAT)
Definition: trip_restart.F90:4
real, save xundef