SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_pgd_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_pgd_seaflux_n (DTCO, DTS, SG, S, U, &
7  hprogram)
8 ! #########################################
9 !
10 !!**** *READ_PGD_SEAFLUX_n* - routine to read SEAFLUX physiographic fields
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 !! V. Masson *Meteo France*
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 01/2003
37 !-------------------------------------------------------------------------------
38 !
39 !* 0. DECLARATIONS
40 ! ------------
41 !
42 !
43 !
44 !
48 USE modd_seaflux_n, ONLY : seaflux_t
49 USE modd_surf_atm_n, ONLY : surf_atm_t
50 !
52 !
53 USE modd_data_cover_par, ONLY : jpcover
54 !
56 !
58 USE modi_read_grid
59 USE modi_read_lcover
60 USE modi_read_pgd_seaflux_par_n
61 !
62 !
63 !
64 USE yomhook ,ONLY : lhook, dr_hook
65 USE parkind1 ,ONLY : jprb
66 !
67 USE modi_get_type_dim_n
68 !
69 IMPLICIT NONE
70 !
71 !* 0.1 Declarations of arguments
72 ! -------------------------
73 !
74 !
75 TYPE(data_cover_t), INTENT(INOUT) :: dtco
76 TYPE(data_seaflux_t), INTENT(INOUT) :: dts
77 TYPE(seaflux_grid_t), INTENT(INOUT) :: sg
78 TYPE(seaflux_t), INTENT(INOUT) :: s
79 TYPE(surf_atm_t), INTENT(INOUT) :: u
80 !
81  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! calling program
82 !
83 !* 0.2 Declarations of local variables
84 ! -------------------------------
85 !
86 INTEGER :: iresp ! Error code after redding
87 !
88  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
89 !
90 INTEGER :: iversion ! surface version
91 REAL(KIND=JPRB) :: zhook_handle
92 !
93 !-------------------------------------------------------------------------------
94 !
95 !* 1D physical dimension
96 !
97 IF (lhook) CALL dr_hook('READ_PGD_SEAFLUX_N',0,zhook_handle)
98 yrecfm='SIZE_SEA'
99  CALL get_type_dim_n(dtco, u, &
100  'SEA ',sg%NDIM)
101 !
102 !
103 !* 2. Physiographic data fields:
104 ! -------------------------
105 !
106 !* cover classes
107 !
108 ALLOCATE(s%LCOVER(jpcover))
109  CALL read_lcover(&
110  hprogram,s%LCOVER)
111 !
112 ALLOCATE(s%XCOVER(sg%NDIM,jpcover))
113  CALL read_surf_cov(&
114  hprogram,'COVER',s%XCOVER(:,:),s%LCOVER,iresp)
115 !
116 !* orography
117 !
118 ALLOCATE(s%XZS(sg%NDIM))
119 s%XZS(:) = 0.
120 !
121 yrecfm='VERSION'
122  CALL read_surf(&
123  hprogram,yrecfm,iversion,iresp)
124 !
125 !* bathymetry
126 !
127 ALLOCATE(s%XSEABATHY(sg%NDIM))
128 IF (iversion<=3) THEN
129  s%XSEABATHY(:) = -300.
130 ELSE
131  yrecfm='BATHY'
132  CALL read_surf(&
133  hprogram,yrecfm,s%XSEABATHY(:),iresp)
134 END IF
135 !
136 !* latitude, longitude
137 !
138 ALLOCATE(sg%XLAT (sg%NDIM))
139 ALLOCATE(sg%XLON (sg%NDIM))
140 ALLOCATE(sg%XMESH_SIZE(sg%NDIM))
141  CALL read_grid(&
142  hprogram,sg%CGRID,sg%XGRID_PAR,sg%XLAT,sg%XLON,sg%XMESH_SIZE,iresp)
143 !
144 !
145 !* sst
146 !
147 !
148 IF (iversion<3) THEN
149  dts%LSST_DATA = .false.
150 ELSE
151  yrecfm='SST_DATA'
152  CALL read_surf(&
153  hprogram,yrecfm,dts%LSST_DATA,iresp)
154 END IF
155 !
156 IF (dts%LSST_DATA) CALL read_pgd_seaflux_par_n(dtco, u, dts, sg, &
157  hprogram,sg%NDIM)
158 IF (lhook) CALL dr_hook('READ_PGD_SEAFLUX_N',1,zhook_handle)
159 !
160 !------------------------------------------------------------------------------!
161 END SUBROUTINE read_pgd_seaflux_n
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
subroutine read_grid(HPROGRAM, HGRID, PGRID_PAR, PLAT, PLON, PMESH_SIZE, KRESP, PDIR)
Definition: read_grid.F90:6
subroutine, public read_surf_cov(HPROGRAM, HREC, PFIELD, OFLAG, KRESP, HCOMMENT, HDIR)
subroutine read_lcover(HPROGRAM, OCOVER)
Definition: read_lcover.F90:6
subroutine read_pgd_seaflux_par_n(DTCO, U, DTS, SG, HPROGRAM, KSIZE, HDIR)
subroutine read_pgd_seaflux_n(DTCO, DTS, SG, S, U, HPROGRAM)