SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_slope_file.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 read_slope_file(HPROGRAM,HFILE,HFORM,KNMC,PTANB,PSLOP,PDAREA,PLAMBDA)
8 ! #######################
9 !
10 !!**** *READ_SLOPE_FILE*
11 !!
12 !! PURPOSE
13 !! -------
14 ! This routine aims at reading topographic files
15 !!** METHOD
16 !! ------
17 !
18 !! EXTERNAL
19 !! --------
20 !!
21 !! none
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !!
27 !!
28 !!
29 !!
30 !! REFERENCE
31 !! ---------
32 !!
33 !!
34 !!
35 !! AUTHOR
36 !! ------
37 !!
38 !! B. Vincendon * Meteo-France *
39 !!
40 !! MODIFICATIONS
41 !! -------------
42 !!
43 !! Original 11/2006
44 !! 03/2014 (B. Vincendon) add the possibility of reading topographic
45 !! files produced by a new chain (based of java+GRASS)
46 !-------------------------------------------------------------------------------
47 !
48 !* 0. DECLARATIONS
49 ! ------------
50 !
51 USE modi_get_luout
52 USE modi_open_file
53 USE modi_close_file
54 !
55 USE modd_topd_par, ONLY : nunit
56 USE modd_topodyn, ONLY : npmax
57 USE modd_surf_par, ONLY : xundef
58 !
59 USE yomhook ,ONLY : lhook, dr_hook
60 USE parkind1 ,ONLY : jprb
61 !
62 IMPLICIT NONE
63 !
64 !* 0.1 declarations of arguments
65 !
66  CHARACTER(LEN=*), INTENT(IN) :: hprogram !
67  CHARACTER(LEN=*), INTENT(IN) :: hfile ! File to be read
68  CHARACTER(LEN=*), INTENT(IN) :: hform ! Format of the file to be read
69 INTEGER, INTENT(IN) :: knmc ! Number of pixels in the catchment
70 REAL, DIMENSION(:), INTENT(OUT) :: ptanb ! pixels topographic slope(tan(beta)
71 REAL, DIMENSION(:), INTENT(OUT) :: pslop ! pixels topographic slope/length flow
72 REAL, DIMENSION(:), INTENT(OUT) :: pdarea ! drainage area (aire drainee)
73 REAL, DIMENSION(:), INTENT(OUT) :: plambda ! pure topographic index
74 !
75 !* 0.2 declarations of local variables
76 !
77 !
78 INTEGER :: jj ! loop control
79 INTEGER :: iwrk ! work variable
80 INTEGER :: iluout ! Unit of the files
81 !
82 REAL :: zwrk ! work variable
83 REAL, DIMENSION(KNMC) :: zdarea ! drainage area (aire drainee)
84 REAL(KIND=JPRB) :: zhook_handle
85 !
86  CHARACTER(LEN=100) :: yheader ! Header File to be read
87 !------------------------------------------------------------------------------
88 IF (lhook) CALL dr_hook('READ_SLOPE_FILE',0,zhook_handle)
89 !
90 !* 0.2 preparing file openning
91 ! ----------------------
92  CALL get_luout(hprogram,iluout)
93 !
94  CALL open_file(hprogram,nunit,hfile,hform,haction='READ')
95 !
96 READ(nunit,*) yheader
97 !
98 IF (index(yheader,'pixel_REF')/=0) THEN !Slope file from new java+GRASS chain
99  write(iluout,*) 'Slope file from new java + GRASS chain'
100  DO jj=1,knmc
101  READ(nunit,*,end=110) iwrk, ptanb(jj),plambda(jj)
102  ENDDO
103  pslop(:)=plambda(:) !not used
104  pdarea(:)=plambda(:) !not used
105 ELSE !slope file from old f77 chain
106  write(*,*) 'Slope file from old f77 chain'
107  DO jj=1,knmc
108  READ(nunit,*,end=110) iwrk, ptanb(jj), pslop(jj), zwrk, pdarea(jj)
109  plambda(jj) = log(pdarea(jj)/pslop(jj))
110  ENDDO
111 ENDIF
112 110 CALL close_file(hprogram,nunit)
113 !
114 IF (lhook) CALL dr_hook('READ_SLOPE_FILE',1,zhook_handle)
115 !
116 END SUBROUTINE read_slope_file
117 
118 
119 
120 
121 
122 
123 
subroutine read_slope_file(HPROGRAM, HFILE, HFORM, KNMC, PTANB, PSLOP, PDAREA, PLAMBDA)
subroutine close_file(HPROGRAM, KUNIT)
Definition: close_file.F90:6
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine open_file(HPROGRAM, KUNIT, HFILE, HFORM, HACTION, HACCESS, KRECL)
Definition: open_file.F90:6