SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
treat_bathyfield.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 treat_bathyfield (UG, U, USS, &
7  hprogram,hscheme,hfiletype, &
8  hsubroutine,hfilename,hncvarname, &
9  hfield, ppgdarray,hsftype )
10 ! ##############################################################
11 !
12 !!**** *TREAT_BATHYFIELD* chooses which treatment subroutine to use to read
13 !! the bathymetry
14 !!
15 !! PURPOSE
16 !! -------
17 !!
18 !! METHOD
19 !! ------
20 !!
21 !! EXTERNAL
22 !! --------
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !! REFERENCE
28 !! ---------
29 !!
30 !! AUTHOR
31 !! ------
32 !!
33 !! C. Lebeaupin Brossier Meteo-France
34 !!
35 !! MODIFICATION
36 !! ------------
37 !!
38 !! Original 01/2008
39 !!
40 !----------------------------------------------------------------------------
41 !
42 !* 0. DECLARATION
43 ! -----------
44 !
45 !
46 !
47 !
49 USE modd_surf_atm_n, ONLY : surf_atm_t
51 !
52 USE modi_get_luout
53 USE modi_read_direct
54 USE modi_read_binllv
55 USE modi_read_binllvfast
56 USE modi_read_ascllv
57 USE modi_read_netcdf
58 USE modi_average2_mesh
59 !
60 !
61 !
62 USE yomhook ,ONLY : lhook, dr_hook
63 USE parkind1 ,ONLY : jprb
64 !
65 USE modi_abor1_sfx
66 !
67 USE modi_average2_cover
68 !
69 USE modi_average2_orography
70 !
71 USE modi_read_direct_gauss
72 IMPLICIT NONE
73 !
74 !* 0.1 Declaration of arguments
75 ! ------------------------
76 !
77 !
78 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
79 TYPE(surf_atm_t), INTENT(INOUT) :: u
80 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
81 !
82  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
83  CHARACTER(LEN=6), INTENT(IN) :: hscheme ! Scheme treated
84  CHARACTER(LEN=6), INTENT(IN) :: hfiletype ! Type of the data file
85  CHARACTER(LEN=6), INTENT(IN) :: hsubroutine ! Name of the subroutine to call
86  CHARACTER(LEN=28), INTENT(IN) :: hfilename ! Name of the field file.
87  CHARACTER(LEN=28), INTENT(IN) :: hncvarname ! Name of the variable in netcdf file
88  CHARACTER(LEN=20), INTENT(IN) :: hfield ! Name of the field.
89 REAL, DIMENSION(:), INTENT(INOUT), OPTIONAL :: ppgdarray ! field on MESONH grid
90  CHARACTER(LEN=3), INTENT(IN), OPTIONAL :: hsftype
91 !
92 !* 0.2 Declaration of local variables
93 ! ------------------------------
94 !
95 INTEGER :: iluout
96 REAL(KIND=JPRB) :: zhook_handle
97 !-------------------------------------------------------------------------------
98 !
99 IF (lhook) CALL dr_hook('TREAT_BATHYFIELD',0,zhook_handle)
100  CALL get_luout(hprogram,iluout)
101 !
102 !* 1. Selection of type of reading (and point by point treatment)
103 ! -----------------------------------------------------------
104 !
105 SELECT CASE (hfiletype)
106 
107  CASE ('DIRECT')
108  IF(ug%CGRID=="GAUSS ")THEN
109  CALL read_direct_gauss(uss, &
110  hprogram,hscheme,hsubroutine,hfilename,hfield)
111  ELSE
112  CALL read_direct(uss, &
113  hprogram,hscheme,hsubroutine,hfilename,hfield)
114  ENDIF
115  CASE ('BINLLV')
116  CALL read_binllv(uss, &
117  hprogram,hsubroutine,hfilename)
118 
119  CASE ('BINLLF')
120  CALL read_binllvfast(uss, &
121  hprogram,hsubroutine,hfilename)
122 
123  CASE ('ASCLLV')
124  CALL read_ascllv(uss, &
125  hprogram,hsubroutine,hfilename)
126 
127  CASE ('NETCDF')
128  CALL read_netcdf(uss, &
129  hprogram,hsubroutine,hfilename,hncvarname)
130 
131 END SELECT
132 !
133 !-------------------------------------------------------------------------------
134 !
135 !* 2. Call to the adequate subroutine (global treatment)
136 ! --------------------------------------------------
137 !
138 SELECT CASE (hsubroutine)
139 
140  CASE ('A_COVR')
141  CALL average2_cover(u, &
142  hprogram)
143 
144  CASE ('A_OROG')
145  CALL average2_orography(uss)
146 
147  CASE ('A_MESH')
148  IF (.NOT. present(ppgdarray)) THEN
149  WRITE(iluout,*) 'You asked to average a PGD field with A_MESH option,'
150  WRITE(iluout,*) 'but you did not give the array to store this field'
151  CALL abor1_sfx('TREAT_BATHYFIELD: PGD ARRAY IS MISSING')
152  END IF
153  CALL average2_mesh(ppgdarray)
154 
155 END SELECT
156 IF (lhook) CALL dr_hook('TREAT_BATHYFIELD',1,zhook_handle)
157 !-------------------------------------------------------------------------------
158 !
159 END SUBROUTINE treat_bathyfield
subroutine read_netcdf(USS, HPROGRAM, HSUBROUTINE, HFILENAME, HNCVARNAME)
Definition: read_netcdf.F90:6
subroutine average2_cover(U, HPROGRAM)
subroutine read_direct(USS, HPROGRAM, HSCHEME, HSUBROUTINE, HFILENAME, HFIELD)
Definition: read_direct.F90:6
subroutine read_ascllv(USS, HPROGRAM, HSUBROUTINE, HFILENAME)
Definition: read_ascllv.F90:6
subroutine average2_orography(USS)
subroutine read_binllv(USS, HPROGRAM, HSUBROUTINE, HFILENAME)
Definition: read_binllv.F90:6
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine read_binllvfast(USS, HPROGRAM, HSUBROUTINE, HFILENAME)
subroutine average2_mesh(PPGDARRAY)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine treat_bathyfield(UG, U, USS, HPROGRAM, HSCHEME, HFILETYPE, HSUBROUTINE, HFILENAME, HNCVARNAME, HFIELD, PPGDARRAY, HSFTYPE)
subroutine read_direct_gauss(USS, HPROGRAM, HSCHEME, HSUBROUTINE, HFILENAME, HFIELD)