SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
treat_field.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_field (UG, U, USS, &
7  hprogram,hscheme,hfiletype, &
8  hsubroutine,hfilename,hfield, &
9  ppgdarray,hsftype )
10 ! ##############################################################
11 !
12 !!**** *TREAT_FIELD* chooses which treatment subroutine to use
13 !!
14 !! PURPOSE
15 !! -------
16 !!
17 !! METHOD
18 !! ------
19 !!
20 !! EXTERNAL
21 !! --------
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !! AUTHOR
30 !! ------
31 !!
32 !! V. Masson Meteo-France
33 !!
34 !! MODIFICATION
35 !! ------------
36 !!
37 !! Original 11/09/95
38 !!
39 !! Modification
40 !! 25/05/96 (V. Masson) remove useless case for HSUBROUTINE
41 !! 29/11/2002 (D. Gazen) add HSFTYPE argument + call to read_binllvfast routine
42 !! 03/2004 (V. MAsson) externalization
43 !! 04/2009 (B. Decharme) Special treatement for gaussian grid
44 !! 06/2009 (B. Decharme) call Topographic index statistics calculation
45 !! 09/2010 (E. Kourzeneva) call reading of the lake database
46 !! 03/2012 (M. Lafaysse) NETCDF
47 !----------------------------------------------------------------------------
48 !
49 !* 0. DECLARATION
50 ! -----------
51 !
52 !
53 !
54 !
56 USE modd_surf_atm_n, ONLY : surf_atm_t
58 !
59 USE modi_get_luout
60 USE modi_read_direct
61 USE modi_read_direct_gauss
62 USE modi_read_latlon
63 USE modi_read_binllv
64 USE modi_read_binllvfast
65 USE modi_read_ascllv
66 
67 USE modi_read_pgd_netcdf
68 
69 USE modi_average2_mesh
70 !
71 !
72 !
73 USE yomhook ,ONLY : lhook, dr_hook
74 USE parkind1 ,ONLY : jprb
75 !
76 USE modi_abor1_sfx
77 !
78 USE modi_average2_cover
79 !
80 USE modi_average2_cti
81 USE modi_average2_ldb
82 !
83 USE modi_average2_orography
84 !
85 IMPLICIT NONE
86 !
87 !* 0.1 Declaration of arguments
88 ! ------------------------
89 !
90 !
91 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
92 TYPE(surf_atm_t), INTENT(INOUT) :: u
93 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
94 !
95  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
96  CHARACTER(LEN=6), INTENT(IN) :: hscheme ! Scheme treated
97  CHARACTER(LEN=6), INTENT(IN) :: hfiletype ! Type of the data file
98  CHARACTER(LEN=6), INTENT(IN) :: hsubroutine ! Name of the subroutine to call
99  CHARACTER(LEN=28), INTENT(IN) :: hfilename ! Name of the field file.
100  CHARACTER(LEN=20), INTENT(IN) :: hfield ! Name of the field.
101 REAL, DIMENSION(:), INTENT(INOUT), OPTIONAL :: ppgdarray ! field on MESONH grid
102  CHARACTER(LEN=3), INTENT(IN), OPTIONAL :: hsftype
103 !
104 !* 0.2 Declaration of local variables
105 ! ------------------------------
106 !
107 INTEGER :: iluout
108 REAL(KIND=JPRB) :: zhook_handle
109 !-------------------------------------------------------------------------------
110 !
111 IF (lhook) CALL dr_hook('TREAT_FIELD',0,zhook_handle)
112  CALL get_luout(hprogram,iluout)
113 !
114 !* 1. Selection of type of reading (and point by point treatment)
115 ! -----------------------------------------------------------
116 !
117 SELECT CASE (hfiletype)
118 
119  CASE ('DIRECT')
120  IF(ug%CGRID=="GAUSS " .OR. ug%CGRID=="IGN " .OR. ug%CGRID=="LONLAT REG")THEN
121  CALL read_direct_gauss(uss, &
122  hprogram,hscheme,hsubroutine,hfilename,hfield)
123  ELSE
124  CALL read_direct(uss, &
125  hprogram,hscheme,hsubroutine,hfilename,hfield)
126  ENDIF
127 
128  CASE ('BINLLV')
129  CALL read_binllv(uss, &
130  hprogram,hsubroutine,hfilename)
131 
132  CASE ('BINLLF')
133  CALL read_binllvfast(uss, &
134  hprogram,hsubroutine,hfilename)
135 
136  CASE ('ASCLLV')
137  CALL read_ascllv(uss, &
138  hprogram,hsubroutine,hfilename)
139 
140  CASE ('LATLON')
141  CALL read_latlon(uss, &
142  hprogram,hscheme,hsubroutine,hfilename)
143 
144  CASE ('NETCDF')
145  CALL read_pgd_netcdf(uss, &
146  hprogram,hscheme,hsubroutine,hfilename,hfield)
147 
148  CASE default
149  CALL abor1_sfx('TREAT_FIELD: FILE TYPE NOT SUPPORTED: '//hfiletype)
150 
151 END SELECT
152 !
153 !-------------------------------------------------------------------------------
154 !
155 !* 2. Call to the adequate subroutine (global treatment)
156 ! --------------------------------------------------
157 !
158 SELECT CASE (hsubroutine)
159 
160  CASE ('A_COVR')
161  CALL average2_cover(u, &
162  hprogram)
163 
164  CASE ('A_OROG')
165  CALL average2_orography(uss)
166 
167  CASE ('A_CTI ')
168  CALL average2_cti
169 
170  CASE ('A_LDBD')
171  CALL average2_ldb(ppgdarray,'D',1)
172 
173  CASE ('A_LDBS')
174  CALL average2_ldb(ppgdarray,'S',1)
175 
176  CASE ('A_MESH')
177  IF (.NOT. present(ppgdarray)) THEN
178  WRITE(iluout,*) 'You asked to average a PGD field with A_MESH option,'
179  WRITE(iluout,*) 'but you did not give the array to store this field'
180  CALL abor1_sfx('TREAT_FIELD: ARRAY IS MISSING')
181  END IF
182  CALL average2_mesh(ppgdarray)
183 
184 END SELECT
185 !
186 IF (lhook) CALL dr_hook('TREAT_FIELD',1,zhook_handle)
187 !-------------------------------------------------------------------------------
188 !
189 END SUBROUTINE treat_field
subroutine average2_cover(U, HPROGRAM)
subroutine read_latlon(USS, HPROGRAM, HSCHEME, HSUBROUTINE, HFILENAME)
Definition: read_latlon.F90:6
subroutine read_direct(USS, HPROGRAM, HSCHEME, HSUBROUTINE, HFILENAME, HFIELD)
Definition: read_direct.F90:6
subroutine average2_ldb(PPGDARRAY, HTYPE, KSTAT)
Definition: average2_ldb.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 treat_field(UG, U, USS, HPROGRAM, HSCHEME, HFILETYPE, HSUBROUTINE, HFILENAME, HFIELD, PPGDARRAY, HSFTYPE)
Definition: treat_field.F90:6
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine read_binllvfast(USS, HPROGRAM, HSUBROUTINE, HFILENAME)
subroutine average2_cti
Definition: average2_cti.F90:6
subroutine average2_mesh(PPGDARRAY)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine read_pgd_netcdf(USS, HPROGRAM, HSCHEME, HSUBROUTINE, HFILENAME, HFIELD, PFIELD)
subroutine read_direct_gauss(USS, HPROGRAM, HSCHEME, HSUBROUTINE, HFILENAME, HFIELD)