SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_sso_canopyn.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 read_sso_canopy_n (DTCO, SSCP, U, &
7  hprogram,hinit)
8 ! #########################################
9 !
10 !!**** *READ_SSO_CANOPY_n* - reads SSO fields
11 !!
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 !! V. Masson *Meteo France*
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 05/2010
37 !! B. Decharme 07/2011 initialize sso_canopy in prep
38 !! E. Martin 01/2012 Avoid writing of XUNDEF canopy fields
39 !-------------------------------------------------------------------------------
40 !
41 !* 0. DECLARATIONS
42 ! ------------
43 !
44 !
45 !
46 !
49 USE modd_surf_atm_n, ONLY : surf_atm_t
50 !
51 USE modd_surf_par, ONLY : xundef
52 !
54 USE modi_set_sso_levels
55 USE modi_canopy_grid
56 USE modi_get_type_dim_n
57 !
58 USE yomhook ,ONLY : lhook, dr_hook
59 USE parkind1 ,ONLY : jprb
60 !
61 IMPLICIT NONE
62 !
63 !* 0.1 Declarations of arguments
64 ! -------------------------
65 !
66 !
67 TYPE(data_cover_t), INTENT(INOUT) :: dtco
68 TYPE(sso_canopy_t), INTENT(INOUT) :: sscp
69 TYPE(surf_atm_t), INTENT(INOUT) :: u
70 !
71  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! calling program
72  CHARACTER(LEN=3), INTENT(IN) :: hinit ! choice of fields to initialize
73 !
74 !* 0.2 Declarations of local variables
75 ! -------------------------------
76 !
77  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
78  CHARACTER(LEN=3) :: yread
79 INTEGER :: ilu ! 1D physical dimension
80 INTEGER :: iresp ! Error code after redding
81 INTEGER :: jlayer ! loop counter on layers
82 INTEGER :: iversion, ibugfix ! surface version
83 LOGICAL :: gcanopy ! flag to test if SSO canopy fields are in the file
84 REAL(KIND=JPRB) :: zhook_handle
85 !-------------------------------------------------------------------------------
86 !
87 !* 1D physical dimension
88 !
89 IF (lhook) CALL dr_hook('READ_SSO_CANOPY_N',0,zhook_handle)
90  CALL get_type_dim_n(dtco, u, &
91  'FULL ',ilu)
92 !
93 !* flag to use or not canopy levels
94 !
95 yrecfm='VERSION'
96  CALL read_surf(&
97  hprogram,yrecfm,iversion,iresp)
98 !
99 yrecfm='BUG'
100  CALL read_surf(&
101  hprogram,yrecfm,ibugfix,iresp)
102 !
103 IF (iversion<6.OR.hinit=='PGD'.OR. hinit=='PRE') THEN
104  gcanopy = .false.
105 ELSE
106  IF (iversion>7 .OR. iversion==7 .AND.ibugfix>=2) THEN
107  yrecfm='STORAGETYPE'
108  CALL read_surf(&
109  hprogram,yrecfm,yread,iresp)
110  ELSE
111  yread = 'ALL'
112  ENDIF
113  IF (yread/='ALL') THEN
114  gcanopy = .false.
115  ELSE
116  yrecfm='SSO_CANOPY'
117  CALL read_surf(&
118  hprogram,yrecfm,gcanopy,iresp)
119  ENDIF
120 END IF
121 !
122 !* 2. Allocation of Prognostic fields:
123 ! --------------------------------
124 !
125 !* number of vertical levels
126 !
127 IF (.NOT. gcanopy) THEN
128  CALL set_sso_levels(sscp, &
129  ilu)
130 ELSE
131  !
132  yrecfm='SSO_CAN_LVL'
133  CALL read_surf(&
134  hprogram,yrecfm,sscp%NLVL,iresp)
135  !
136  !
137  !* 3. Reading of Prognostic fields:
138  ! -----------------------------
139  !
140  ALLOCATE(sscp%XZ(ilu,sscp%NLVL))
141  ALLOCATE(sscp%XU(ilu,sscp%NLVL))
142  ALLOCATE(sscp%XTKE(ilu,sscp%NLVL))
143  !
144  !* altitudes
145  DO jlayer=1,sscp%NLVL
146  WRITE(yrecfm,'(A9,I2.2,A1)') 'SSO_CAN_Z',jlayer,' '
147  CALL read_surf(&
148  hprogram,yrecfm,sscp%XZ(:,jlayer),iresp)
149  END DO
150  !
151  !* wind in canopy
152  DO jlayer=1,sscp%NLVL
153  WRITE(yrecfm,'(A9,I2.2,A1)') 'SSO_CAN_U',jlayer,' '
154  CALL read_surf(&
155  hprogram,yrecfm,sscp%XU(:,jlayer),iresp)
156  END DO
157  !
158  !* Tke in canopy
159  DO jlayer=1,sscp%NLVL
160  WRITE(yrecfm,'(A9,I2.2,A1)') 'SSO_CAN_E',jlayer,' '
161  CALL read_surf(&
162  hprogram,yrecfm,sscp%XTKE(:,jlayer),iresp)
163  END DO
164  !
165 ENDIF
166 !
167 !
168 !* Grid characteristics
169 !
170 !
171 ! --------------------------------- XZ(k+1) XDZ(k+1)
172 ! ^
173 ! |
174 ! |
175 ! - - - - - - - - - - - - - - - - - XZf(k+1) | XDZf(k+1)
176 ! ^ |
177 ! | |
178 ! --------------------------------- XZ(k), XU, XT, XQ, XTKE | XDZ(k) V
179 ! | ^
180 ! - - - - - - - - - - - - - - - - - XZf(k) V | XDZf(k)
181 ! --------------------------------- XZ(k-1) XDZ(k-1) V
182 ! - - - - - - - - - - - - - - - - - XZf(k-1)
183 !
184 ALLOCATE(sscp%XDZ (ilu,sscp%NLVL))
185 ALLOCATE(sscp%XZF (ilu,sscp%NLVL))
186 ALLOCATE(sscp%XDZF(ilu,sscp%NLVL))
187  CALL canopy_grid(ilu,sscp%NLVL,sscp%XZ,sscp%XZF,sscp%XDZ,sscp%XDZF)
188 IF (lhook) CALL dr_hook('READ_SSO_CANOPY_N',1,zhook_handle)
189 !
190 !-------------------------------------------------------------------------------
191 !
192 END SUBROUTINE read_sso_canopy_n
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
subroutine read_sso_canopy_n(DTCO, SSCP, U, HPROGRAM, HINIT)
subroutine set_sso_levels(SSCP, KDIM)
subroutine canopy_grid(KI, KLVL, PZ, PZF, PDZ, PDZF)
Definition: canopy_grid.F90:6