SURFEX v8.1
General documentation of Surfex
writesurf_covern.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_cover_n (HSELECT, U, HPROGRAM)
7 ! #################################
8 !
9 !!**** *WRITESURF_COVER_n* - writes cover fields
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !!
15 !!
16 !!** METHOD
17 !! ------
18 !!
19 !!
20 !! REFERENCE
21 !! ---------
22 !!
23 !!
24 !! AUTHOR
25 !! ------
26 !! V. Masson *Meteo France*
27 !!
28 !! MODIFICATIONS
29 !! -------------
30 !! Original 01/2003
31 !! M. Moge 02/2015 parallelization using WRITE_LCOVER
32 !-------------------------------------------------------------------------------
33 !
34 !* 0. DECLARATIONS
35 ! ------------
36 !
37 USE modd_surf_atm_n, ONLY : surf_atm_t
38 !
39 USE modd_data_cover_par, ONLY : jpcover
40 !
42 !
44 USE modi_write_lcover
45 !
46 USE yomhook ,ONLY : lhook, dr_hook
47 USE parkind1 ,ONLY : jprb
48 !
49 IMPLICIT NONE
50 !
51 !* 0.1 Declarations of arguments
52 ! -------------------------
53 !
54  CHARACTER(LEN=*), DIMENSION(:), INTENT(IN) :: HSELECT
55 !
56 TYPE(surf_atm_t), INTENT(INOUT) :: U
57 !
58  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling
59 !
60 !* 0.2 Declarations of local variables
61 ! -------------------------------
62 !
63 INTEGER :: IRESP ! IRESP : return-code if a problem appears
64  CHARACTER(LEN=12) :: YRECFM ! Name of the article to be read
65  CHARACTER(LEN=100):: YCOMMENT ! Comment string
66 REAL(KIND=JPRB) :: ZHOOK_HANDLE
67 !
68 !-------------------------------------------------------------------------------
69 !
70 !* 1. Cover classes :
71 ! -------------
72 !
73 IF (lhook) CALL dr_hook('WRITESURF_COVER_N',0,zhook_handle)
74 !
75 ycomment = '(-)'
76  CALL write_surf(hselect, &
77  hprogram,'FRAC_SEA ',u%XSEA, iresp,hcomment=ycomment)
78  CALL write_surf(hselect, &
79  hprogram,'FRAC_NATURE',u%XNATURE,iresp,hcomment=ycomment)
80  CALL write_surf(hselect, &
81  hprogram,'FRAC_WATER ',u%XWATER, iresp,hcomment=ycomment)
82  CALL write_surf(hselect, &
83  hprogram,'FRAC_TOWN ',u%XTOWN, iresp,hcomment=ycomment)
84 !
85  CALL write_lcover(hselect,hprogram,u%LCOVER)
86 !
87 ycomment='COVER FIELDS'
88  CALL write_surf_cov(hselect, &
89  hprogram,'COVER',u%XCOVER(:,:),u%LCOVER,iresp,hcomment=ycomment)
90 !
91 !-------------------------------------------------------------------------------
92 !
93 !* 2. Orography :
94 ! ---------
95 !
96 yrecfm='ZS'
97 ycomment='X_Y_ZS (M)'
98  CALL write_surf(hselect,hprogram,yrecfm,u%XZS(:),iresp,hcomment=ycomment)
99 !
100 IF (lhook) CALL dr_hook('WRITESURF_COVER_N',1,zhook_handle)
101 !
102 !-------------------------------------------------------------------------------
103 !
104 END SUBROUTINE writesurf_cover_n
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine writesurf_cover_n(HSELECT, U, HPROGRAM)
subroutine write_lcover(HSELECT, HPROGRAM, OCOVER)
Definition: write_lcover.F90:7