SURFEX v8.1
General documentation of Surfex
init_topd_ol.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_topd_ol(HPROGRAM)
8 ! #######################
9 !
10 !!**** *INIT_TOPD_OL*
11 !!
12 !! PURPOSE
13 !! -------
14 ! This routine aims at initialising the variables
15 ! needed of running Topmodel for OFFLINE step.
16 !
17 !
18 !!** METHOD
19 !! ------
20 !
21 !! EXTERNAL
22 !! --------
23 !!
24 !! none
25 !!
26 !! IMPLICIT ARGUMENTS
27 !! ------------------
28 !!
29 !!
30 !!
31 !!
32 !!
33 !! REFERENCE
34 !! ---------
35 !!
36 !!
37 !!
38 !! AUTHOR
39 !! ------
40 !!
41 !! B. Vincendon * Meteo-France *
42 !!
43 !! MODIFICATIONS
44 !! -------------
45 !!
46 !! Original 03/2014
47 !-------------------------------------------------------------------------------
48 !
49 !* 0. DECLARATIONS
50 ! ------------
51 !
54  xdxt, nnxc, nnyc,&
55  xnul, xx0, xy0, nnpt,&
58  nline, xdmaxt,&
61  xqtot, xtanb, xslop, xdarea,&
63 !
64 USE modd_topd_par, ONLY : ndim
65 USE modd_surf_par, ONLY : xundef, nundef
66 !
67 USE modi_get_luout
68 USE modi_init_topd
69 USE modi_read_topd_header_dtm
70 USE modi_read_topd_file
71 USE modi_read_topd_header_connex
72 USE modi_read_connex_file
73 USE modi_open_file
74 USE modi_close_file
75 !
76 USE yomhook ,ONLY : lhook, dr_hook
77 USE parkind1 ,ONLY : jprb
78 !
79 IMPLICIT NONE
80 !
81 !* 0.1 declarations of arguments
82 !
83  CHARACTER(LEN=*), INTENT(IN) :: HPROGRAM !
84 !
85 !* 0.2 declarations of local variables
86 !
87 !
88 INTEGER :: JI,JJ,JCAT,JO ! loop control
89 INTEGER :: IOVER ! Unit of the files
90 INTEGER :: ILUOUT ! Unit of the files
91 INTEGER :: IOS
92 !
93 CHARACTER(LEN=28) :: YFILE
94 !
95 REAL :: ZTMP !Temporary variable read
96 !
97 REAL :: ZDHIL ! distance along slope
98 REAL :: ZDRIV ! distance along rivers
99 !
100 REAL(KIND=JPRB) :: ZHOOK_HANDLE
101 !-------------------------------------------------------------------------------
102 IF (lhook) CALL dr_hook('INIT_TOPD_OL',0,zhook_handle)
103 !
104 
105 
106 !* 1 Initialization:
107 ! ---------------
108 !
109  CALL get_luout(hprogram,iluout)
110 !
111 WRITE(iluout,*) 'INITIALISATION INIT_TOPD_OL'
112 !
113 CALL INIT_TOPD('ASCII ')
114 !
115  !* 2 Calculations for routing by geomorpho
116  ! -------------------------------------
117  !
118  ALLOCATE(nx_step_rout(nncat))
119  ALLOCATE(xtime_topd(nncat,nmesht))
120  ALLOCATE(xtime_topd_drain(nncat,nmesht))
121  !
122  xtime_topd(:,:) = 0.0
123  xtime_topd_drain(:,:) = 0.0
124  !
125  !
126  DO jcat=1,nncat
127  !
128  IF ( xspeedr(jcat)/=0. .AND. xspeedg(jcat)/=0. ) THEN
129  WHERE ( xdhil(jcat,1:nnmc(jcat))/=xundef .AND. xdriv(jcat,1:nnmc(jcat))/=xundef ) &
130  xtime_topd(jcat,1:nnmc(jcat)) = xdhil(jcat,1:nnmc(jcat)) / xspeedh(jcat) + &
131  xdriv(jcat,1:nnmc(jcat)) / xspeedr(jcat)
132  WHERE ( xdgrd(jcat,1:nnmc(jcat))/=xundef .AND. xdriv(jcat,1:nnmc(jcat))/=xundef ) &
133  xtime_topd_drain(jcat,1:nnmc(jcat)) = xdgrd(jcat,1:nnmc(jcat)) / xspeedg(jcat) + &
134  xdriv(jcat,1:nnmc(jcat)) / xspeedr(jcat)
135  ELSE
136  WRITE(iluout,*) 'You have to choose some values for routing velocities'
137  ENDIF
138  !
139  IF (xtopd_step/=0.) &
140  nx_step_rout(jcat) = int(maxval(xtime_topd(jcat,1:nnmc(jcat))) / xtopd_step) + 1
141  !
142  ENDDO
143  !
144  IF ( nnb_stp_restart==0 ) nnb_stp_restart = max(nnb_topd_step,maxval(nx_step_rout(:)))
145  !
146  !
147  ALLOCATE(xqb_dr(nncat,nnb_topd_step))
148  xqb_dr(:,:)=0.0
149  ALLOCATE(xqb_run(nncat,nnb_topd_step))
150  xqb_run(:,:)=0.0
151  !
152 
153 !
154 IF (lhook) CALL dr_hook('INIT_TOPD_OL',1,zhook_handle)
155 !
156 END SUBROUTINE init_topd_ol
real, dimension(:,:), allocatable xlambda
real, dimension(jpcat) xspeedh
real, dimension(:,:), allocatable xdriv
real, dimension(:,:), allocatable xtopd
real, dimension(jpcat) xspeedr
real, dimension(:), allocatable xx0
character(len=15), dimension(jpcat) ccat
real, dimension(:,:), allocatable xslop
real, dimension(:,:), allocatable xqb_dr
real, dimension(:,:), allocatable xqb_run
real, dimension(:,:), allocatable xdmaxt
real, dimension(:,:), allocatable xdarea
integer nnb_topd_step
real, dimension(:,:), allocatable xtanb
integer, dimension(:,:), allocatable nline
real, parameter xundef
integer nmesht
integer, parameter jprb
Definition: parkind1.F90:32
real, dimension(:), allocatable xdxt
integer, parameter nundef
integer, dimension(:), allocatable nx_step_rout
real, dimension(:,:), allocatable xdhil
integer, dimension(:), allocatable nnyc
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
real, dimension(:), allocatable xnul
logical lhook
Definition: yomhook.F90:15
integer, dimension(:), allocatable nnxc
real, dimension(:), allocatable xy0
subroutine init_topd_ol(HPROGRAM)
Definition: init_topd_ol.F90:8
integer, dimension(:), allocatable nnpt
real, dimension(:,:), allocatable xtime_topd_drain
real, dimension(jpcat) xspeedg
real, dimension(:,:), allocatable xtime_topd
real, dimension(:,:,:), allocatable xconn
real, dimension(:,:), allocatable xdgrd
integer, parameter ndim
integer, dimension(:), allocatable nnmc
real, dimension(:,:), allocatable xqtot