SURFEX v8.1
General documentation of Surfex
writesurf_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 writesurf_sso_canopy_n (HSELECT,SB,HPROGRAM,OWRITE)
7 ! ####################################
8 !
9 !!**** *WRITE_SSO_n* - writes SSO fields
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !!** METHOD
15 !! ------
16 !!
17 !! EXTERNAL
18 !! --------
19 !!
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !!
28 !! AUTHOR
29 !! ------
30 !! V. Masson *Meteo France*
31 !!
32 !! MODIFICATIONS
33 !! -------------
34 !! Original 01/2003
35 !! E. Martin 01/2012 avoid write of XUNDEF fields
36 !-------------------------------------------------------------------------------
37 !
38 !* 0. DECLARATIONS
39 ! ------------
40 !
41 !
42 !
43 !
44 !
45 !
46 !
47 USE modd_diag_n, ONLY : diag_options_t
48 USE modd_surf_atm_n, ONLY : surf_atm_t
49 !
50 USE modd_canopy_n, ONLY : canopy_t
51 !
53 !
54 USE yomhook ,ONLY : lhook, dr_hook
55 USE parkind1 ,ONLY : jprb
56 !
57 IMPLICIT NONE
58 !
59 !* 0.1 Declarations of arguments
60 ! -------------------------
61 !
62 !
63 !
64  CHARACTER(LEN=*), DIMENSION(:), INTENT(IN) :: HSELECT
65 !
66 TYPE(canopy_t), INTENT(INOUT) :: SB
67 !
68  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling
69 LOGICAL, INTENT(IN) :: OWRITE ! flag to write canopy terms
70 !
71 !* 0.2 Declarations of local variables
72 ! -------------------------------
73 !
74 INTEGER :: IRESP ! IRESP : return-code if a problem appears
75  CHARACTER(LEN=12) :: YRECFM ! Name of the article to be read
76  CHARACTER(LEN=100):: YCOMMENT ! Comment string
77 !
78 INTEGER :: JLAYER ! loop counter on layers
79 REAL(KIND=JPRB) :: ZHOOK_HANDLE
80 !-------------------------------------------------------------------------------
81 !
82 !* 1. Prognostic fields:
83 ! -----------------
84 !
85 !
86 !* flag to define if canopy is computed
87 !
88 IF (lhook) CALL dr_hook('WRITESURF_SSO_CANOPY_N',0,zhook_handle)
89 yrecfm='SSO_CANOPY'
90 ycomment='flag to use canopy levels'
91  CALL write_surf(hselect,hprogram,yrecfm,owrite,iresp,hcomment=ycomment)
92 !
93 IF (.NOT. owrite .AND. lhook) CALL dr_hook('WRITESURF_SSO_CANOPY_N',1,zhook_handle)
94 IF (.NOT. owrite) RETURN
95 !
96 !* number of levels
97 !
98 yrecfm='SSO_CAN_LVL'
99 ycomment='number of canopy levels'
100  CALL write_surf(hselect,hprogram,yrecfm,sb%NLVL,iresp,hcomment=ycomment)
101 !
102 !* altitudes
103 !
104 DO jlayer=1,sb%NLVL
105  WRITE(yrecfm,'(A9,I2.2,A1)') 'SSO_CAN_Z',jlayer,' '
106  ycomment='altitudes of canopy levels (m)'
107  CALL write_surf(hselect,hprogram,yrecfm,sb%XZ(:,jlayer),iresp,hcomment=ycomment)
108 END DO
109 !
110 !* wind in canopy
111 !
112 DO jlayer=1,sb%NLVL
113  WRITE(yrecfm,'(A9,I2.2,A1)') 'SSO_CAN_U',jlayer,' '
114  ycomment='wind at canopy levels (m/s)'
115  CALL write_surf(hselect,hprogram,yrecfm,sb%XU(:,jlayer),iresp,hcomment=ycomment)
116 END DO
117 !
118 !* Tke in canopy
119 !
120 DO jlayer=1,sb%NLVL
121  WRITE(yrecfm,'(A9,I2.2,A1)') 'SSO_CAN_E',jlayer,' '
122  ycomment='Tke at canopy levels (m2/s2)'
123  CALL write_surf(hselect,hprogram,yrecfm,sb%XTKE(:,jlayer),iresp,hcomment=ycomment)
124 END DO
125 !
126 IF (lhook) CALL dr_hook('WRITESURF_SSO_CANOPY_N',1,zhook_handle)
127 !
128 !-------------------------------------------------------------------------------
129 !
130 END SUBROUTINE writesurf_sso_canopy_n
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine writesurf_sso_canopy_n(HSELECT, SB, HPROGRAM, OWRITE)