SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
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 (DGU, &
7  u, &
8  hprogram)
9 ! #################################
10 !
11 !!**** *WRITESURF_COVER_n* - writes cover fields
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !!
17 !!
18 !!** METHOD
19 !! ------
20 !!
21 !!
22 !! REFERENCE
23 !! ---------
24 !!
25 !!
26 !! AUTHOR
27 !! ------
28 !! V. Masson *Meteo France*
29 !!
30 !! MODIFICATIONS
31 !! -------------
32 !! Original 01/2003
33 !-------------------------------------------------------------------------------
34 !
35 !* 0. DECLARATIONS
36 ! ------------
37 !
38 !
39 !
40 !
41 !
43 !
44 USE modd_surf_atm_n, ONLY : surf_atm_t
45 !
46 USE modd_data_cover_par, ONLY : jpcover
47 !
49 !
51 !
52 USE yomhook ,ONLY : lhook, dr_hook
53 USE parkind1 ,ONLY : jprb
54 !
55 IMPLICIT NONE
56 !
57 !* 0.1 Declarations of arguments
58 ! -------------------------
59 !
60 !
61 !
62 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
63 !
64 TYPE(surf_atm_t), INTENT(INOUT) :: u
65 !
66  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
67 !
68 !* 0.2 Declarations of local variables
69 ! -------------------------------
70 !
71 INTEGER :: iresp ! IRESP : return-code if a problem appears
72  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
73  CHARACTER(LEN=100):: ycomment ! Comment string
74 REAL(KIND=JPRB) :: zhook_handle
75 !
76 !-------------------------------------------------------------------------------
77 !
78 !* 1. Cover classes :
79 ! -------------
80 !
81 IF (lhook) CALL dr_hook('WRITESURF_COVER_N',0,zhook_handle)
82 !
83 ycomment = '(-)'
84  CALL write_surf(dgu, u, &
85  hprogram,'FRAC_SEA ',u%XSEA, iresp,hcomment=ycomment)
86  CALL write_surf(dgu, u, &
87  hprogram,'FRAC_NATURE',u%XNATURE,iresp,hcomment=ycomment)
88  CALL write_surf(dgu, u, &
89  hprogram,'FRAC_WATER ',u%XWATER, iresp,hcomment=ycomment)
90  CALL write_surf(dgu, u, &
91  hprogram,'FRAC_TOWN ',u%XTOWN, iresp,hcomment=ycomment)
92 !
93 yrecfm='COVER_LIST'
94 ycomment='(LOGICAL LIST)'
95  CALL write_surf(dgu, u, &
96  hprogram,yrecfm,u%LCOVER(:),iresp,hcomment=ycomment,hdir='-')
97 !
98 ycomment='COVER FIELDS'
99  CALL write_surf_cov(dgu, u, &
100  hprogram,'COVER',u%XCOVER(:,:),u%LCOVER,iresp,hcomment=ycomment)
101 !
102 !-------------------------------------------------------------------------------
103 !
104 !* 2. Orography :
105 ! ---------
106 !
107 yrecfm='ZS'
108 ycomment='X_Y_ZS (M)'
109  CALL write_surf(dgu, u, &
110  hprogram,yrecfm,u%XZS(:),iresp,hcomment=ycomment)
111 !
112 IF (lhook) CALL dr_hook('WRITESURF_COVER_N',1,zhook_handle)
113 !
114 !-------------------------------------------------------------------------------
115 !
116 END SUBROUTINE writesurf_cover_n
subroutine writesurf_cover_n(DGU, U, HPROGRAM)
subroutine, public write_surf_cov(DGU, U, HPROGRAM, HREC, PFIELD, OFLAG, KRESP, HCOMMENT, HDIR)