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