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.
zoom.F90 in branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/TOOLS/DMP_TOOLS/src – NEMO

source: branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/TOOLS/DMP_TOOLS/src/zoom.F90 @ 7261

Last change on this file since 7261 was 7261, checked in by cbricaud, 7 years ago

phaze the rest of NEMOGCM directory ( all except NEMO directory) of the CRS branch with nemo_v3_6_STABLE branch at rev 7213 (09-09-2016) (merge -r 5519:7213 )

File size: 3.7 KB
Line 
1MODULE zoom
2   
3   USE utils
4
5   CONTAINS
6
7   SUBROUTINE dtacof_zoom( presto, mask)
8      !!----------------------------------------------------------------------
9      !!                  ***  ROUTINE dtacof_zoom  ***
10      !!
11      !! ** Purpose :   Compute the damping coefficient for zoom domain
12      !!
13      !! ** Method  : - set along closed boundary due to zoom a damping over
14      !!                6 points with a max time scale of 5 days.
15      !!              - ORCA arctic/antarctic zoom: set the damping along
16      !!                south/north boundary over a latitude strip.
17      !!
18      !! ** Action  : - resto, the damping coeff. for T and S
19      !!----------------------------------------------------------------------
20      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout)  ::   presto   ! restoring coeff. (s-1)
21      REAL(wp), DIMENSION(jpi,jpj), INTENT(in)  ::   mask   ! restoring coeff. (s-1)
22      !
23      INTEGER  ::   ji, jj, jn   ! dummy loop indices
24      REAL(wp) ::   zlat, zlat0, zlat1, zlat2, z1_5d   ! local scalar
25      REAL(wp), DIMENSION(6)  ::   zfact               ! 1Dworkspace
26
27      !Namelist variables
28      LOGICAL :: lzoom_w, lzoom_e, lzoom_n, lzoom_s 
29      NAMELIST/nam_zoom_dmp/lzoom_n,lzoom_e,lzoom_w,lzoom_s
30      !!----------------------------------------------------------------------
31     
32      ! Read namelist
33      OPEN( UNIT=numnam, FILE='namelist', FORM='FORMATTED', STATUS='OLD' )
34      READ( numnam, nam_dmp_create )
35      CLOSE( numnam )
36
37      zfact(1) =  1._wp
38      zfact(2) =  1._wp
39      zfact(3) = 11._wp / 12._wp
40      zfact(4) =  8._wp / 12._wp
41      zfact(5) =  4._wp / 12._wp
42      zfact(6) =  1._wp / 12._wp
43      zfact(:) = zfact(:) / ( 5._wp * rday )    ! 5 days max restoring time scale
44
45      presto(:,:) = 0._wp
46
47      ! damping along the forced closed boundary over 6 grid-points
48      DO jn = 1, 6
49         IF( lzoom_w )   presto( jn, : )                    = zfact(jn)   ! west  closed
50         IF( lzoom_s )   presto( : , jn )                    = zfact(jn)   ! south closed
51         IF( lzoom_e )   presto( jpi+1-jn , : ) = zfact(jn)   ! east  closed
52         IF( lzoom_n )   presto( : , jpj+1-jn ) = zfact(jn)   ! north closed
53      END DO
54
55      !                                           ! ====================================================
56      IF( cp_cfz == "arctic" .OR. cp_cfz == "antarctic" ) THEN   !  ORCA configuration : arctic or antarctic zoom
57         !                                        ! ====================================================
58         WRITE(numout,*)
59         IF(cp_cfz == "arctic" ) WRITE(numout,*) '              dtacof_zoom : ORCA    Arctic zoom'
60         IF(cp_cfz == "antarctic" ) WRITE(numout,*) '           dtacof_zoom : ORCA Antarctic zoom'
61         WRITE(numout,*)
62         !
63         !                          ! Initialization :
64         presto(:,:) = 0._wp
65         zlat0 = 10._wp                     ! zlat0 : latitude strip where resto decreases
66         zlat1 = 30._wp                     ! zlat1 : resto = 1 before zlat1
67         zlat2 = zlat1 + zlat0              ! zlat2 : resto decreases from 1 to 0 between zlat1 and zlat2
68         z1_5d = 1._wp / ( 5._wp * rday )   ! z1_5d : 1 / 5days
69
70         DO jj = 1, jpj
71            DO ji = 1, jpi
72               zlat = ABS( gphit(ji,jj) )
73               IF( zlat1 <= zlat .AND. zlat <= zlat2 ) THEN
74                  presto(ji,jj) = 0.5_wp * z1_5d * (  1._wp - COS( rpi*(zlat2-zlat)/zlat0 )  ) 
75               ELSEIF( zlat < zlat1 ) THEN
76                  presto(ji,jj) = z1_5d
77               ENDIF
78            END DO
79         END DO
80         !
81      ENDIF
82      !                             ! Mask resto array
83      presto(:,:) = presto(:,:) * mask(:,:)
84
85   END SUBROUTINE dtacof_zoom
86
87END MODULE zoom
Note: See TracBrowser for help on using the repository browser.