New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
cyclone.F90 in branches/2012/dev_r3438_LOCEAN15_PISLOB/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2012/dev_r3438_LOCEAN15_PISLOB/NEMOGCM/NEMO/OPA_SRC/SBC/cyclone.F90 @ 3556

Last change on this file since 3556 was 3556, checked in by cetlod, 11 years ago

branch:2012/dev_r3438_LOCEAN15_PISLOB add the Tropical Cyclones module

File size: 14.7 KB
RevLine 
[3556]1MODULE cyclone
2   !!======================================================================
3   !!                       ***  MODULE  cyclone  ***
4   !! add the Tropical Cyclones along tracks to the surface wind forcing
5   !!                 
6   !!======================================================================
7   !! History : 3.3  ! 2010-05  (E Vincent, G Madec, S Masson)  Original code
8   !!----------------------------------------------------------------------
9
10#if defined key_cyclone
11   !!----------------------------------------------------------------------
12   !!  'key_cyclone' : key option add Tropical Cyclones in the wind forcing
13   !!----------------------------------------------------------------------
14   !!   wnd_cyc      : 1 module subroutine
15   !!----------------------------------------------------------------------
16   USE oce             ! ocean dynamics and active tracers
17   USE sbc_oce         ! surface boundary condition: ocean
18   USE dom_oce         ! ocean space domain variables
19   USE phycst          ! physical constant
20   USE fldread         ! read input fields
21   USE in_out_manager  ! I/O manager
22   USE geo2ocean       ! tools for projection on ORCA grid
23   USE lib_mpp       
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC   wnd_cyc   ! routine called in sbcblk_core.F90 module
29
30   INTEGER , PARAMETER ::   jp_is1  = 1   ! index of presence 1 or absence 0 of a TC record
31   INTEGER , PARAMETER ::   jp_lon  = 2   ! index of longitude for present TCs
32   INTEGER , PARAMETER ::   jp_lat  = 3   ! index of latitude  for present TCs
33   INTEGER , PARAMETER ::   jp_vmax = 4   ! index of max wind  for present TCs
34   INTEGER , PARAMETER ::   jp_pres = 5   ! index of eye-pres  for present TCs
35
36   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf   ! structure of input fields (file informations, fields read)
37
38   !! * Substitutions
39#  include "vectopt_loop_substitute.h90"
40   !!----------------------------------------------------------------------
41   !! NEMO/OPA 3.3 , LOCEAN-IPSL (2010)
42   !! $Id: module_example 1146 2008-06-25 11:42:56Z rblod $
43   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
44   !!----------------------------------------------------------------------
45
46CONTAINS
47
48   SUBROUTINE wnd_cyc( kt, pwnd_i, pwnd_j, ptmask_tc )
49      !!----------------------------------------------------------------------
50      !!                    ***  ROUTINE wnd_cyc  ***
51      !!
52      !! ** Purpose :  Add cyclone winds on the ORCA grid
53      !!
54      !! ** Action  : - open TC data, find TCs for the current timestep
55      !!              - for each potential TC, add the winds on the grid
56      !!----------------------------------------------------------------------
57      INTEGER , INTENT(in)                      ::   kt       ! time step index
58      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) ::   pwnd_i   ! wind speed i-components at T-point ORCA direction
59      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) ::   pwnd_j   ! wind speed j-components at T-point ORCA direction
60      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) ::   ptmask_tc ! mask = 1 where TC are added
61      ! add Manu !
62     
63      !!
64      INTEGER  ::   ji, jj , jtc        ! loop arguments
65      INTEGER  ::   ierror              ! loop arguments
66      INTEGER  ::   vortex=1            ! vortex shape to be used: 0=Holland 1=Willoughby
67      REAL(wp) ::   zrout1=1.5e6        ! distance from center where we begin to kill vortex (m)
68      REAL(wp) ::   zrout2=2.5e6        ! distance from center where we bring vortex to zero (m)
69      REAL(wp) ::   zb                  ! power in Holland vortex shape
70      REAL(wp) ::   zA                  ! shape parameter in Willoughby vortex : A transtion between first and second outter exp
71      REAL(wp) ::   zn                  ! shape parameter in Willoughby vortex : n power law in the eye
72      REAL(wp) ::   zXX1                ! shape parameter in Willoughby vortex : decay length second outter exponential
73      REAL(wp) ::   zXX2                ! shape parameter in Willoughby vortex : decay length first  outter exponential
74      REAL(wp) ::   zztmp               ! temporary
75      REAL(wp) ::   zzrglam, zzrgphi    ! temporary
76      REAL(wp) ::   ztheta              ! azimuthal angle
77      REAL(wp) ::   zdist               ! dist to the TC center
78      REAL(wp) ::   zhemi               ! 1 for NH ;  -1 for SH
79      REAL(wp) ::   zinfl               ! clim inflow angle in TCs
80      REAL(wp) ::   zrmw                ! mean radius of Max wind of a tropical cyclone (Willoughby 2004) [m]
81      REAL(wp) ::   zwnd_r, zwnd_t      ! radial and tangential components of the wind
82      REAL(wp), DIMENSION(jpi,jpj) ::   zwnd_x, zwnd_y   ! zonal and meridional components of the wind
83
84      REAL(wp), DIMENSION(14,5)    ::   ztct                ! tropical cyclone track data at kt
85      REAL(wp)                     ::   zvmax               ! timestep interpolated vmax
86      REAL(wp)                     ::   zrlon, zrlat        ! temporary
87      !!
88      CHARACTER(len=100) ::  cn_dir            ! Root directory for location of files
89      TYPE(FLD_N), DIMENSION(1) ::   slf_i     ! array of namelist informations on the TC position
90      TYPE(FLD_N) ::   sn_tc                   ! informations about the fields to be read
91      !      NAMELIST/namsbc_tc/ cn_dir , sn_tc
92      !!--------------------------------------------------------------------
93
94
95      !                                         ! ====================== !
96      IF( kt == nit000 ) THEN                   !  First call kt=nit000  !
97         !                                      ! ====================== !
98         ! set file information (default values)
99         cn_dir = './'       ! directory in which the model is executed
100         !
101         ! (NB: frequency positive => hours, negative => months)
102         !          !    file     ! frequency !  variable ! time intep !  clim   ! 'yearly' or ! weights  ! rotation   !
103         !          !    name     !  (hours)  !   name    !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs      !
104         sn_tc = FLD_N( 'tc_track',     6     ,  'tc'     ,  .true.    , .false. ,   'yearly'  , ''       , ''         )
105         !
106         !         REWIND( numnam )                    ! ... read in namlist namsbc_core
107         !         READ  ( numnam, namsbc_tc )
108         !
109         ! set sf structure
110         ALLOCATE( sf(1), STAT=ierror )
111         IF( ierror > 0 ) THEN
112            CALL ctl_stop( 'wnd_cyc: unable to allocate sf structure' )   ;   RETURN
113         ENDIF
114         ALLOCATE( sf(1)%fnow(14,5,1) )
115         ALLOCATE( sf(1)%fdta(14,5,2,1) )
116         slf_i(1) = sn_tc
117         !
118         ! fill sf with slf_i and control print
119         CALL fld_fill( sf, slf_i, cn_dir, 'sbc_blk_tc', 'tropical cyclone track', 'namsbc_tc' )
120         !
121      ENDIF
122
123
124      !       Interpolation of lon lat vmax... at the current timestep
125      !       ***************************************************************
126
127      CALL fld_read( kt, nn_fsbc, sf )                   ! input fields provided at the current time-step
128
129      ztct(:,:) = sf(1)%fnow(:,:,1)
130
131      !       Add TC wind on the grid
132      !       ***************************************************************
133
134      zwnd_x(:,:) = 0.e0 
135      zwnd_y(:,:) = 0.e0 
136     
137      ptmask_tc(:,:) = 0.e0 
138      ! add Manu !
139 
140      DO jtc = 1, 14
141         !
142         IF( ztct(jtc,jp_is1) == 1 ) THEN                ! cyclone is defined in this slot ? yes--> begin
143
144            zvmax =       ztct(jtc,jp_vmax)
145            zrlon = rad * ztct(jtc,jp_lon )
146            zrlat = rad * ztct(jtc,jp_lat )
147            zhemi = SIGN( 1. , zrlat )
148            zinfl = 15.* rad                             ! clim inflow angle in Tropical Cyclones
149         IF ( vortex == 0 ) THEN
150
151            ! Vortex Holland reconstruct wind at each lon-lat position
152            ! ********************************************************
153            zrmw = 51.6 * EXP( -0.0223*zvmax + 0.0281* ABS( ztct(jtc,jp_lat) ) ) * 1000.
154            ! climatological ZRMW of cyclones as a function of wind and latitude (Willoughby 2004)             
155            ! zb = 1.0036 + 0.0173 * zvmax - 0.0313 * LOG(zrmw/1000.) + 0.0087 * ABS( ztct(jtc,jp_lat) )
156            ! fitted B parameter (Willoughby 2004)
157            zb = 2.
158
159            DO jj = 1, jpj
160               DO ji = 1, jpi
161
162                  ! calc distance between TC center and any point following great circle
163                  ! source : http://www.movable-type.co.uk/scripts/latlong.html
164                  zzrglam = rad * glamt(ji,jj) - zrlon
165                  zzrgphi = rad * gphit(ji,jj)
166                  zdist = ra * ACOS(  SIN( zrlat ) * SIN( zzrgphi )   &
167                     &              + COS( zrlat ) * COS( zzrgphi ) * COS( zzrglam ) )
168
169                 IF (zdist < zrout2) THEN ! calculation of wind only to a given max radius
170                  ! shape of the wind profile
171                  zztmp = ( zrmw / ( zdist + 1.e-12 ) )**zb
172                  zztmp =  zvmax * SQRT( zztmp * EXP(1. - zztmp) )   
173
174                  IF (zdist > zrout1) THEN ! bring to zero between r_out1 and r_out2
175                     zztmp = zztmp * ( (zrout2-zdist)*1.e-6 )
176                  ENDIF
177
178                  ! !!! KILL EQ WINDS
179                  ! IF (SIGN( 1. , zrlat ) /= zhemi) THEN
180                  !    zztmp = 0.                              ! winds in other hemisphere
181                  !    IF (ABS(gphit(ji,jj)) <= 5.) zztmp=0.   ! kill between 5N-5S
182                  ! ENDIF
183                  ! IF (ABS(gphit(ji,jj)) <= 10. .and. ABS(gphit(ji,jj)) > 5.) THEN
184                  !    zztmp = zztmp * ( 1./5. * (ABS(gphit(ji,jj)) - 5.) )
185                  !    !linear to zero between 10 and 5
186                  ! ENDIF
187                  ! !!! / KILL EQ
188
189                  IF (ABS(gphit(ji,jj)) >= 55.) zztmp = 0. ! kill weak spurious winds at high latitude
190
191                  zwnd_t =   COS( zinfl ) * zztmp   
192                  zwnd_r = - SIN( zinfl ) * zztmp
193
194                  ! Project radial-tangential components on zonal-meridional components
195                  ! -------------------------------------------------------------------
196                 
197                  ! ztheta = azimuthal angle of the great circle between two points
198                  zztmp = COS( zrlat ) * SIN( zzrgphi ) &
199                     &  - SIN( zrlat ) * COS( zzrgphi ) * COS( zzrglam )
200                  ztheta = ATAN2(        COS( zzrgphi ) * SIN( zzrglam ) , zztmp )
201
202                  zwnd_x(ji,jj) = zwnd_x(ji,jj) - zhemi * COS(ztheta)*zwnd_t + SIN(ztheta)*zwnd_r
203                  zwnd_y(ji,jj) = zwnd_y(ji,jj) + zhemi * SIN(ztheta)*zwnd_t + COS(ztheta)*zwnd_r
204
205                  ptmask_tc(ji,jj) = 1. !MAX( 1., ptmask_tc(ji,jj) )
206                  ! add Manu !
207 
208
209                 ENDIF
210               END DO
211            END DO
212         
213         ELSE IF ( vortex == 1 ) THEN
214
215            ! Vortex Willoughby reconstruct wind at each lon-lat position
216            ! ***********************************************************
217            zrmw = 46.4 * EXP( -0.0155*zvmax + 0.0169* ABS( ztct(jtc,jp_lat) ) )*1000.
218            ! climatological ZRMW of cyclones as a function of wind and latitude (Willoughby 2006)
219            zXX2 = 25.*1000.                                              ! 25km fixed "near-eye" exponential decay
220            zXX1 = ( 287.6  - 1.942 *zvmax + 7.799 *LOG(zrmw/1000.) + 1.819 *ABS( ztct(jtc,jp_lat) ) )*1000.   
221            zn   =   2.1340 + 0.0077*zvmax - 0.4522*LOG(zrmw/1000.) - 0.0038*ABS( ztct(jtc,jp_lat) )           
222            zA   =   0.5913 + 0.0029*zvmax - 0.1361*LOG(zrmw/1000.) - 0.0042*ABS( ztct(jtc,jp_lat) ) 
223            IF (zA < 0) THEN
224               zA=0
225            ENDIF           
226       
227            DO jj = 1, jpj
228               DO ji = 1, jpi
229                                 
230                  zzrglam = rad * glamt(ji,jj) - zrlon
231                  zzrgphi = rad * gphit(ji,jj)
232                  zdist = ra * ACOS(  SIN( zrlat ) * SIN( zzrgphi )   &
233                     &              + COS( zrlat ) * COS( zzrgphi ) * COS( zzrglam ) )
234
235                 IF (zdist < zrout2) THEN ! calculation of wind only to a given max radius
236               
237                  ! shape of the wind profile                     
238                  IF (zdist <= zrmw) THEN     ! inside the Radius of Maximum Wind
239                     zztmp  = zvmax * (zdist/zrmw)**zn
240                  ELSE
241                     zztmp  = zvmax * ( (1-zA) * EXP(- (zdist-zrmw)/zXX1 ) + zA * EXP(- (zdist-zrmw)/zXX2 ) )
242                  ENDIF
243
244                  IF (zdist > zrout1) THEN ! bring to zero between r_out1 and r_out2
245                     zztmp = zztmp * ( (zrout2-zdist)*1.e-6 )
246                  ENDIF
247
248                  ! !!! KILL EQ WINDS
249                  ! IF (SIGN( 1. , zrlat ) /= zhemi) THEN
250                  !    zztmp = 0.                              ! winds in other hemisphere
251                  !    IF (ABS(gphit(ji,jj)) <= 5.) zztmp=0.   ! kill between 5N-5S
252                  ! ENDIF
253                  ! IF (ABS(gphit(ji,jj)) <= 10. .and. ABS(gphit(ji,jj)) > 5.) THEN
254                  !    zztmp = zztmp * ( 1./5. * (ABS(gphit(ji,jj)) - 5.) )
255                  !    !linear to zero between 10 and 5
256                  ! ENDIF
257                  ! !!! / KILL EQ
258
259                  IF (ABS(gphit(ji,jj)) >= 55.) zztmp = 0. ! kill weak spurious winds at high latitude
260
261                  zwnd_t =   COS( zinfl ) * zztmp   
262                  zwnd_r = - SIN( zinfl ) * zztmp
263
264                  ! Project radial-tangential components on zonal-meridional components
265                  ! -------------------------------------------------------------------
266                 
267                  ! ztheta = azimuthal angle of the great circle between two points
268                  zztmp = COS( zrlat ) * SIN( zzrgphi ) &
269                     &  - SIN( zrlat ) * COS( zzrgphi ) * COS( zzrglam )
270                  ztheta = ATAN2(        COS( zzrgphi ) * SIN( zzrglam ) , zztmp )
271
272                  zwnd_x(ji,jj) = zwnd_x(ji,jj) - zhemi * COS(ztheta)*zwnd_t + SIN(ztheta)*zwnd_r
273                  zwnd_y(ji,jj) = zwnd_y(ji,jj) + zhemi * SIN(ztheta)*zwnd_t + COS(ztheta)*zwnd_r
274                 
275                  ptmask_tc(ji,jj) = 1. !MAX( 1., ptmask_tc(ji,jj) )
276                  ! add Manu !
277 
278                 ENDIF
279               END DO
280            END DO
281         ENDIF                                         ! / vortex Holland or Wiloughby
282         ENDIF                                           ! / cyclone is defined in this slot ? yes--> begin
283      END DO ! / end simultaneous cyclones loop
284
285      CALL rot_rep ( zwnd_x, zwnd_y, 'T', 'en->i', pwnd_i ) !rotation of components on ORCA grid
286      CALL rot_rep ( zwnd_x, zwnd_y, 'T', 'en->j', pwnd_j ) !rotation of components on ORCA grid
287
288
289   END SUBROUTINE wnd_cyc
290
291#endif
292
293   !!======================================================================
294END MODULE cyclone
Note: See TracBrowser for help on using the repository browser.