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