SURFEX v8.1
General documentation of Surfex
prep_seaflux_extern.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 prep_seaflux_extern (GCP,HPROGRAM,HSURF,HFILE,HFILETYPE,HFILEPGD,HFILEPGDTYPE,KLUOUT,PFIELD)
7 ! #################################################################################
8 !
9 !
11 !
12 USE modd_surfex_mpi, ONLY : nrank,npio
13 !
15 !
16 USE modi_prep_grid_extern
18 USE modi_open_aux_io_surf
19 USE modi_close_aux_io_surf
20 !
21 USE modd_surf_par, ONLY : xundef
23 !
24 USE yomhook ,ONLY : lhook, dr_hook
25 USE parkind1 ,ONLY : jprb
26 !
27 IMPLICIT NONE
28 !
29 !* 0.1 declarations of arguments
30 !
31 TYPE(grid_conf_proj_t),INTENT(INOUT) :: GCP
32 !
33  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
34  CHARACTER(LEN=7), INTENT(IN) :: HSURF ! type of field
35  CHARACTER(LEN=28), INTENT(IN) :: HFILE ! name of file
36  CHARACTER(LEN=6), INTENT(IN) :: HFILETYPE ! type of input file
37  CHARACTER(LEN=28), INTENT(IN) :: HFILEPGD ! name of file
38  CHARACTER(LEN=6), INTENT(IN) :: HFILEPGDTYPE ! type of input file
39 INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing
40 REAL,DIMENSION(:,:), POINTER :: PFIELD ! field to interpolate horizontally
41 !
42 !* 0.2 declarations of local variables
43 !
44 !
45 REAL, DIMENSION(:), ALLOCATABLE :: ZMASK
46  CHARACTER(LEN=12) :: YRECFM ! Name of the article to be read
47 INTEGER :: IRESP ! reading return code
48 !
49 INTEGER :: INI ! total 1D dimension
50 INTEGER :: IVERSION ! total 1D dimension
51 REAL(KIND=JPRB) :: ZHOOK_HANDLE
52 !
53 !-------------------------------------------------------------------------------------
54 !
55 !* 1. Preparation of IO for reading in the file
56 ! -----------------------------------------
57 !
58 !* Note that all points are read, even those without physical meaning.
59 ! These points will not be used during the horizontal interpolation step.
60 ! Their value must be defined as XUNDEF.
61 !
62 IF (lhook) CALL dr_hook('PREP_SEAFLUX_EXTERN',0,zhook_handle)
63 !
64 !-------------------------------------------------------------------------------------
65 !
66 !* 2. Reading of grid
67 ! ---------------
68 !
69  CALL open_aux_io_surf(hfilepgd,hfilepgdtype,'FULL ')
70  CALL prep_grid_extern(gcp,hfilepgdtype,kluout,cingrid_type,cinterp_type,ini)
71 !
72 yrecfm='VERSION'
73  CALL read_surf(hfilepgdtype,yrecfm,iversion,iresp)
74 !
75 IF (nrank/=npio) ini = 0
76 !
77 ALLOCATE(zmask(ini))
78 IF (iversion>=7) THEN
79  yrecfm='FRAC_SEA'
80  CALL read_surf(hfilepgdtype,yrecfm,zmask,iresp,hdir='A')
81 ELSE
82  zmask(:) = 1.
83 ENDIF
84 !
85  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
86 !
87 IF (nrank/=npio) ini = 0
88 !---------------------------------------------------------------------------------------
89 SELECT CASE(hsurf)
90 !---------------------------------------------------------------------------------------
91 !
92 !* 3. Orography
93 ! ---------
94 !
95  CASE('ZS ')
96  ALLOCATE(pfield(ini,1))
97  pfield(:,:) = 0.
98 !
99 !* 4. Sea surface temperature
100 ! -----------------------
101 !
102  CASE('SST ')
103  ALLOCATE(pfield(ini,1))
104  yrecfm='SST'
105  CALL open_aux_io_surf(hfile,hfiletype,'SEA ')
106  CALL read_surf(hfiletype,yrecfm,pfield(:,1),iresp,hdir='E')
107  CALL close_aux_io_surf(hfile,hfiletype)
108  WHERE (zmask(:)==0.) pfield(:,1) = xundef
109 !
110 !* 5. Sea surface salinity
111 ! --------------------
112 !
113  CASE('SSS ')
114  ALLOCATE(pfield(ini,1))
115  yrecfm='SSS'
116  CALL open_aux_io_surf(hfile,hfiletype,'FULL ')
117  CALL read_surf(hfiletype,'VERSION',iversion,iresp)
118  CALL close_aux_io_surf(hfile,hfiletype)
119  IF(iversion>=8)THEN
120  CALL open_aux_io_surf(hfile,hfiletype,'SEA ')
121  CALL read_surf(hfiletype,yrecfm,pfield(:,1),iresp,hdir='E')
122  CALL close_aux_io_surf(hfile,hfiletype)
123  WHERE (zmask(:)==0.) pfield(:,1) = xundef
124  ELSE
125  pfield = 0.0
126  ENDIF
127 !
128 !* 6. Sea ice fraction
129 ! ----------------
130 !
131  CASE('SIC ')
132  ALLOCATE(pfield(ini,1))
133  pfield = 0.0
134 !
135 !---------------------------------------------------------------------------------------
136 END SELECT
137 !-------------------------------------------------------------------------------------
138 !
139 DEALLOCATE(zmask)
140 !
141 !* 6. End of IO
142 ! ---------
143 !
144 IF (lhook) CALL dr_hook('PREP_SEAFLUX_EXTERN',1,zhook_handle)
145 !
146 !---------------------------------------------------------------------------------------
147 !
148 END SUBROUTINE prep_seaflux_extern
character(len=10) cingrid_type
Definition: modd_prep.F90:39
character(len=6) cinterp_type
Definition: modd_prep.F90:40
subroutine close_aux_io_surf(HFILE, HFILETYPE)
subroutine prep_grid_extern(GCP, HFILETYPE, KLUOUT, HGRIDTYPE, HINTER
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine prep_seaflux_extern(GCP, HPROGRAM, HSURF, HFILE, HFILETYPE, HFILEPGD, HFILEPGDTYPE, KLUOUT, PFIELD)
subroutine open_aux_io_surf(HFILE, HFILETYPE, HMASK, HDIR)