SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
compare_orography.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 compare_orography (YSC, &
7  hprogram, osurfzs, pdelt_zsmax )
8 !**************************************************************************
9 !
10 !! PURPOSE
11 !! -------
12 !! Check consistency orographies read from forcing file and from initial file
13 !!
14 !!** METHOD
15 !! ------
16 !!
17 !! EXTERNAL
18 !! --------
19 !!
20 !! IMPLICIT ARGUMENTS
21 !! ------------------
22 !!
23 !! REFERENCE
24 !! ---------
25 !!
26 !!
27 !! AUTHOR
28 !! ------
29 !! P. Le Moigne *Meteo France*
30 !!
31 !
32 USE modd_surfex_n, ONLY : surfex_t
33 !
34 USE modi_init_io_surf_n
36 USE modi_end_io_surf_n
37 USE modi_get_luout
38 USE modd_surf_par, ONLY : xundef
39 USE modd_forc_atm, ONLY : xzs
40 USE modd_surf_conf, ONLY : cprogname
41 !
42 USE modi_set_surfex_filein
43 !
44 USE yomhook ,ONLY : lhook, dr_hook
45 USE parkind1 ,ONLY : jprb
46 !
47 USE modi_abor1_sfx
48 !
49 IMPLICIT NONE
50 !
51 ! global variables
52 !
53 TYPE(surfex_t), INTENT(INOUT) :: ysc
54 !
55  CHARACTER(LEN=6) ,INTENT(IN) :: hprogram
56 REAL ,INTENT(IN) :: pdelt_zsmax
57 LOGICAL ,INTENT(IN) :: osurfzs
58 
59 ! local variables
60 INTEGER :: iluout
61 INTEGER :: iret
62 REAL, DIMENSION(SIZE(XZS,1)) :: zs1 ! orography read from FORCING.nc
63 REAL(KIND=JPRB) :: zhook_handle
64 !
65 IF (lhook) CALL dr_hook('COMPARE_OROGRAPHY',0,zhook_handle)
66  cprogname = hprogram
67 !
68 ! read orography
69 !
70 ! orography from initial file
71  CALL set_surfex_filein(hprogram,'PGD ') ! change input file name to pgd name
72  CALL init_io_surf_n(ysc%DTCO, ysc%DGU, ysc%U, &
73  hprogram,'FULL ','SURF ','READ ')
74  CALL read_surf(&
75  hprogram,'ZS', zs1, iret)
76  CALL end_io_surf_n(hprogram)
77  CALL set_surfex_filein(hprogram,'PREP') ! restore input file name
78 !
79 IF (osurfzs) THEN
80  CALL get_luout('ASCII ',iluout)
81  WRITE(iluout,*)' OROGRAPHY READ FROM INITIAL FILE'
82  xzs(:) = zs1(:)
83 ELSEIF (maxval(abs(xzs(:)-zs1(:))) > pdelt_zsmax) THEN
84  CALL get_luout('ASCII ',iluout)
85  WRITE(iluout,*)' DIFFERENCE OF OROGRAPHY TOO BIG BETWEEN FORCING AND INITIAL FILE'
86  WRITE(iluout,*)' Maximum orography difference allowed (m) : ', pdelt_zsmax
87  WRITE(iluout,*)' Maximum orography difference (m) : ', maxval(abs(xzs(:)-zs1(:)))
88  CALL abor1_sfx('COMPARE_OROGRAPHY: DIFFERENCE OF OROGRAPHY TOO BIG BETWEEN FORCING AND INITIAL FILE')
89 ENDIF
90 !
91 IF (lhook) CALL dr_hook('COMPARE_OROGRAPHY',1,zhook_handle)
92 !
93 END SUBROUTINE compare_orography
subroutine init_io_surf_n(DTCO, DGU, U, HPROGRAM, HMASK, HSCHEME, HACTION)
subroutine set_surfex_filein(HPROGRAM, HMASK)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine end_io_surf_n(HPROGRAM)
Definition: end_io_surfn.F90:6
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine compare_orography(YSC, HPROGRAM, OSURFZS, PDELT_ZSMAX)