SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
writesurf_pgd_flaken.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_pgd_flake_n (DGU, U, &
7  fg, f, &
8  hprogram)
9 ! ###################################################
10 !
11 !!**** *WRITESURF_PGD_FLAKE_n* - writes FLAKE 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 !! B. Decharme 07/2011 : delete argument HWRITE
38 !-------------------------------------------------------------------------------
39 !
40 !* 0. DECLARATIONS
41 ! ------------
42 !
43 !
44 !
45 !
46 !
48 USE modd_surf_atm_n, ONLY : surf_atm_t
49 !
51 USE modd_flake_n, ONLY : flake_t
52 !
53 USE modd_data_cover_par, ONLY : jpcover
54 !
56 !
58 USE modi_write_grid
59 !
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(flake_grid_t), INTENT(INOUT) :: fg
75 TYPE(flake_t), INTENT(INOUT) :: f
76 !
77  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
78 
79 !
80 !* 0.2 Declarations of local variables
81 ! -------------------------------
82 !
83 INTEGER :: iresp ! IRESP : return-code if a problem appears
84  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
85  CHARACTER(LEN=100):: ycomment ! Comment string
86 REAL(KIND=JPRB) :: zhook_handle
87 !
88 !-------------------------------------------------------------------------------
89 !
90 !
91 !* 2. Physiographic data fields:
92 ! -------------------------
93 !
94 !* cover classes
95 !
96 IF (lhook) CALL dr_hook('WRITESURF_PGD_FLAKE_N',0,zhook_handle)
97 yrecfm='COVER_LIST'
98 ycomment='(LOGICAL LIST)'
99  CALL write_surf(dgu, u, &
100  hprogram,yrecfm,f%LCOVER(:),iresp,hcomment=ycomment,hdir='-')
101 !
102 ycomment='COVER FIELDS'
103  CALL write_surf_cov(dgu, u, &
104  hprogram,'COVER',f%XCOVER(:,:),f%LCOVER,iresp,hcomment=ycomment)
105 !
106 !* orography
107 !
108 yrecfm='ZS'
109 ycomment='ZS'
110  CALL write_surf(dgu, u, &
111  hprogram,yrecfm,f%XZS(:),iresp,hcomment=ycomment)
112 !
113 !* latitude, longitude
114 !
115  CALL write_grid(dgu, u, &
116  hprogram,fg%CGRID,fg%XGRID_PAR,fg%XLAT,fg%XLON,fg%XMESH_SIZE,iresp)
117 !
118 !* FLake parameters
119 !
120 yrecfm='WATER_DEPTH'
121 ycomment='X_Y_'//yrecfm//' (m)'
122  CALL write_surf(dgu, u, &
123  hprogram,yrecfm,f%XWATER_DEPTH(:),iresp,hcomment=ycomment)
124 !
125 yrecfm='WATER_FETCH'
126 ycomment='X_Y_'//yrecfm//' (m)'
127  CALL write_surf(dgu, u, &
128  hprogram,yrecfm,f%XWATER_FETCH(:),iresp,hcomment=ycomment)
129 !
130 yrecfm='T_BS'
131 ycomment='X_Y_'//yrecfm//' (K)'
132  CALL write_surf(dgu, u, &
133  hprogram,yrecfm,f%XT_BS(:),iresp,hcomment=ycomment)
134 !
135 yrecfm='DEPTH_BS'
136 ycomment='X_Y_'//yrecfm//' (m)'
137  CALL write_surf(dgu, u, &
138  hprogram,yrecfm,f%XDEPTH_BS(:),iresp,hcomment=ycomment)
139 !
140 yrecfm='EXTCOEF_WAT'
141 ycomment='X_Y_'//yrecfm//' '
142  CALL write_surf(dgu, u, &
143  hprogram,yrecfm,f%XEXTCOEF_WATER(:),iresp,hcomment=ycomment)
144 IF (lhook) CALL dr_hook('WRITESURF_PGD_FLAKE_N',1,zhook_handle)
145 !
146 !-------------------------------------------------------------------------------
147 !
148 END SUBROUTINE writesurf_pgd_flake_n
subroutine write_grid(DGU, U, HPROGRAM, HGRID, PGRID_PAR, PLAT, PLON, PMESH_SIZE, KRESP, PDIR, HDIR)
Definition: write_grid.F90:6
subroutine writesurf_pgd_flake_n(DGU, U, FG, F, HPROGRAM)
subroutine, public write_surf_cov(DGU, U, HPROGRAM, HREC, PFIELD, OFLAG, KRESP, HCOMMENT, HDIR)