SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_surf_atm_confn.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_surf_atm_conf_n (CHU, DGU, USS, &
7  hprogram)
8 ! #######################################################
9 !
10 !!**** *READ_SURF_ATM_CONF* - reads the general configuration for surface
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !!
29 !! AUTHOR
30 !! ------
31 !! V. Masson *Meteo France*
32 !!
33 !! MODIFICATIONS
34 !! -------------
35 !! Original 01/2003
36 !-------------------------------------------------------------------------------
37 !
38 !* 0. DECLARATIONS
39 ! ------------
40 !
41 !
42 !
43 !
44 !
45 USE modd_ch_surf_n, ONLY : ch_surf_t
48 !
50 !
52 USE modi_get_luout
53 USE modi_open_namelist
54 USE modi_close_namelist
55 USE mode_pos_surf
56 !
57 USE modd_read_namelist, ONLY : lnam_read
58 USE modn_sso_n
60 !
61 USE yomhook ,ONLY : lhook, dr_hook
62 USE parkind1 ,ONLY : jprb
63 !
64 IMPLICIT NONE
65 !
66 !* 0.1 Declarations of arguments
67 ! -------------------------
68 !
69 !
70 TYPE(ch_surf_t), INTENT(INOUT) :: chu
71 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
72 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
73 !
74  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling GROUND
75 !
76 !* 0.2 Declarations of local variables
77 ! -------------------------------
78 !
79 !
80 LOGICAL :: gfound ! Return code when searching namelist
81 INTEGER :: iluout ! logical unit of output file
82 INTEGER :: inam ! logical unit of namelist file
83 INTEGER :: imi
84 REAL(KIND=JPRB) :: zhook_handle
85 !-------------------------------------------------------------------------------
86 !
87 !* get output listing file logical unit
88 !
89 IF (lhook) CALL dr_hook('READ_SURF_ATM_CONF_N',0,zhook_handle)
90  CALL get_luout(hprogram,iluout)
91 !
93 !
94 IF (imi.NE.-1 .AND. lnam_read) THEN
95  CALL init_nam_sson(uss)
96  CALL init_nam_ch_controln(chu)
97  CALL init_nam_ch_surfn(chu)
98  CALL init_nam_diag_surf_atmn(dgu)
99  CALL init_nam_diag_surfn(dgu)
100  CALL init_nam_write_diag_surfn(dgu)
101 ENDIF
102 !
103 IF (lnam_read) THEN
104  !
105  !* open namelist file
106  !
107  CALL open_namelist(hprogram,inam)
108  !
109  !* reading of namelist
110  ! -------------------
111  !
112  !
113  CALL posnam(inam,'NAM_SSON',gfound,iluout)
114  IF (gfound) READ(unit=inam,nml=nam_sson)
115  CALL test_nam_var_surf(iluout,'CROUGH',crough,'NONE','Z01D','Z04D','BE04')
116  !
117  CALL posnam(inam,'NAM_DIAG_SURFN',gfound,iluout)
118  IF (gfound) READ(unit=inam,nml=nam_diag_surfn)
119  !
120  cselect(:) = ' '
121  CALL posnam(inam,'NAM_WRITE_DIAG_SURFN',gfound,iluout)
122  IF (gfound) READ(unit=inam,nml=nam_write_diag_surfn)
123  !
124  CALL posnam(inam,'NAM_DIAG_SURF_ATMN',gfound,iluout)
125  IF (gfound) READ(unit=inam,nml=nam_diag_surf_atmn)
126  !
127  CALL posnam(inam,'NAM_CH_CONTROLN',gfound,iluout)
128  IF (gfound) READ(unit=inam,nml=nam_ch_controln)
129  !
130  CALL posnam(inam,'NAM_CH_SURFN',gfound,iluout)
131  IF (gfound) READ(unit=inam,nml=nam_ch_surfn)
132  !
133  !* close namelist file
134  !
135  CALL close_namelist(hprogram,inam)
136  !
137 ENDIF
138 !
139 IF (imi.NE.-1) THEN
140  CALL update_nam_sson(uss)
141  CALL update_nam_ch_controln(chu)
142  CALL update_nam_ch_surfn(chu)
143  CALL update_nam_diag_surf_atmn(dgu)
144  CALL update_nam_diag_surfn(dgu)
146 ENDIF
147 IF (lhook) CALL dr_hook('READ_SURF_ATM_CONF_N',1,zhook_handle)
148 !
149 !
150 !-------------------------------------------------------------------------------
151 !
152 END SUBROUTINE read_surf_atm_conf_n
subroutine update_nam_ch_controln(CHI)
Definition: modn_isban.F90:365
subroutine update_nam_diag_surf_atmn(DGU)
subroutine update_nam_write_diag_surfn(DGU)
subroutine init_nam_ch_controln(CHI)
Definition: modn_isban.F90:350
subroutine update_nam_ch_surfn(CHU)
subroutine init_nam_diag_surfn(DGF)
subroutine read_surf_atm_conf_n(CHU, DGU, USS, HPROGRAM)
subroutine update_nam_sson(USS)
Definition: modn_sson.F90:67
subroutine update_nam_diag_surfn(DGF)
subroutine init_nam_ch_surfn(CHU)
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine init_nam_sson(USS)
Definition: modn_sson.F90:51
subroutine init_nam_write_diag_surfn(DGU)
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)
subroutine init_nam_diag_surf_atmn(DGU)
integer function get_current_model_index_surfex()