SURFEX v8.1
General documentation of Surfex
trip_run.F90
Go to the documentation of this file.
1 SUBROUTINE trip_run (TPDG, TP, TPG, &
2  OOASIS, OXIOS, &
3  KLISTING,KLON,KLAT,KNB_TSTEP_RUN, &
4  PRUNTIME,KLON_OL,KLAT_OL,KNB_OL, &
5  KYEAR,KMONTH,KDAY,PTIME )
6 !#############################################
7 !
8 !!**** *TRIP_RUN*
9 !!
10 !! PURPOSE
11 !! -------
12 !!
13 !! Run trip
14 !!
15 !! REFERENCE
16 !! ---------
17 !!
18 !! AUTHOR
19 !! ------
20 !! B. Decharme
21 !!
22 !! MODIFICATIONS
23 !! -------------
24 !! Original 06/08
25 !! B. Decharme 10/2016 bug surface/groundwater coupling
26 !! S.Sénési 08/11/16 : interface to XIOS
27 !-------------------------------------------------------------------------------
28 !
29 !* 0. DECLARATIONS
30 ! ------------
31 !
32 USE modd_trip_diag, ONLY : trip_diag_t
33 USE modd_trip, ONLY : trip_t
34 USE modd_trip_grid, ONLY : trip_grid_t
35 !
37 !
38 USE modn_trip_run, ONLY : lrestart, lprint, &
40 !
41 USE modd_trip_par, ONLY : xundef, nundef, xday
42 !
43 USE modi_trip_forcing
44 USE modi_trip_interface
45 USE modi_trip_date
46 !
47 USE modi_trip_oasis_recv
48 USE modi_trip_oasis_send
49 !
50 USE yomhook ,ONLY : lhook, dr_hook
51 USE parkind1 ,ONLY : jprb
52 !
53 IMPLICIT NONE
54 !
55 !-------------------------------------------------------------------------------
56 !
57 !* 0.1 declarations of arguments
58 !
59 !
60 TYPE(trip_diag_t), INTENT(INOUT) :: TPDG
61 TYPE(trip_t), INTENT(INOUT) :: TP
62 TYPE(trip_grid_t), INTENT(INOUT) :: TPG
63 !
64 LOGICAL, INTENT(IN) :: OOASIS ! Oasis coupling or not
65 LOGICAL, INTENT(IN) :: OXIOS ! Do we use XIOS
66 !
67 INTEGER, INTENT(IN) :: KLISTING ! Listing ID
68 INTEGER, INTENT(IN) :: KLON ! Number of longitude
69 INTEGER, INTENT(IN) :: KLAT ! Number of latittude
70 INTEGER, INTENT(IN) :: KNB_TSTEP_RUN ! number of time step in the run
71 REAL, INTENT(IN) :: PRUNTIME ! total simulated time
72 !
73 INTEGER, INTENT(IN) :: KLON_OL ! Number of longitude if forcing offline
74 INTEGER, INTENT(IN) :: KLAT_OL ! Number of latittude if forcing offline
75 INTEGER, INTENT(IN) :: KNB_OL ! number of time step if forcing offline
76 !
77 INTEGER, INTENT(OUT) :: KYEAR ! current year (UTC)
78 INTEGER, INTENT(OUT) :: KMONTH ! current month (UTC)
79 INTEGER, INTENT(OUT) :: KDAY ! current day (UTC)
80 REAL, INTENT(OUT) :: PTIME ! current time (s)
81 !
82 !-------------------------------------------------------------------------------
83 !
84 !* 0.2 declarations of local variables
85 !
86 REAL, DIMENSION(KLON_OL,KLAT_OL,KNB_OL) :: ZDRAIN_OL ! Drainage from the forcing file (kg)
87 REAL, DIMENSION(KLON_OL,KLAT_OL,KNB_OL) :: ZRUNOFF_OL ! Surface runoff from the forcing file (kg)
88 REAL, DIMENSION(KLON_OL,KLAT_OL,KNB_OL) :: ZSRC_FLOOD_OL ! Flood source term from the forcing file (kg)
89 !
90 REAL, DIMENSION(KLON,KLAT) :: ZRUNOFF ! Surface runoff (kg/s)
91 REAL, DIMENSION(KLON,KLAT) :: ZDRAIN ! Drainage (kg/s)
92 REAL, DIMENSION(KLON,KLAT) :: ZCALVING ! Calving flux (kg/s)
93 REAL, DIMENSION(KLON,KLAT) :: ZSRC_FLOOD ! Input P-E-I flood source term(kg/s)
94 !
95 REAL :: ZTIMEC ! cumulated current time (s)
96 REAL :: ZTIME_CPL ! Coupling time
97 INTEGER :: JNB_TSTEP_RUN ! TSTEP_RUN counter
98 INTEGER :: JNB_TSTEP_DIAG ! DIAG call counter
99 INTEGER :: ICOUNT
100  CHARACTER(LEN=3) :: YWORK
101 !
102 REAL(KIND=JPRB) :: ZHOOK_HANDLE
103 !
104 ! --------------------------------------------------------------------------------------
105 ! * 1. Initialize
106 ! --------------------------------------------------------------------------------------
107 !
108 IF (lhook) CALL dr_hook('TRIP_RUN',0,zhook_handle)
109 !
110 zrunoff(:,:) = xundef
111 zdrain(:,:) = xundef
112 zcalving(:,:) = xundef
113 zsrc_flood(:,:) = xundef
114 !
115 ! --------------------------------------------------------------------------------------
116 ! * 2. Read and prepare drainage and runoff if offline
117 ! --------------------------------------------------------------------------------------
118 !
119 IF(.NOT.ooasis)THEN
120  zdrain_ol(:,:,:) = xundef
121  zrunoff_ol(:,:,:) = xundef
122  zsrc_flood_ol(:,:,:) = xundef
123  CALL trip_forcing(tpg, &
124  klisting,klon,klat,knb_tstep_run, &
125  zdrain_ol,zrunoff_ol,zsrc_flood_ol)
126 ENDIF
127 !
128 ! --------------------------------------------------------------------------------------
129 ! * 3. Temporal loops
130 ! --------------------------------------------------------------------------------------
131 !
132 ztimec = 0
133 icount = 0
134 jnb_tstep_diag = 0
135 !
136 DO jnb_tstep_run = 1, knb_tstep_run
137 !
138 ! * TRIP INPUT FLUXES (kg/s)
139 !
140  IF(ooasis)THEN
141  CALL trip_oasis_recv(tp, tpg, &
142  klisting,klon,klat,ztimec,zrunoff, &
143  zdrain,zcalving,zsrc_flood )
144  ELSE
145  zdrain(:,:) = zdrain_ol(:,:,jnb_tstep_run) / xtstep_run
146  zrunoff(:,:) = zrunoff_ol(:,:,jnb_tstep_run) / xtstep_run
147  zsrc_flood(:,:) = zsrc_flood_ol(:,:,jnb_tstep_run) / xtstep_run
148  zcalving(:,:) = 0.0
149  ENDIF
150 !
151 ! * TRIP PHYSIC CALL
152 !
153  CALL trip_interface(tpdg, tp, tpg, &
154  klisting,klon,klat,ptime,ztimec, &
155  lprint,jnb_tstep_run,jnb_tstep_diag,&
156  xtstep_run,xtstep_diag,zrunoff, &
157  zdrain,zcalving,zsrc_flood,oxios )
158 !
159 ! * TRIP OUTPUT FLUXES
160 !
161  IF(ooasis)THEN
162  ztime_cpl=ztimec-xtstep_run
163  CALL trip_oasis_send(tp, tpg, &
164  klisting,klon,klat,ztime_cpl)
165  ENDIF
166 !
167  IF (lprint.AND.mod(ztimec,xday)==0.0) THEN
168  icount = icount +1
169  WRITE(*,'(A10,I5,A2,I5)')'TRIP DAY :',icount,' /',int(pruntime/xday)
170  ENDIF
171 !
172 ! * TRIP DATE INCREMENT
173 !
174  CALL trip_date(kyear,kmonth,kday,ptime)
175 !
176 ENDDO
177 !
178 ! --------------------------------------------------------------------------------------
179 ! * 4. End TRIP run
180 ! --------------------------------------------------------------------------------------
181 !
182 IF (lhook) CALL dr_hook('TRIP_RUN',1,zhook_handle)
183 !
184 !-------------------------------------------------------------------------------
185 END SUBROUTINE trip_run
subroutine trip_forcing(TPG, KLUOUT, KLON, KLAT, KNB_TSTEP_RUN, PDRAIN, PRUNOFF, PSRC_FLOOD)
Definition: trip_forcing.F90:5
integer, save nundef
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
subroutine trip_oasis_send(TP, TPG, KLISTING, KLON, KLAT, PTIMEC)
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine trip_date(KYEAR, KMONTH, KDAY, PTIME)
Definition: trip_date.F90:2
subroutine trip_oasis_recv(TP, TPG, KLISTING, KLON, KLAT, PTIMEC, PRUNOFF, PDRAIN, PCALVING, PSRC_FLOOD)
subroutine trip_interface(TPDG, TP, TPG, KLISTING, KLON, KLAT, PTIME, PTIMEC, OPRINT, KNB_TSTEP_RUN, KNB_TSTEP_DIAG, PTSTEP_RUN, PTSTEP_DIAG, PRUNOFF, PDRAIN, PCALVING, PSRC_FLOOD, OXIOS)
real, save xundef