SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
init_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 ! #############################################################
7  SUBROUTINE init_surf_topd (DGEI, I, UG, U, &
8  hprogram,ki)
9 ! #############################################################
10 !
11 !!**** *INIT_SURF_TOPD* - routine to initialize variables needed for coupling with Topmodel
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !!** METHOD
17 !! ------
18 !! The routine open and read the namelists NAM_COUPL_TOPD and NAM_TOPD,
19 !! calculates the number of catchments concerned, the different time step
20 !! variables and all the variables nedded for coupling with Topmodel.
21 !!
22 !! EXTERNAL
23 !! --------
24 !!
25 !!
26 !! IMPLICIT ARGUMENTS
27 !! ------------------
28 !!
29 !! REFERENCE
30 !! ---------
31 !!
32 !!
33 !! AUTHOR
34 !! ------
35 !! B. Vincendon *Meteo France*
36 !!
37 !! MODIFICATIONS
38 !! -------------
39 !! Original 11/2006
40 !! Modif 04/2007: Arguments PTOPD_STEP,KNB_TOPD_STEP become module
41 !! variables from MODD_TOPDDYN
42 !! Modif 03/2014: New organisation of routines with init_topd_ol and
43 !! displacement of init_budget
44 !-------------------------------------------------------------------------------
45 !
46 !* 0. DECLARATIONS
47 ! ------------
48 !
49 !
50 !
52 USE modd_isba_n, ONLY : isba_t
54 USE modd_surf_atm_n, ONLY : surf_atm_t
55 !
56 USE modd_surfex_mpi, ONLY : nproc
57 USE modd_surfex_omp, ONLY : nblocktot
58 !
59 USE modd_topodyn, ONLY :ccat, xspeedr, xspeedh, nncat, &
60  xrtop_d2, xspeedg
61 USE modd_coupling_topd, ONLY : lcoupl_topd, nnb_topd, lbudget_topd
62 !
63 !
64 USE modi_get_luout
65 USE modi_abor1_sfx
66 !
67 USE modi_init_topd_ol
68 USE modi_init_coupl_topd
69 USE modi_init_budget_coupl_rout
70 !
71 USE yomhook ,ONLY : lhook, dr_hook
72 USE parkind1 ,ONLY : jprb
73 !
74 IMPLICIT NONE
75 !
76 !* 0.1 Declarations of arguments
77 ! -------------------------
78 !
79 !
80 TYPE(diag_evap_isba_t), INTENT(INOUT) :: dgei
81 TYPE(isba_t), INTENT(INOUT) :: i
82 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
83 TYPE(surf_atm_t), INTENT(INOUT) :: u
84 !
85  CHARACTER(LEN=*), INTENT(IN) :: hprogram !
86 INTEGER, INTENT(IN) :: ki ! grid dimension
87 !
88 INTEGER :: iluout
89 REAL(KIND=JPRB) :: zhook_handle
90 !-------------------------------------------------------------------------------
91 IF (lhook) CALL dr_hook('INIT_SURF_TOPD',0,zhook_handle)
92 !
93 IF (lcoupl_topd) THEN
94  IF (nproc>1) CALL abor1_sfx('INIT_SURF_TOPD: TOPD CANNOT RUN WITH MORE THAN 1 MPI TASK')
95  IF (nblocktot>1) CALL abor1_sfx("INIT_SURF_TOPD: TOPD CANNOT RUN WITH NUMEROUS OPENMP BLOCKS")
96  IF (i%TSNOW%SCHEME/='3-L') &
97  CALL abor1_sfx("INIT_SURF_TOPD: coupling with topmodel only runs with TSNOW%SCHEME=3-L")
98 ENDIF
99 !
100  CALL get_luout(hprogram,iluout)
101 !
102 ! 1. Reads the namelists
103 ! --------------------
104 !
105 WRITE(iluout,*) 'Debut init_surf_topo_n'
106 !
107 IF (lcoupl_topd) THEN
108  !
109  ! 3. Initialises variables specific to Topmodel
110  ! -------------------------------------------
111  WRITE(iluout,*) 'NNCAT',nncat
112  !
113  CALL init_topd_ol(hprogram)
114  !
115  ! 4. Initialises variables nedded for coupling with Topmodel
116  ! -------------------------------------------------------
117  !
118  CALL init_coupl_topd(dgei, i, ug, u, &
119  hprogram,ki)
120  !
121  WRITE(iluout,*) 'Couplage avec TOPMODEL active'
122  !
123  !IF (LBUDGET_TOPD) CALL INIT_BUDGET_COUPL_ROUT(KI)
124  !
125 ELSE
126  !
127  WRITE(iluout,*) 'Pas de couplage avec TOPMODEL'
128  !
129 ENDIF
130 !
131 IF (lhook) CALL dr_hook('INIT_SURF_TOPD',1,zhook_handle)
132 !
133 END SUBROUTINE init_surf_topd
subroutine init_surf_topd(DGEI, I, UG, U, HPROGRAM, KI)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine init_topd_ol(HPROGRAM)
Definition: init_topd_ol.F90:7
subroutine init_coupl_topd(DGEI, I, UG, U, HPROGRAM, KI)