SURFEX v8.1
General documentation of Surfex
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 (HSELECT, DTS, G, S, HPROGRAM)
7 ! ###################################################
8 !
9 !!**** *WRITE_SEAFLUX_n* - writes SEAFLUX 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 !! B. Decharme 07/2011 : delete argument HWRITE
36  !! M. Moge 02/2015 parallelization using WRITE_LCOVER
37 !-------------------------------------------------------------------------------
38 !
39 !* 0. DECLARATIONS
40 ! ------------
41 !
43 USE modd_sfx_grid_n, ONLY : grid_t
44 USE modd_seaflux_n, ONLY : seaflux_t
45 !
46 USE modd_data_cover_par, ONLY : jpcover
47 !
49 !
51 USE modi_write_grid
52 USE modi_writesurf_pgd_seaf_par_n
53 USE modi_write_lcover
54 !
55 USE yomhook ,ONLY : lhook, dr_hook
56 USE parkind1 ,ONLY : jprb
57 !
58 IMPLICIT NONE
59 !
60 !* 0.1 Declarations of arguments
61 ! -------------------------
62 !
63  CHARACTER(LEN=*), DIMENSION(:), INTENT(IN) :: HSELECT
64 !
65 TYPE(data_seaflux_t), INTENT(INOUT) :: DTS
66 TYPE(grid_t), INTENT(INOUT) :: G
67 TYPE(seaflux_t), INTENT(INOUT) :: S
68 !
69  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling
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 REAL(KIND=JPRB) :: ZHOOK_HANDLE
78 !
79 !-------------------------------------------------------------------------------
80 !
81 !
82 !
83 !* 2. Physiographic data fields:
84 ! -------------------------
85 !
86 !* cover classes
87 !
88 IF (lhook) CALL dr_hook('WRITESURF_PGD_SEAFLUX_N',0,zhook_handle)
89 !
90  CALL write_lcover(hselect,hprogram,s%LCOVER)
91 !
92 !
93 !* orography
94 !
95 yrecfm='ZS'
96 ycomment='ZS'
97  CALL write_surf(hselect, hprogram,yrecfm,s%XZS(:),iresp,hcomment=ycomment)
98 !
99 !* bathymetry
100 !
101 yrecfm='BATHY'
102 ycomment='BATHY'
103  CALL write_surf(hselect, hprogram,yrecfm,s%XSEABATHY(:),iresp,hcomment=ycomment)
104 !
105 !* latitude, longitude
106 !
107  CALL write_grid(hselect, hprogram,g%CGRID,g%XGRID_PAR,g%XLAT,g%XLON,g%XMESH_SIZE,iresp)
108 !
109 !* sst
110 !
111 yrecfm='SST_DATA'
112 ycomment='(LOGICAL)'
113  CALL write_surf(hselect, hprogram,yrecfm,dts%LSST_DATA,iresp,hcomment=ycomment)
114 !
115 IF (dts%LSST_DATA) CALL writesurf_pgd_seaf_par_n(hselect, dts, hprogram)
116 IF (lhook) CALL dr_hook('WRITESURF_PGD_SEAFLUX_N',1,zhook_handle)
117 !
118 !-------------------------------------------------------------------------------
119 !
120 END SUBROUTINE writesurf_pgd_seaflux_n
subroutine writesurf_pgd_seaflux_n(HSELECT, DTS, G, S, HPROGRAM)
subroutine writesurf_pgd_seaf_par_n(HSELECT, DTS, HPROGRAM)
integer, parameter jprb
Definition: parkind1.F90:32
subroutine write_grid(HSELECT, HPROGRAM, HGRID, PGRID_PAR, PLAT, PLON,
Definition: write_grid.F90:7
logical lhook
Definition: yomhook.F90:15
subroutine write_lcover(HSELECT, HPROGRAM, OCOVER)
Definition: write_lcover.F90:7