SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_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 read_lcover (&
7  hprogram,ocover)
8 ! ################################
9 !
10 !!**** *READ_LCOVER* - routine to read a file for
11 !! physiographic data file of model _n
12 !!
13 !! PURPOSE
14 !! -------
15 !! The purpose of this routine is to initialise the list of covers
16 !!
17 !!
18 !!** METHOD
19 !! ------
20 !!
21 !! EXTERNAL
22 !! --------
23 !!
24 !!
25 !!
26 !! IMPLICIT ARGUMENTS
27 !! ------------------
28 !!
29 !! REFERENCE
30 !! ---------
31 !!
32 !!
33 !! AUTHOR
34 !! ------
35 !! V. Masson *Meteo France*
36 !!
37 !! MODIFICATIONS
38 !! -------------
39 !! Original 10/2008
40 !-------------------------------------------------------------------------------
41 !
42 !* 0. DECLARATIONS
43 ! ------------
44 !
45 !
46 !
47 !
48 USE modd_data_cover_par, ONLY : jpcover
49 !
51 USE modi_old_name
52 !
53 USE yomhook ,ONLY : lhook, dr_hook
54 USE parkind1 ,ONLY : jprb
55 !
56 IMPLICIT NONE
57 !
58 !* 0.1 Declarations of arguments
59 ! -------------------------
60 !
61 !
62 !
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 redding
70  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
71 INTEGER :: iversion ! version of surfex file being read
72 LOGICAL, DIMENSION(:), ALLOCATABLE :: gcover ! cover list in the file
73 REAL(KIND=JPRB) :: zhook_handle
74 !-------------------------------------------------------------------------------
75 !
76 !
77 !* ascendant compatibility
78 IF (lhook) CALL dr_hook('READ_LCOVER',0,zhook_handle)
79 yrecfm='VERSION'
80  CALL read_surf(&
81  hprogram,yrecfm,iversion,iresp)
82 IF (iversion<=3) THEN
83  ALLOCATE(gcover(255))
84 ELSE
85  ALLOCATE(gcover(jpcover))
86 END IF
87  CALL old_name(&
88  hprogram,'COVER_LIST ',yrecfm)
89  CALL read_surf(&
90  hprogram,yrecfm,gcover(:),iresp,hdir='-')
91 !
92 ocover=.false.
93 ocover(:SIZE(gcover))=gcover(:)
94 DEALLOCATE(gcover)
95 IF (lhook) CALL dr_hook('READ_LCOVER',1,zhook_handle)
96 !
97 !-------------------------------------------------------------------------------
98 !
99 END SUBROUTINE read_lcover
subroutine read_lcover(HPROGRAM, OCOVER)
Definition: read_lcover.F90:6
subroutine old_name(HPROGRAM, HRECIN, HRECOUT)
Definition: old_name.F90:6