SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
mod1dn.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 mod1d_n (DGO, O, OR, SG, S, &
7  hprogram,ptime,pemis,pdir_alb,psca_alb,plw,psca_sw,&
8  pdir_sw, psfth,psftq,psfu,psfv,prain,psst )
9 ! #######################################################################
10 !
11 !!**** *MOD1D_n*
12 !!
13 !! PURPOSE
14 !! -------
15 ! Source that exchanges Fluxes and SST between SURFEX (coupling_seaflux)
16 ! and the oceanic 1D model in TKE eqations (mixtl_n)
17 !
18 !!** METHOD
19 !! ------
20 ! Change turbulent fluxes in solar, non solar, and fresh water fluxes
21 ! with the oceanic convention for orientation of fluxes
22 ! The stress of wind is exchange between SURFEX and TKE model
23 !
24 !! EXTERNAL
25 !! --------
26 !!
27 !! IMPLICIT ARGUMENTS
28 !! ------------------
29 !!
30 !! REFERENCE
31 !! ---------
32 !!
33 !!
34 !! AUTHOR
35 !! ------
36 !! C. Lebeaupin *Météo-France*
37 !!
38 !! MODIFICATIONS
39 !! -------------
40 !! Original 02/2008
41 !! Modified 07/2012, P. Le Moigne : CMO1D phasing
42 !-------------------------------------------------------------------------------
43 !
44 !* 0. DECLARATIONS
45 ! ------------
46 !
47 !
48 !
49 !
51 USE modd_ocean_n, ONLY : ocean_t
52 USE modd_ocean_rel_n, ONLY : ocean_rel_t
54 USE modd_seaflux_n, ONLY : seaflux_t
55 !
56 USE modd_csts
58 USE modd_surf_par, ONLY : xundef
59 !
60 USE modi_mixtl_n
61 USE modi_diag_inline_ocean_n
62 !
63 USE modi_get_luout
64 !
65 !
66 USE yomhook ,ONLY : lhook, dr_hook
67 USE parkind1 ,ONLY : jprb
68 !
69 IMPLICIT NONE
70 !
71 !* 0.1 declarations of arguments
72 !
73 !
74 !
75 TYPE(diag_ocean_t), INTENT(INOUT) :: dgo
76 TYPE(ocean_t), INTENT(INOUT) :: o
77 TYPE(ocean_rel_t), INTENT(INOUT) :: or
78 TYPE(seaflux_grid_t), INTENT(INOUT) :: sg
79 TYPE(seaflux_t), INTENT(INOUT) :: s
80 !
81  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling surf. schemes
82 REAL ,INTENT(IN) :: ptime ! current time since midnight in second
83 REAL, DIMENSION(:) ,INTENT(IN) :: pemis ! emissivity
84 REAL, DIMENSION(:,:),INTENT(IN) :: pdir_alb ! direct albedo
85 REAL, DIMENSION(:,:),INTENT(IN) :: psca_alb ! scattered albedo
86 REAL, DIMENSION(:) ,INTENT(IN) :: plw ! longwave radiation on horizontal surface (W/m2)
87 REAL, DIMENSION(:,:),INTENT(IN) :: psca_sw ! diffuse solar radiation on horizontal surface (W/m2)
88 REAL, DIMENSION(:,:),INTENT(IN) :: pdir_sw ! direct solar radiation on horizontal surface (W/m2)
89 REAL, DIMENSION(:) ,INTENT(IN) :: psfth ! flux of heat (W/m2)
90 REAL, DIMENSION(:) ,INTENT(IN) :: psftq ! flux of water vapor (kg/m2/s)
91 REAL, DIMENSION(:) ,INTENT(IN) :: psfu ! zonal stress (Pa)
92 REAL, DIMENSION(:) ,INTENT(IN) :: psfv ! meridian stress (Pa)
93 REAL, DIMENSION(:) ,INTENT(IN) :: prain ! liquid precipitation (kg/s/m2)
94 !
95 REAL, DIMENSION(:) ,INTENT(INOUT) :: psst ! sea surface temperature (K)
96 !
97 !* 0.2 declarations of local variables
98 !
99 INTEGER :: jpt
100 INTEGER :: itime,nocean_step
101 REAL, DIMENSION(SIZE(PSFTH)) :: zfsol,zfnsol !total solar and non-solar fluxes (W/m2)
102 REAL, DIMENSION(SIZE(PSFTH)) :: zsfteau !fresh water flux(kg/m2/s)
103 REAL, DIMENSION(SIZE(PSFTH)) :: zlv !latent heat
104 !
105 REAL, DIMENSION(SIZE(PSFTH)) :: zlwu !long waves upward fluxes (W/m2)
106 REAL, DIMENSION(SIZE(PDIR_ALB,1),SIZE(PDIR_ALB,2)) :: zswu
107  !shortwave upward fluxes (W/m2)
108 !
109 REAL, DIMENSION(SIZE(PSFTH)) :: zseatemp !surface temperature (K)
110 !
111 LOGICAL :: gcallmixt, gtimeok
112 INTEGER :: iluout ! output listing logical unit
113 REAL(KIND=JPRB) :: zhook_handle
114 !
115 !-------------------------------------------------------------------------------
116 !
117 IF (lhook) CALL dr_hook('MOD1D_N',0,zhook_handle)
118 !
119  CALL get_luout(hprogram,iluout)
120 !
121 itime=int(ptime)
122 nocean_step=int(o%XOCEAN_TSTEP)
123 !
124 gtimeok=(mod(itime,nocean_step)==0)
125 gcallmixt=((mod(itime,nocean_step)==0).AND.(o%NOCTCOUNT>0))
126 !
127 !Call 1D model if ptime proportional to the oceanic model time step
128 !
129 IF (gcallmixt) THEN
130 !
131 ! 1. Initializations
132 !________________________________________________________________________
133 !Computation of solar, non solar and fresh water fluxes
134  DO jpt=1,SIZE(psfth)
135  !SW Flux up
136  zswu(jpt,:)= pdir_sw(jpt,:) * pdir_alb(jpt,:) + psca_sw(jpt,:)*psca_alb(jpt,:)
137  !Net solar flux
138  zfsol(jpt)=(sum(pdir_sw(jpt,:))+sum(psca_sw(jpt,:))-sum(zswu(jpt,:)))/(xrhosw*xcpsw)
139  !Calcul flux LW UP
140  zlwu(jpt)= pemis(jpt)*xstefan*psst(jpt)**4 + (1-pemis(jpt))*plw(jpt)
141 
142  IF (psst(jpt)<=(xtt-2)) THEN
143  zfnsol(jpt)=(plw(jpt)-zlwu(jpt)-psfth(jpt)-(xlstt*psftq(jpt)))/(xrhosw*xcpsw)
144  zsfteau(jpt)=psftq(jpt)/xrhoswref
145  ELSE
146  zlv(jpt)=xlvtt+(xcpv-xcl)*(psst(jpt)-xtt)
147  zfnsol(jpt)=(plw(jpt)-zlwu(jpt)-psfth(jpt)-(zlv(jpt)*psftq(jpt)))/(xrhosw*xcpsw)
148  zsfteau(jpt)=(psftq(jpt)-prain(jpt))/xrhoswref
149  ENDIF
150  ENDDO
151 !__________________________________________________________________________
152 !
153 ! 2. Call oceanic TKE model
154 ! ----------------------
155 !
156  IF (or%LFLUX_NULL) THEN
157  WRITE(iluout,*) 'Caution : SURFACE FLUX ARE SET TO 0 '
158  zfsol(:) = 0.
159  zfnsol(:) = 0.
160  zsfteau(:) = 0.
161  END IF
162 
163  CALL mixtl_n(o, or, sg, &
164  zfsol,zfnsol,zsfteau,psfu,psfv,zseatemp)
165 !
166 !---------------------------------------------------------------------------
167 ! 3. Coupling with SURFEX by SST (and relative wind) evolution
168 !
169  IF (o%LPROGSST) THEN
170  psst(:)=zseatemp(:)
171  !WRITE(ILUOUT,*) '**SST CHANGED FOR THE ',NOCTCOUNT,'TIME BY FIRST LEVEL OCEANIC MODEL TEMPERATURE AT ', ITIME,' s **'
172  ENDIF
173  !
174 ENDIF
175 !
176 IF (gtimeok) THEN
177  CALL diag_inline_ocean_n(dgo, o, s)
178  o%NOCTCOUNT=o%NOCTCOUNT+1
179 ENDIF
180 !
181 IF (lhook) CALL dr_hook('MOD1D_N',1,zhook_handle)
182 !!-------------------------------------------------------------------------------
183 !!-----------------------------------------------------------------------------
184 END SUBROUTINE mod1d_n
subroutine diag_inline_ocean_n(DGO, O, S)
subroutine mixtl_n(O, OR, SG, PFSOL, PFNSOL, PSFTEAU, PSFU, PSFV, PSEATEMP)
Definition: mixtln.F90:6
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine mod1d_n(DGO, O, OR, SG, S, HPROGRAM, PTIME, PEMIS, PDIR_ALB, PSCA_ALB, PLW, PSCA_SW, PDIR_SW, PSFTH, PSFTQ, PSFU, PSFV, PRAIN, PSST)
Definition: mod1dn.F90:6