SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
writesurf_seafluxn.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_seaflux_n (DGU, U, &
7  o, or, s, &
8  hprogram)
9 ! ########################################
10 !
11 !!**** *WRITE_SEAFLUX_n* - writes SEAFLUX fields
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 01/2003
37 !! Modified 01/2014 : S. Senesi : handle seaice scheme
38 !! S. Belamari 03/2014 Include sea surface salinity XSSS
39 !! R. Séférian 01/2015 : introduce interactive ocean surface albedo
40 !-------------------------------------------------------------------------------
41 !
42 !* 0. DECLARATIONS
43 ! ------------
44 !
45 !
46 !
47 !
48 !
49 !
51 USE modd_surf_atm_n, ONLY : surf_atm_t
52 !
53 USE modd_ocean_n, ONLY : ocean_t
54 USE modd_ocean_rel_n, ONLY : ocean_rel_t
55 USE modd_seaflux_n, ONLY : seaflux_t
56 !
58 USE modi_writesurf_ocean_n
59 USE modi_writesurf_seaice_n
60 !
61 USE yomhook ,ONLY : lhook, dr_hook
62 USE parkind1 ,ONLY : jprb
63 !
64 IMPLICIT NONE
65 !
66 !* 0.1 Declarations of arguments
67 ! -------------------------
68 !
69 !
70 !
71 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
72 TYPE(surf_atm_t), INTENT(INOUT) :: u
73 !
74 TYPE(ocean_t), INTENT(INOUT) :: o
75 TYPE(ocean_rel_t), INTENT(INOUT) :: or
76 TYPE(seaflux_t), INTENT(INOUT) :: s
77 !
78  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
79 
80 !
81 !* 0.2 Declarations of local variables
82 ! -------------------------------
83 !
84 INTEGER :: jmth, inmth
85  CHARACTER(LEN=2 ) :: ymth
86 !
87 INTEGER :: iresp ! IRESP : return-code if a problem appears
88  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
89  CHARACTER(LEN=100):: ycomment ! Comment string
90 REAL(KIND=JPRB) :: zhook_handle
91 !
92 !-------------------------------------------------------------------------------
93 !
94 !
95 IF (lhook) CALL dr_hook('WRITESURF_SEAFLUX_N',0,zhook_handle)
96 !
97  CALL writesurf_ocean_n(dgu, u, &
98  o, or, &
99  hprogram)
100 !
101 !* 2. Sea-ice prognostic fields:
102 ! --------------------------
103 !
104 !* flag to tell if Sea Ice model is used
105 !
106 ycomment='flag to handle sea ice cover'
107  CALL write_surf(dgu, u, &
108  hprogram,'HANDLE_SIC',s%LHANDLE_SIC,iresp,ycomment)
109 !
110 IF (s%LHANDLE_SIC) CALL writesurf_seaice_n(dgu, u, &
111  s, &
112  hprogram)
113 !
114 !
115 !* 3. Prognostic fields:
116 ! -----------------
117 !
118 !* water temperature
119 !
120 IF(s%LINTERPOL_SST)THEN
121 !
122  inmth=SIZE(s%XSST_MTH,2)
123 !
124  DO jmth=1,inmth
125  WRITE(ymth,'(I2)') (jmth-1)
126  yrecfm='SST_MTH'//adjustl(ymth(:len_trim(ymth)))
127  ycomment='SST at month t'//adjustl(ymth(:len_trim(ymth)))
128  CALL write_surf(dgu, u, &
129  hprogram,yrecfm,s%XSST_MTH(:,jmth),iresp,hcomment=ycomment)
130  ENDDO
131 !
132 ENDIF
133 !
134 yrecfm='SST'
135 ycomment='SST'
136  CALL write_surf(dgu, u, &
137  hprogram,yrecfm,s%XSST(:),iresp,hcomment=ycomment)
138 !
139 !-------------------------------------------------------------------------------
140 !
141 !* 4. Semi-prognostic fields:
142 ! ----------------------
143 !
144 !* roughness length
145 !
146 yrecfm='Z0SEA'
147 ycomment='Z0SEA (m)'
148  CALL write_surf(dgu, u, &
149  hprogram,yrecfm,s%XZ0(:),iresp,hcomment=ycomment)
150 !
151 !
152 !* sea surface salinity
153 !
154 IF(s%LINTERPOL_SSS)THEN
155  !
156  inmth=SIZE(s%XSSS_MTH,2)
157  !
158  DO jmth=1,inmth
159  WRITE(ymth,'(I2)') (jmth-1)
160  yrecfm='SSS_MTH'//adjustl(ymth(:len_trim(ymth)))
161  ycomment='Sea Surface Salinity at month t'//adjustl(ymth(:len_trim(ymth)))
162  CALL write_surf(dgu, u, &
163  hprogram,yrecfm,s%XSSS_MTH(:,jmth),iresp,hcomment=ycomment)
164  ENDDO
165 !
166 ENDIF
167 !
168 yrecfm='SSS'
169 ycomment='Sea Surface Salinity'
170  CALL write_surf(dgu, u, &
171  hprogram,yrecfm,s%XSSS(:),iresp,hcomment=ycomment)
172 !
173 !
174 !* ocean surface albedo (direct and diffuse fraction)
175 !
176 IF(s%CSEA_ALB=='RS14')THEN
177 !
178  yrecfm='OSA_DIR'
179  ycomment='direct ocean surface albedo (-)'
180  CALL write_surf(dgu, u, &
181  hprogram,yrecfm,s%XDIR_ALB(:),iresp,hcomment=ycomment)
182 !
183  yrecfm='OSA_SCA'
184  ycomment='diffuse ocean surface albedo (-)'
185  CALL write_surf(dgu, u, &
186  hprogram,yrecfm,s%XSCA_ALB(:),iresp,hcomment=ycomment)
187 !
188 ENDIF
189 !
190 !-------------------------------------------------------------------------------
191 !
192 !* 5. Time
193 ! ----
194 !
195 yrecfm='DTCUR'
196 ycomment='s'
197  CALL write_surf(dgu, u, &
198  hprogram,yrecfm,s%TTIME,iresp,hcomment=ycomment)
199 IF (lhook) CALL dr_hook('WRITESURF_SEAFLUX_N',1,zhook_handle)
200 !
201 !
202 !-------------------------------------------------------------------------------
203 !
204 END SUBROUTINE writesurf_seaflux_n
subroutine writesurf_seaflux_n(DGU, U, O, OR, S, HPROGRAM)
subroutine writesurf_ocean_n(DGU, U, O, OR, HPROGRAM)
subroutine writesurf_seaice_n(DGU, U, S, HPROGRAM)