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