SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_default_seafluxn.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_default_seaflux_n (CHS, DGO, DGS, DGSI, O, S, &
7  hprogram)
8 ! #############################################################
9 !
10 !!**** *READ_SEAFLUX_CONF* - routine to read the configuration for SEAFLUX
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 !! Modified 01/2006 : sea flux parameterization.
37 !! Modified 09/2013 : S. Senesi : introduce sea-ice scheme
38 !! Modified 01/2015 : R. Séférian : introduce ocean surface albedo
39 !-------------------------------------------------------------------------------
40 !
41 !* 0. DECLARATIONS
42 ! ------------
43 !
44 !
45 !
46 !
47 !
48 !
49 !
54 USE modd_ocean_n, ONLY : ocean_t
55 USE modd_seaflux_n, ONLY : seaflux_t
56 !
58 !
59 USE mode_pos_surf
60 !
62 USE modi_get_default_nam_n
63 USE modi_get_luout
64 !
65 USE modd_read_namelist, ONLY : lnam_read
67 !
68 USE yomhook ,ONLY : lhook, dr_hook
69 USE parkind1 ,ONLY : jprb
70 !
71 IMPLICIT NONE
72 !
73 !* 0.1 Declarations of arguments
74 ! -------------------------
75 !
76 !
77 TYPE(ch_seaflux_t), INTENT(INOUT) :: chs
78 TYPE(diag_ocean_t), INTENT(INOUT) :: dgo
79 TYPE(diag_seaflux_t), INTENT(INOUT) :: dgs
80 TYPE(diag_seaice_t), INTENT(INOUT) :: dgsi
81 TYPE(ocean_t), INTENT(INOUT) :: o
82 TYPE(seaflux_t), INTENT(INOUT) :: s
83 !
84  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling ISBA
85 !
86 !* 0.2 Declarations of local variables
87 ! -------------------------------
88 !
89 !
90 LOGICAL :: gfound ! Return code when searching namelist
91 INTEGER :: iluout ! output listing logical unit
92 INTEGER :: iludes ! .des file logical unit
93 INTEGER :: imi
94 REAL(KIND=JPRB) :: zhook_handle
95 !-------------------------------------------------------------------------------
96 !
97 IF (lhook) CALL dr_hook('READ_DEFAULT_SEAFLUX_N',0,zhook_handle)
98  CALL get_luout(hprogram,iluout)
99 !
100  CALL get_default_nam_n(hprogram,'READ ',iludes)
101 !
102 IF (iludes==0 .AND. lhook) CALL dr_hook('READ_DEFAULT_SEAFLUX_N',1,zhook_handle)
103 IF (iludes==0) RETURN
104 !
106 !
107 IF (imi.NE.-1 .AND. lnam_read) THEN
108  CALL init_nam_seafluxn(o, s)
109  CALL init_nam_diag_surfn(dgs)
110  CALL init_nam_ch_seafluxn(chs)
111  CALL init_nam_diag_oceann(dgo)
112  CALL init_nam_seaicen(dgsi, s)
113 ENDIF
114 !
115 IF (lnam_read) THEN
116  !
117  !* reading of namelist
118  ! -------------------
119  !
120  CALL posnam(iludes,'NAM_SEAFLUXN',gfound,iluout)
121  IF (gfound) READ(unit=iludes,nml=nam_seafluxn)
122  CALL posnam(iludes,'NAM_DIAG_SURFN',gfound,iluout)
123  IF (gfound) READ(unit=iludes,nml=nam_diag_surfn)
124  CALL posnam(iludes,'NAM_CH_SEAFLUXN',gfound,iluout)
125  IF (gfound) READ(unit=iludes,nml=nam_ch_seafluxn)
126  CALL posnam(iludes,'NAM_DIAG_OCEANN',gfound,iluout)
127  IF (gfound) READ(unit=iludes,nml=nam_diag_oceann)
128  !
129  CALL posnam(iludes,'NAM_SEAICEN',gfound,iluout)
130  IF (gfound) READ(unit=iludes,nml=nam_seaicen)
131  !
132  CALL test_nam_var_surf(iluout,'CSEA_FLUX',csea_flux,'DIRECT','ITERAT','ECUME ','ECUME6','COARE3')
133  CALL test_nam_var_surf(iluout,'CSEA_ALB', csea_alb, 'UNIF','TA96','MK10','RS14')
134  CALL test_nam_var_surf(iluout,'CCH_DRY_DEP',cch_dry_dep,' ','WES89 ','NONE ')
135  CALL test_nam_var_surf(iluout,'CINTERPOL_SST',cinterpol_sst,'LINEAR','UNIF ','QUADRA','NONE ')
136  CALL test_nam_var_surf(iluout,'CINTERPOL_SSS',cinterpol_sss,'LINEAR','UNIF ','QUADRA','NONE ')
137  CALL test_nam_var_surf(iluout,'CINTERPOL_SIC',cinterpol_sic,'LINEAR','UNIF ','NONE ')
138  CALL test_nam_var_surf(iluout,'CINTERPOL_SIT',cinterpol_sit,'LINEAR','UNIF ','NONE ')
139 
140 ENDIF
141 !
142 IF (imi.NE.-1) THEN
143  CALL update_nam_seafluxn(o, s)
144  CALL update_nam_diag_surfn(dgs)
145  CALL update_nam_ch_seafluxn(chs)
146  CALL update_nam_diag_oceann(dgo)
147  CALL update_nam_seaicen(dgsi, s)
148 ENDIF
149 IF (lhook) CALL dr_hook('READ_DEFAULT_SEAFLUX_N',1,zhook_handle)
150 !
151 !
152 !-------------------------------------------------------------------------------
153 !
154 END SUBROUTINE read_default_seaflux_n
subroutine read_default_seaflux_n(CHS, DGO, DGS, DGSI, O, S, HPROGRAM)
subroutine update_nam_ch_seafluxn(CHS)
subroutine init_nam_ch_seafluxn(CHS)
subroutine init_nam_seaicen(DGSI, S)
subroutine init_nam_diag_surfn(DGF)
subroutine update_nam_diag_surfn(DGF)
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine init_nam_diag_oceann(DGO)
subroutine update_nam_seafluxn(O, S)
subroutine update_nam_seaicen(DGSI, S)
subroutine update_nam_diag_oceann(DGO)
integer function get_current_model_index_surfex()
subroutine init_nam_seafluxn(O, S)
subroutine get_default_nam_n(HPROGRAM, HACTION, KLUDES)