SURFEX v8.1
General documentation of Surfex
prep_hor_ocean_fields.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_hor_ocean_fields (DTCO, UG, U, GCP, O, OR, KLAT, PSEABATHY, &
7  HPROGRAM,HSURF,HFILE,HFILETYPE,KLUOUT,OUNIF)
8 ! #######################################################
9 !
10 !
11 !!**** *PREP_HOR_OCEAN_FIELDS* - prepares all oceanic fields for the 1D oceanic model
12 !!
13 !! PURPOSE
14 !! -------
15 !
16 !!** METHOD
17 !! ------
18 !!
19 !! REFERENCE
20 !! ---------
21 !!
22 !!
23 !! AUTHOR
24 !! ------
25 !! C. Lebeaupin Brossier
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 01/2008
30 !! Modified 07/2012, P. Le Moigne : CMO1D phasing
31 !!------------------------------------------------------------------
32 !
35 USE modd_surf_atm_n, ONLY : surf_atm_t
37 !
38 USE modd_ocean_n, ONLY : ocean_t
39 USE modd_ocean_rel_n, ONLY : ocean_rel_t
40 !
41 USE modd_surf_par, ONLY : xundef
42 USE modd_ocean_csts, ONLY : xrhoswref
44 !
45 USE modi_prep_hor_ocean_field
46 !
47 !
48 USE yomhook ,ONLY : lhook, dr_hook
49 USE parkind1 ,ONLY : jprb
50 !
51 IMPLICIT NONE
52 !
53 !* 0.1 declarations of arguments
54 !
55 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
56 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
57 TYPE(surf_atm_t), INTENT(INOUT) :: U
58 TYPE(grid_conf_proj_t),INTENT(INOUT) :: GCP
59 !
60 TYPE(ocean_t), INTENT(INOUT) :: O
61 TYPE(ocean_rel_t), INTENT(INOUT) :: OR
62 REAL, DIMENSION(:), INTENT(IN) :: PSEABATHY
63 INTEGER, INTENT(IN) :: KLAT
64 !
65  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
66  CHARACTER(LEN=7), INTENT(IN) :: HSURF ! type of field
67  CHARACTER(LEN=28), INTENT(IN) :: HFILE ! file name
68  CHARACTER(LEN=6), INTENT(IN) :: HFILETYPE ! file type
69 INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing
70 LOGICAL, INTENT(IN) :: OUNIF ! flag for prescribed uniform field
71 !
72 !
73 !* 0.2 declarations of local variables
74 !
75  CHARACTER(LEN=8) :: YSURF ! type of field
76  CHARACTER(LEN=28) :: YNCVARNAME ! variable to read
77 !
78 INTEGER :: IL ! number of points
79 INTEGER :: IK1
80 INTEGER :: J, JLEV ! loop counters
81 REAL(KIND=JPRB) :: ZHOOK_HANDLE
82 !---------------------------------------------------------------------------
83 !
84 !* 1. Patch
85 !
86 !---------------------------------------------------------------------------
87 !
88 !* 3. Treatment of oceanic temperature
89 IF (lhook) CALL dr_hook('PREP_HOR_OCEAN_FIELDS',0,zhook_handle)
90 ysurf='TEMP_OC'
91 yncvarname='temperature'
92  CALL prep_hor_ocean_field(dtco, ug, u, gcp, o, or, klat, &
93  hprogram,hfile,hfiletype,kluout,ounif,ysurf,yncvarname)
94 !---------------------------------------------------------------------------
95 !
96 !* 4. Treatment of oceanic salinity
97 ysurf='SALT_OC'
98 yncvarname='salinity'
99  CALL prep_hor_ocean_field(dtco, ug, u, gcp, o, or, klat, &
100  hprogram,hfile,hfiletype,kluout,ounif,ysurf,yncvarname)
101 !---------------------------------------------------------------------------
102 !
103 !* 5. Treatment of oceanic current
104 ysurf='UCUR_OC'
105 yncvarname='u'
106  CALL prep_hor_ocean_field(dtco, ug, u, gcp, o, or, klat, &
107  hprogram,hfile,hfiletype,kluout,ounif,ysurf,yncvarname)
108 ysurf='VCUR_OC'
109 yncvarname='v'
110  CALL prep_hor_ocean_field(dtco, ug, u, gcp, o, or, klat, &
111  hprogram,hfile,hfiletype,kluout,ounif,ysurf,yncvarname)
112 !---------------------------------------------------------------------------
113 !
114 ik1=nockmin+1
115 il = SIZE(o%XSEAT,1)
116 IF (il/=0) THEN
117  ALLOCATE(o%XSEAE (SIZE(o%XSEAT,1),nockmin:nockmax))
118  o%XSEAE(:,:) =1.e-3
119  ALLOCATE(o%XSEABATH (SIZE(o%XSEAT,1),nockmin:nockmax))
120  o%XSEABATH(:,:)=1.
121  ALLOCATE(o%XSEAHMO (SIZE(o%XSEAT,1)))
122  o%XSEAHMO(:) =xundef
123  ALLOCATE(o%XLE (SIZE(o%XSEAT,1),nockmin:nockmax))
124  ALLOCATE(o%XLK (SIZE(o%XSEAT,1),nockmin:nockmax))
125  ALLOCATE(o%XKMEL (SIZE(o%XSEAT,1),nockmin:nockmax))
126  ALLOCATE(o%XKMELM (SIZE(o%XSEAT,1),nockmin:nockmax))
127  o%XLE(:,:) =xundef
128  o%XLK(:,:) =xundef
129  o%XKMEL(:,:) =xundef
130  o%XKMELM(:,:) =xundef
131  ALLOCATE(o%XSEATEND (SIZE(o%XSEAT,1)))
132  o%XSEATEND(:) =xundef
133  !
134  ALLOCATE(o%XDTFNSOL (SIZE(o%XSEAT,1)))
135  o%XDTFNSOL(:) = xundef
136  ALLOCATE(o%XDTFSOL (SIZE(o%XSEAT,1),nockmin:nockmax))
137  o%XDTFSOL(:,:)= xundef
138 !!----------------------------------------------------------------------------
139 !!
140 !!* 6. Treatment of bathymetry indice and
141 !! apply bathy mask
142  DO j=1,il
143  DO jlev=ik1+1,nockmax
144  IF (pseabathy(j)-xzhoc(jlev)>0.) THEN
145  o%XSEABATH(j,jlev)=0.
146  o%XSEAE(j,jlev) = xundef
147  o%XSEAU(j,jlev) = xundef
148  o%XSEAV(j,jlev) = xundef
149  o%XSEAT(j,jlev) = xundef
150  o%XSEAS(j,jlev) = xundef
151  !
152  or%XSEAT_REL(j,jlev) = xundef
153  or%XSEAS_REL(j,jlev) = xundef
154  !
155  or%XSEAU_REL(j,jlev) = xundef
156  or%XSEAV_REL(j,jlev) = xundef
157  !
158  ENDIF
159  ENDDO
160  ENDDO
161 !
162 !---------------------------------------------------------------------------
163 ENDIF
164 IF (lhook) CALL dr_hook('PREP_HOR_OCEAN_FIELDS',1,zhook_handle)
165 !----------------------------------------------------------------------------
166 END SUBROUTINE prep_hor_ocean_fields
real, dimension(:), pointer xzhoc
subroutine prep_hor_ocean_field(DTCO, UG, U, GCP, O, OR, KLAT, HPROGRAM, HFILE, HFILETYPE, KLUOUT, OUNIF, HSURF, HNCVARNAME)
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
integer, save nockmax
subroutine prep_hor_ocean_fields(DTCO, UG, U, GCP, O, OR, KLAT, PSEABATHY, HPROGRAM, HSURF, HFILE, HFILETYPE, KLUOUT, OUNIF)
real, dimension(:), pointer xdz1
integer, save nockmin
real, save xrhoswref