SURFEX v8.1
General documentation of Surfex
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, GCP, DTS, KDIM, HPROGRAM,KSIZE,HDIR)
7 ! ################################################
8 !
9 !!**** *READ_PGD_SEAFLUX_PAR_n* - reads SEAFLUX sst
10 !!
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 !! P. Le Moigne *Meteo France*
32 !!
33 !! MODIFICATIONS
34 !! -------------
35 !! Original 09/2007
36 !-------------------------------------------------------------------------------
37 !
38 !* 0. DECLARATIONS
39 ! ------------
40 !
42 USE modd_surf_atm_n, ONLY : surf_atm_t
44 !
46 !
48 USE modd_prep, ONLY : linterp
49 !
50 USE modi_get_luout
52 USE modi_hor_interpol
53 !
54 USE yomhook ,ONLY : lhook, dr_hook
55 USE parkind1 ,ONLY : jprb
56 !
57 IMPLICIT NONE
58 !
59 !* 0.1 Declarations of arguments
60 ! -------------------------
61 !
62 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
63 TYPE(surf_atm_t), INTENT(INOUT) :: U
64 TYPE(grid_conf_proj_t),INTENT(INOUT) :: GCP
65 !
66 TYPE(data_seaflux_t), INTENT(INOUT) :: DTS
67 !
68 INTEGER, INTENT(IN) :: KDIM
69 !
70  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling
71 INTEGER, INTENT(IN) :: KSIZE
72  CHARACTER(LEN=1),OPTIONAL,INTENT(IN) :: HDIR ! type of field :
73 ! ! 'H' : field with
74 ! ! horizontal spatial dim.
75 ! ! '-' : no horizontal dim.
76 !
77 !* 0.2 Declarations of local variables
78 ! -------------------------------
79 !
80 REAL, DIMENSION(:,:), ALLOCATABLE :: ZDATA_SST
81  CHARACTER(LEN=12) :: YRECFM ! Name of the article to be read
82  CHARACTER(LEN=100):: YCOMMENT ! Comment string
83  CHARACTER(LEN=1) :: YDIR
84 INTEGER :: ILUOUT
85 INTEGER :: IRESP ! IRESP : return-code if a problem appears
86 INTEGER :: JTIME ! loop index
87 INTEGER :: IVERSION, IBUGFIX
88 REAL(KIND=JPRB) :: ZHOOK_HANDLE
89 !-------------------------------------------------------------------------------
90 !
91 IF (lhook) CALL dr_hook('READ_PGD_SEAFLUX_PAR_N',0,zhook_handle)
92 !
93  CALL get_luout(hprogram,iluout)
94 !
95 ydir = 'H'
96 IF (PRESENT(hdir)) ydir = hdir
97 !
98 yrecfm='VERSION'
99  CALL read_surf(hprogram,yrecfm,iversion,iresp)
100 !
101 yrecfm='BUG'
102  CALL read_surf(hprogram,yrecfm,ibugfix,iresp)
103 !
104 IF (iversion<4 .OR. iversion==4 .AND. ibugfix<=4 .OR. &
105  iversion>5 .OR. iversion==5 .AND. ibugfix>=1) THEN
106  yrecfm='ND_SEA_TIME'
107 ELSE
108  yrecfm='NDATA_SEA_TIME'
109 ENDIF
110  CALL read_surf(hprogram,yrecfm,dts%NTIME,iresp,hcomment=ycomment)
111 !
112 ALLOCATE(zdata_sst(ksize,dts%NTIME))
113 DO jtime=1,dts%NTIME
114  !
115  IF (iversion>5 .OR. iversion==5 .AND. ibugfix>=1) THEN
116  WRITE(yrecfm,fmt='(A7,I3.3)') 'D_SST_T',jtime
117  ELSEIF (iversion<4 .OR. iversion==4 .AND. ibugfix<=4) THEN
118  WRITE(yrecfm,fmt='(A9,I3.3)') 'DATA_SST_',jtime
119  ELSE
120  WRITE(yrecfm,fmt='(A10,I3.3)') 'DATA_SST_T',jtime
121  ENDIF
122  !
123  CALL read_surf(hprogram,yrecfm,zdata_sst(:,jtime),iresp,&
124  hcomment=ycomment,hdir=ydir)
125  !
126 END DO
127 !
128 ALLOCATE(dts%XDATA_SST(kdim,dts%NTIME))
129 IF (kdim/=ksize) THEN
130  linterp(:) = .true.
131  DO jtime=1,dts%NTIME
132  CALL hor_interpol(dtco, u, gcp, iluout,zdata_sst(:,jtime:jtime),dts%XDATA_SST(:,jtime:jtime))
133  ENDDO
134  DEALLOCATE(zdata_sst)
135 ELSE
136  dts%XDATA_SST(:,:) = zdata_sst(:,:)
137 ENDIF
138 !
139 ALLOCATE(dts%TDATA_SST (dts%NTIME))
140 !
141 IF (iversion<4 .OR. iversion==4 .AND. ibugfix<=4) THEN
142  DO jtime=1,dts%NTIME
143  WRITE(yrecfm,fmt='(A7,I3.3)') 'DTA_SST',jtime
144  ycomment='(-)'
145  CALL read_surf(hprogram,yrecfm,dts%TDATA_SST,iresp,hcomment=ycomment)
146  END DO
147 ELSE
148  IF (iversion>7 .OR. iversion==7 .AND. ibugfix>=3) THEN
149  yrecfm='TD_SST'
150  ELSE
151  yrecfm='TDATA_SST'
152  ENDIF
153  ycomment='(-)'
154  CALL read_surf(hprogram,yrecfm,dts%TDATA_SST,iresp,hcomment=ycomment)
155 ENDIF
156 !
157 IF (lhook) CALL dr_hook('READ_PGD_SEAFLUX_PAR_N',1,zhook_handle)
158 !-------------------------------------------------------------------------------
159 END SUBROUTINE read_pgd_seaflux_par_n
subroutine read_pgd_seaflux_par_n(DTCO, U, GCP, DTS, KDIM, HPROGR
logical, dimension(:), allocatable linterp
Definition: modd_prep.F90:43
subroutine hor_interpol(DTCO, U, GCP, KLUOUT, PFIELDIN, PFIELDOUT)
Definition: hor_interpol.F90:7
integer, parameter jprb
Definition: parkind1.F90:32
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
logical lhook
Definition: yomhook.F90:15