SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
coupling_surf_topd.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 !###################################################################
6 SUBROUTINE coupling_surf_topd (DGEI, DGMI, IG, I, UG, U, &
7  hprogram,ki)
8 !###################################################################
9 !
10 !!**** *COUPLING_SURF_TOPD*
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !! Driver for the coupling between SURFEX and TOPODYN
16 !!
17 !! REFERENCE
18 !! ---------
19 !! *COUPLING_SURF_TRIP from B. Decharme
20 !!
21 !! AUTHOR
22 !! ------
23 !! B. Vincendon
24 !!
25 !! MODIFICATIONS
26 !! -------------
27 !! Original 07/06/11
28 !-------------------------------------------------------------------------------
29 !
30 !* 0. DECLARATIONS
31 ! ------------
32 !
33 !
34 !
35 !
38 USE modd_isba_grid_n, ONLY : isba_grid_t
39 USE modd_isba_n, ONLY : isba_t
41 USE modd_surf_atm_n, ONLY : surf_atm_t
42 !
43 USE modi_get_luout
44 USE modi_coupl_topd
45 USE modi_rout_data_isba
46 USE modi_budget_coupl_rout
47 USE modi_write_discharge_file
48 USE modi_write_budget_coupl_rout
49 USE modi_prep_restart_coupl_topd
50 !
51 USE modd_topodyn, ONLY : xqtot, nnb_topd_step, xqb_run, xqb_dr
52 USE modd_coupling_topd, ONLY : lcoupl_topd, lbudget_topd, nnb_topd, ltopd_step, ntopd_step, &
53  nyear,nmonth,nday,nh,nm
54 !
55 !
56 USE yomhook ,ONLY : lhook, dr_hook
57 USE parkind1 ,ONLY : jprb
58 !
59 IMPLICIT NONE
60 !
61 !* 0.1 declarations of arguments
62 !
63 !
64 TYPE(diag_evap_isba_t), INTENT(INOUT) :: dgei
65 TYPE(diag_misc_isba_t), INTENT(INOUT) :: dgmi
66 TYPE(isba_grid_t), INTENT(INOUT) :: ig
67 TYPE(isba_t), INTENT(INOUT) :: i
68 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
69 TYPE(surf_atm_t), INTENT(INOUT) :: u
70 !
71  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling surf. schemes
72 INTEGER, INTENT(IN) :: ki ! Surfex grid dimension
73  ! in a forcing iteration
74 !
75 !* 0.2 declarations of local variables
76 !
77  CHARACTER(LEN=3) :: ystep ! time stepsurf_tmp/off
78 INTEGER :: iluout ! unit of output listing file
79 INTEGER :: jj ! loop control
80 !
81 REAL, DIMENSION(KI) :: zdg_full
82 REAL, DIMENSION(KI) :: zwg2_full,zwg3_full,zdg2_full,zdg3_full
83 REAL(KIND=JPRB) :: zhook_handle
84 !-------------------------------------------------------------------------------
85 IF (lhook) CALL dr_hook('COUPLING_SURF_TOPD',0,zhook_handle)
86 !
87  CALL get_luout(hprogram,iluout)
88 !
89 IF ( .NOT.lcoupl_topd ) THEN
90  IF (lhook) CALL dr_hook('COUPLING_SURF_TOPD',1,zhook_handle)
91  RETURN
92 ENDIF
93  !
94 IF ( ltopd_step ) THEN
95  !
96  ! * 1. Calling coupling or routing
97  !
98  IF (ntopd_step<10) THEN
99  WRITE(ystep,'(I1)') ntopd_step
100  ELSEIF (ntopd_step < 100) THEN
101  WRITE(ystep,'(I2)') ntopd_step
102  ELSE
103  WRITE(ystep,'(I3)') ntopd_step
104  ENDIF
105  !
106  write(iluout,*) 'pas de temps coupl ',ystep
107  !
108  IF (i%CRUNOFF=='TOPD') THEN
109  CALL coupl_topd(dgei, dgmi, ig, i, ug, u, &
110  hprogram,ystep,ki,ntopd_step)
111  ELSE
112  CALL rout_data_isba(dgei, dgmi, ig, i, ug, u, &
113  hprogram,ki,ntopd_step)
114  ENDIF
115  !
116  IF (lbudget_topd) CALL budget_coupl_rout(dgei, dgmi, i, u, &
117  ki,ntopd_step)
118  !
119 endif! (LCOUPL_TOPD.AND......
120 !
121 IF (lhook) CALL dr_hook('COUPLING_SURF_TOPD',1,zhook_handle)
122 !-------------------------------------------------------------------------------
123 END SUBROUTINE coupling_surf_topd
subroutine coupling_surf_topd(DGEI, DGMI, IG, I, UG, U, HPROGRAM, KI)
subroutine budget_coupl_rout(DGEI, DGMI, I, U, KNI, KFORC_STEP)
subroutine rout_data_isba(DGEI, DGMI, IG, I, UG, U, HPROGRAM, KI, KSTEP)
subroutine coupl_topd(DGEI, DGMI, IG, I, UG, U, HPROGRAM, HSTEP, KI, KSTEP)
Definition: coupl_topd.F90:7
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6