SURFEX v8.1
General documentation of Surfex
pgd_seaflux_par.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 pgd_seaflux_par (DTCO, DTS, KDIM, UG, U, USS, HPROGRAM)
7 ! ##############################################################
8 !
9 !!**** *PGD_SEAFLUX_PAR* monitor for averaging and interpolations of sst
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! METHOD
15 !! ------
16 !!
17 !
18 !! EXTERNAL
19 !! --------
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !! AUTHOR
28 !! ------
29 !!
30 !! P. Le Moigne Meteo-France
31 !!
32 !! MODIFICATION
33 !! ------------
34 !!
35 !! Original 09/2007
36 !!
37 !!
38 !----------------------------------------------------------------------------
39 !
40 !* 0. DECLARATION
41 ! -----------
42 !
43 !
44 !
48 USE modd_surf_atm_n, ONLY : surf_atm_t
49 USE modd_sso_n, ONLY : sso_t
50 !
51 USE modd_surf_par, ONLY : xundef, nundef
52 !
53 USE modd_pgdwork, ONLY : catype
54 !
56 !
57 USE modi_get_luout
58 USE modi_open_namelist
59 USE modi_close_namelist
61 !
62 USE mode_pos_surf
63 !
64 !
65 USE yomhook ,ONLY : lhook, dr_hook
66 USE parkind1 ,ONLY : jprb
67 !
68 USE modi_abor1_sfx
69 !
70 IMPLICIT NONE
71 !
72 !* 0.1 Declaration of arguments
73 ! ------------------------
74 !
75 !
76 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
77 TYPE(data_seaflux_t), INTENT(INOUT) :: DTS
78 INTEGER, INTENT(IN) :: KDIM
79 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
80 TYPE(surf_atm_t), INTENT(INOUT) :: U
81 TYPE(sso_t), INTENT(INOUT) :: USS
82 !
83  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! Type of program
84 !
85 !
86 !* 0.2 Declaration of local variables
87 ! ------------------------------
88 !
89 INTEGER :: ILUOUT ! output listing logical unit
90 INTEGER :: ILUNAM ! namelist file logical unit
91 LOGICAL :: GFOUND ! true if namelist is found
92 !
93 INTEGER :: JTIME ! loop counter on time
94 !
95 !* 0.3 Declaration of namelists
96 ! ------------------------
97 !
98 INTEGER :: NTIME_SST
99 INTEGER, PARAMETER :: NTIME_MAX = 800
100 !
101 REAL, DIMENSION(NTIME_MAX) :: XUNIF_SST ! sea surface temperature
102 
103 INTEGER, DIMENSION(NTIME_MAX) :: NYEAR_SST
104 INTEGER, DIMENSION(NTIME_MAX) :: NMONTH_SST
105 INTEGER, DIMENSION(NTIME_MAX) :: NDAY_SST
106 REAL, DIMENSION(NTIME_MAX) :: XTIME_SST
107 LOGICAL :: LSST_DATA
108 !
109 ! name of files containing data
110 !
111  CHARACTER(LEN=28), DIMENSION(NTIME_MAX) :: CFNAM_SST ! sea surface temperature
112  CHARACTER(LEN=6), DIMENSION(NTIME_MAX) :: CFTYP_SST ! sea surface temperature
113 REAL(KIND=JPRB) :: ZHOOK_HANDLE
114 !
115 NAMELIST/nam_data_seaflux/ntime_sst, lsst_data, xunif_sst, cfnam_sst, cftyp_sst, &
116  nyear_sst, nmonth_sst, nday_sst, xtime_sst
117 !-------------------------------------------------------------------------------
118 !
119 !* 1. Initializations
120 ! ---------------
121 !
122 IF (lhook) CALL dr_hook('PGD_SEAFLUX_PAR',0,zhook_handle)
123 ntime_sst = 12
124 xunif_sst(:) = xundef ! sea surface temperature
125 !
126 CFNAM_SST (:) = ' '
127 !
128 CFTYP_SST (:) = ' '
129 !
130 nyear_sst(:) = nundef
131 nmonth_sst(:) = nundef
132 nday_sst(:) = nundef
133 xtime_sst(:) = xundef
134 !
135 lsst_data = .false.
136 !-------------------------------------------------------------------------------
137 !
138 !* 2. Input file for cover types
139 ! --------------------------
140 !
141  CALL get_luout(hprogram,iluout)
142  CALL open_namelist(hprogram,ilunam)
143 !
144  CALL posnam(ilunam,'NAM_DATA_SEAFLUX',gfound,iluout)
145 IF (gfound) READ(unit=ilunam,nml=nam_data_seaflux)
146 !
147  CALL close_namelist(hprogram,ilunam)
148 !
149 dts%LSST_DATA = lsst_data
150 IF (.NOT. lsst_data .AND. lhook) CALL dr_hook('PGD_SEAFLUX_PAR',1,zhook_handle)
151 IF (.NOT. lsst_data) RETURN
152 !
153 IF (ntime_sst > ntime_max) THEN
154  WRITE(iluout,*)'NTIME_SST SHOULD NOT EXCEED',ntime_max
155  CALL abor1_sfx('PGD_SEAFLUX_PAR: NTIME TOO BIG')
156 ENDIF
157 ALLOCATE(dts%XDATA_SST (kdim,ntime_sst))
158 ALLOCATE(dts%TDATA_SST (ntime_sst))
159 !
160 !-------------------------------------------------------------------------------
161 !
162 !* 3. Uniform fields are prescribed
163 ! -----------------------------
164 !
165 CATYPE = 'ARI'
166 !
167 DO jtime=1,ntime_sst
168  CALL pgd_field(dtco, ug, u, uss, &
169  hprogram,'SST: sea surface temperature','SEA',cfnam_sst(jtime), &
170  cftyp_sst(jtime),xunif_sst(jtime),dts%XDATA_SST(:,jtime))
171 !
172  dts%TDATA_SST(jtime)%TDATE%YEAR = nyear_sst(jtime)
173  dts%TDATA_SST(jtime)%TDATE%MONTH = nmonth_sst(jtime)
174  dts%TDATA_SST(jtime)%TDATE%DAY = nday_sst(jtime)
175  dts%TDATA_SST(jtime)%TIME = xtime_sst(jtime)
176 !
177 END DO
178 IF (lhook) CALL dr_hook('PGD_SEAFLUX_PAR',1,zhook_handle)
179 !
180 !-------------------------------------------------------------------------------
181 !
182 END SUBROUTINE pgd_seaflux_par
character(len=3) catype
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine pgd_seaflux_par(DTCO, DTS, KDIM, UG, U, USS, HPROGRAM)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
integer, parameter nundef
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
logical lhook
Definition: yomhook.F90:15
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)