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