SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
put_zs_inland_watern.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 put_zs_inland_water_n (F, W, &
7  hprogram,ki,pzs,hwater)
8 ! #################################################
9 !
10 !!**** *PUT_ZS_INLAND_WATER_n* - routine to modify inland water oropgraphy using atmospheric
11 ! model orography
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !!** METHOD
17 !! ------
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !!
30 !! AUTHOR
31 !! ------
32 !! P. Le Moigne *Meteo France*
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 05/2007
37 !-------------------------------------------------------------------------------
38 !
39 !* 0. DECLARATIONS
40 ! ------------
41 !
42 !
43 USE modd_flake_n, ONLY : flake_t
44 USE modd_watflux_n, ONLY : watflux_t
45 !
46 USE modi_get_luout
47 !
48 !
49 USE yomhook ,ONLY : lhook, dr_hook
50 USE parkind1 ,ONLY : jprb
51 !
52 USE modi_abor1_sfx
53 !
54 IMPLICIT NONE
55 !
56 !* 0.1 Declarations of arguments
57 ! -------------------------
58 !
59 !
60 TYPE(flake_t), INTENT(INOUT) :: f
61 TYPE(watflux_t), INTENT(INOUT) :: w
62 !
63  CHARACTER(LEN=6), INTENT(IN) :: hwater ! name of the scheme for inland water
64  CHARACTER(LEN=6), INTENT(IN) :: hprogram
65 INTEGER, INTENT(IN) :: ki ! horizontal dim. of cover
66 REAL, DIMENSION(KI), INTENT(IN) :: pzs ! orography
67 !
68 !
69 !* 0.2 Declarations of local variables
70 ! -------------------------------
71 !
72 INTEGER :: iluout
73 REAL(KIND=JPRB) :: zhook_handle
74 !
75 IF (lhook) CALL dr_hook('PUT_ZS_INLAND_WATER_N',0,zhook_handle)
76 IF (hwater=='FLAKE ') THEN
77  CALL put_zs_flake_n
78 ELSE
79  CALL put_zs_watflx_n
80 END IF
81 !
82 IF (lhook) CALL dr_hook('PUT_ZS_INLAND_WATER_N',1,zhook_handle)
83  CONTAINS
84 !
85 !------------------------------------------------------------------------------
86 !------------------------------------------------------------------------------
87 !
88 SUBROUTINE put_zs_watflx_n
89 !
90 !
91 !-------------------------------------------------------------------------------
92 
93 REAL(KIND=JPRB) :: zhook_handle
94 
95 IF (lhook) CALL dr_hook('PUT_ZS_WATFLX_N',0,zhook_handle)
96  CALL get_luout(hprogram,iluout)
97 !-------------------------------------------------------------------------------
98 !
99 IF ( SIZE(pzs) /= SIZE(w%XZS) ) THEN
100  WRITE(iluout,*) 'try to get ZS field from atmospheric model, but size is not correct'
101  WRITE(iluout,*) 'size of field expected by the atmospheric model (PZS) :', SIZE(pzs)
102  WRITE(iluout,*) 'size of field for inland water (WATFLX) (XZS) :', SIZE(w%XZS)
103  CALL abor1_sfx('PUT_ZS_INLAND_WATERN (WATFLX): GET ZS FROM ATMOSPHERIC MODEL: SIZE NOT CORRECT')
104 ELSE
105  w%XZS = pzs
106 END IF
107 IF (lhook) CALL dr_hook('PUT_ZS_WATFLX_N',1,zhook_handle)
108 !
109 END SUBROUTINE put_zs_watflx_n
110 !
111 !------------------------------------------------------------------------------
112 !------------------------------------------------------------------------------
113 !
114 SUBROUTINE put_zs_flake_n
115 !
116 !
117 !-------------------------------------------------------------------------------
118 
119 REAL(KIND=JPRB) :: zhook_handle
120 
121 IF (lhook) CALL dr_hook('PUT_ZS_FLAKE_N',0,zhook_handle)
122  CALL get_luout(hprogram,iluout)
123 !-------------------------------------------------------------------------------
124 !
125 IF ( SIZE(pzs) /= SIZE(f%XZS) ) THEN
126  WRITE(iluout,*) 'try to get ZS field from atmospheric model, but size is not correct'
127  WRITE(iluout,*) 'size of field expected by the atmospheric model (PZS) :', SIZE(pzs)
128  WRITE(iluout,*) 'size of field for inland water (FLAKE) (XZS) :', SIZE(f%XZS)
129  CALL abor1_sfx('PUT_ZS_INLAND_WATERN (FLAKE): GET ZS FROM ATMOSPHERIC MODEL: SIZE NOT CORRECT')
130 ELSE
131  f%XZS = pzs
132 END IF
133 IF (lhook) CALL dr_hook('PUT_ZS_FLAKE_N',1,zhook_handle)
134 !
135 END SUBROUTINE put_zs_flake_n
136 !==============================================================================
137 !
138 END SUBROUTINE put_zs_inland_water_n
subroutine put_zs_inland_water_n(F, W, HPROGRAM, KI, PZS, HWATER)
subroutine put_zs_flake_n
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine put_zs_watflx_n
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6