SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
writesurf_pgd_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_pgd_seaflux_n (DGU, U, &
7  dts, sg, 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 !! 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 !
52 USE modd_seaflux_n, ONLY : seaflux_t
53 !
54 USE modd_data_cover_par, ONLY : jpcover
55 !
57 !
59 USE modi_write_grid
60 USE modi_writesurf_pgd_seaf_par_n
61 !
62 !
63 USE yomhook ,ONLY : lhook, dr_hook
64 USE parkind1 ,ONLY : jprb
65 !
66 IMPLICIT NONE
67 !
68 !* 0.1 Declarations of arguments
69 ! -------------------------
70 !
71 !
72 !
73 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
74 TYPE(surf_atm_t), INTENT(INOUT) :: u
75 !
76 TYPE(data_seaflux_t), INTENT(INOUT) :: dts
77 TYPE(seaflux_grid_t), INTENT(INOUT) :: sg
78 TYPE(seaflux_t), INTENT(INOUT) :: s
79 !
80  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
81 !
82 !* 0.2 Declarations of local variables
83 ! -------------------------------
84 !
85 INTEGER :: iresp ! IRESP : return-code if a problem appears
86  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
87  CHARACTER(LEN=100):: ycomment ! Comment string
88 REAL(KIND=JPRB) :: zhook_handle
89 !
90 !-------------------------------------------------------------------------------
91 !
92 !
93 !
94 !* 2. Physiographic data fields:
95 ! -------------------------
96 !
97 !* cover classes
98 !
99 IF (lhook) CALL dr_hook('WRITESURF_PGD_SEAFLUX_N',0,zhook_handle)
100 yrecfm='COVER_LIST'
101 ycomment='(LOGICAL LIST)'
102  CALL write_surf(dgu, u, &
103  hprogram,yrecfm,s%LCOVER(:),iresp,hcomment=ycomment,hdir='-')
104 !
105 ycomment='COVER FIELDS'
106  CALL write_surf_cov(dgu, u, &
107  hprogram,'COVER',s%XCOVER(:,:),s%LCOVER,iresp,hcomment=ycomment)
108 !
109 !
110 !* orography
111 !
112 yrecfm='ZS'
113 ycomment='ZS'
114  CALL write_surf(dgu, u, &
115  hprogram,yrecfm,s%XZS(:),iresp,hcomment=ycomment)
116 !
117 !* bathymetry
118 !
119 yrecfm='BATHY'
120 ycomment='BATHY'
121  CALL write_surf(dgu, u, &
122  hprogram,yrecfm,s%XSEABATHY(:),iresp,hcomment=ycomment)
123 !
124 !* latitude, longitude
125 !
126  CALL write_grid(dgu, u, &
127  hprogram,sg%CGRID,sg%XGRID_PAR,sg%XLAT,sg%XLON,sg%XMESH_SIZE,iresp)
128 !
129 !* sst
130 !
131 yrecfm='SST_DATA'
132 ycomment='(LOGICAL)'
133  CALL write_surf(dgu, u, &
134  hprogram,yrecfm,dts%LSST_DATA,iresp,hcomment=ycomment)
135 !
136 IF (dts%LSST_DATA) CALL writesurf_pgd_seaf_par_n(dgu, u, &
137  dts, &
138  hprogram)
139 IF (lhook) CALL dr_hook('WRITESURF_PGD_SEAFLUX_N',1,zhook_handle)
140 !
141 !-------------------------------------------------------------------------------
142 !
143 END SUBROUTINE writesurf_pgd_seaflux_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_seaf_par_n(DGU, U, DTS, HPROGRAM)
subroutine writesurf_pgd_seaflux_n(DGU, U, DTS, SG, S, HPROGRAM)
subroutine, public write_surf_cov(DGU, U, HPROGRAM, HREC, PFIELD, OFLAG, KRESP, HCOMMENT, HDIR)