SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_pgd_seaflux_parn.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_pgd_seaflux_par_n (DTCO, U, DTS, SG, &
7  hprogram,ksize,hdir)
8 ! ################################################
9 !
10 !!**** *READ_PGD_SEAFLUX_PAR_n* - reads SEAFLUX sst
11 !!
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !!** METHOD
17 !! ------
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !!
30 !! AUTHOR
31 !! ------
32 !! P. Le Moigne *Meteo France*
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 09/2007
37 !-------------------------------------------------------------------------------
38 !
39 !* 0. DECLARATIONS
40 ! ------------
41 !
42 !
43 !
44 !
45 !
46 !
48 USE modd_surf_atm_n, ONLY : surf_atm_t
49 !
50 !
53 !
55 USE modd_prep, ONLY : linterp
56 !
57 USE modi_get_luout
59 USE modi_hor_interpol
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 !
71 !
72 TYPE(data_cover_t), INTENT(INOUT) :: dtco
73 TYPE(surf_atm_t), INTENT(INOUT) :: u
74 !
75 !
76 TYPE(data_seaflux_t), INTENT(INOUT) :: dts
77 TYPE(seaflux_grid_t), INTENT(INOUT) :: sg
78 !
79  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
80 INTEGER, INTENT(IN) :: ksize
81  CHARACTER(LEN=1),OPTIONAL,INTENT(IN) :: hdir ! type of field :
82 ! ! 'H' : field with
83 ! ! horizontal spatial dim.
84 ! ! '-' : no horizontal dim.
85 !
86 !* 0.2 Declarations of local variables
87 ! -------------------------------
88 !
89 REAL, DIMENSION(:,:), ALLOCATABLE :: zdata_sst
90  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
91  CHARACTER(LEN=100):: ycomment ! Comment string
92  CHARACTER(LEN=1) :: ydir
93 INTEGER :: iluout
94 INTEGER :: iresp ! IRESP : return-code if a problem appears
95 INTEGER :: jtime ! loop index
96 INTEGER :: iversion, ibugfix
97 REAL(KIND=JPRB) :: zhook_handle
98 !-------------------------------------------------------------------------------
99 !
100 IF (lhook) CALL dr_hook('READ_PGD_SEAFLUX_PAR_N',0,zhook_handle)
101 !
102  CALL get_luout(hprogram,iluout)
103 !
104 ydir = 'H'
105 IF (present(hdir)) ydir = hdir
106 !
107 yrecfm='VERSION'
108  CALL read_surf(&
109  hprogram,yrecfm,iversion,iresp)
110 !
111 yrecfm='BUG'
112  CALL read_surf(&
113  hprogram,yrecfm,ibugfix,iresp)
114 !
115 IF (iversion<4 .OR. iversion==4 .AND. ibugfix<=4 .OR. &
116  iversion>5 .OR. iversion==5 .AND. ibugfix>=1) THEN
117  yrecfm='ND_SEA_TIME'
118 ELSE
119  yrecfm='NDATA_SEA_TIME'
120 ENDIF
121  CALL read_surf(&
122  hprogram,yrecfm,dts%NTIME,iresp,hcomment=ycomment)
123 !
124 ALLOCATE(zdata_sst(ksize,dts%NTIME))
125 DO jtime=1,dts%NTIME
126  !
127  IF (iversion>5 .OR. iversion==5 .AND. ibugfix>=1) THEN
128  WRITE(yrecfm,fmt='(A7,I3.3)') 'D_SST_T',jtime
129  ELSEIF (iversion<4 .OR. iversion==4 .AND. ibugfix<=4) THEN
130  WRITE(yrecfm,fmt='(A9,I3.3)') 'DATA_SST_',jtime
131  ELSE
132  WRITE(yrecfm,fmt='(A10,I3.3)') 'DATA_SST_T',jtime
133  ENDIF
134  !
135  CALL read_surf(&
136  hprogram,yrecfm,zdata_sst(:,jtime),iresp,&
137  hcomment=ycomment,hdir=ydir)
138  !
139 END DO
140 !
141 ALLOCATE(dts%XDATA_SST(sg%NDIM,dts%NTIME))
142 IF (sg%NDIM/=ksize) THEN
143  linterp(:) = .true.
144  DO jtime=1,dts%NTIME
145  CALL hor_interpol(dtco, u, &
146  iluout,zdata_sst(:,jtime:jtime),dts%XDATA_SST(:,jtime:jtime))
147  ENDDO
148  DEALLOCATE(zdata_sst)
149 ELSE
150  dts%XDATA_SST(:,:) = zdata_sst(:,:)
151 ENDIF
152 !
153 ALLOCATE(dts%TDATA_SST (dts%NTIME))
154 !
155 IF (iversion<4 .OR. iversion==4 .AND. ibugfix<=4) THEN
156  DO jtime=1,dts%NTIME
157  WRITE(yrecfm,fmt='(A7,I3.3)') 'DTA_SST',jtime
158  ycomment='(-)'
159  CALL read_surf(&
160  hprogram,yrecfm,dts%TDATA_SST,iresp,hcomment=ycomment)
161  END DO
162 ELSE
163  IF (iversion>7 .OR. iversion==7 .AND. ibugfix>=3) THEN
164  yrecfm='TD_SST'
165  ELSE
166  yrecfm='TDATA_SST'
167  ENDIF
168  ycomment='(-)'
169  CALL read_surf(&
170  hprogram,yrecfm,dts%TDATA_SST,iresp,hcomment=ycomment)
171 ENDIF
172 !
173 IF (lhook) CALL dr_hook('READ_PGD_SEAFLUX_PAR_N',1,zhook_handle)
174 !-------------------------------------------------------------------------------
175 END SUBROUTINE read_pgd_seaflux_par_n
subroutine hor_interpol(DTCO, U, KLUOUT, PFIELDIN, PFIELDOUT)
Definition: hor_interpol.F90:6
subroutine read_pgd_seaflux_par_n(DTCO, U, DTS, SG, HPROGRAM, KSIZE, HDIR)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6