SURFEX v8.1
General documentation of Surfex
write_lcover.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 write_lcover(HSELECT,HPROGRAM,OCOVER)
7 ! ################################
8 !
9 !!**** *READ_LCOVER* - routine to write a file for
10 !! physiographic data file of model _n
11 !!
12 !! PURPOSE
13 !! -------
14 !! The purpose of this routine is to write the list of covers to a file in parallel using MPI
15 !!
16 !!
17 !!** METHOD
18 !! ------
19 !!
20 !! EXTERNAL
21 !! --------
22 !!
23 !!
24 !!
25 !! IMPLICIT ARGUMENTS
26 !! ------------------
27 !!
28 !! REFERENCE
29 !! ---------
30 !!
31 !!
32 !! AUTHOR
33 !! ------
34 !! M. Moge *LA - CNRS*
35 !!
36 !! MODIFICATIONS
37 !! -------------
38 !!
39 !-------------------------------------------------------------------------------
40 !
41 !* 0. DECLARATIONS
42 ! ------------
43 !
44 USE modd_data_cover_par, ONLY : jpcover
45 !
47 !
48 USE yomhook ,ONLY : lhook, dr_hook
49 USE parkind1 ,ONLY : jprb
50 !
51 IMPLICIT NONE
52 !
53 #ifdef MNH_PARALLEL
54 #ifndef NOMPI
55 include "mpif.h"
56 #endif
57 #endif
58 !
59 !* 0.1 Declarations of arguments
60 ! -------------------------
61 !
62  CHARACTER(LEN=*), DIMENSION(:), INTENT(IN) :: HSELECT
63  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! calling program
64 LOGICAL, DIMENSION(JPCOVER) :: OCOVER ! list of covers
65 !
66 !* 0.2 Declarations of local variables
67 ! -------------------------------
68 !
69 INTEGER :: IRESP ! Error code after reading
70  CHARACTER(LEN=12) :: YRECFM ! Name of the article to be read
71  CHARACTER(LEN=100):: YCOMMENT ! Comment string
72 LOGICAL, DIMENSION(JPCOVER) :: GCOVER ! tmp list of covers
73 REAL(KIND=JPRB) :: ZHOOK_HANDLE
74 INTEGER :: IINFO
75 !-------------------------------------------------------------------------------
76 !
77 !
78 !* ascendant compatibility
79 IF (lhook) CALL dr_hook('WRITE_LCOVER',0,zhook_handle)
80 !
81 #ifdef MNH_PARALLEL
82 #ifndef NOMPI
83  CALL mpi_allreduce(ocover, gcover, SIZE(ocover),mpi_logical, mpi_lor, mpi_comm_world, iinfo)
84 ocover(:)=gcover(:)
85 #endif
86 #endif
87 !
88 yrecfm='COVER_LIST'
89 ycomment='(LOGICAL LIST)'
90  CALL write_surf(hselect,hprogram,yrecfm,ocover(:),iresp,hcomment=ycomment,hdir='-')
91 !
92 IF (lhook) CALL dr_hook('WRITE_LCOVER',1,zhook_handle)
93 !
94 !-------------------------------------------------------------------------------
95 !
96 END SUBROUTINE write_lcover
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine write_lcover(HSELECT, HPROGRAM, OCOVER)
Definition: write_lcover.F90:7