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.
Changeset 6583 for branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/usrdef.F90 – NEMO

Ignore:
Timestamp:
2016-05-20T11:10:37+02:00 (8 years ago)
Author:
flavoni
Message:

add module for sbc gyre in usr_def module , see ticket #1692

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/usrdef.F90

    r6579 r6583  
    22   !!============================================================================== 
    33   !!                       ***  MODULE usrdef   *** 
    4    !! User defined module: used like example to define init, sbc, bathy, ... 
     4   !! User defined module: used like example to define domain, init, sbc, ... 
    55   !!============================================================================== 
    66   !! History :  NEMO ! 2016-03  (S. Flavoni)  
     
    1010   !!   usr_def_hgr       : initialize the horizontal mesh  
    1111   !!   usr_def_ini       : initial state  
    12    !!   usr_def_sbc       : initialize the surface bounday conditions 
    1312   !!---------------------------------------------------------------------- 
    1413   USE step_oce       ! module used in the ocean time stepping module (step.F90) 
     
    2928CONTAINS 
    3029 
    31    SUBROUTINE usr_def_hgr( nbench, jp_cfg, kff    , pff   , & ! Coriolis parameter  (if domain not on the sphere) 
    32            &               pglamt, pglamu, pglamv , pglamf, & ! gridpoints position (required) 
    33            &               pgphit, pgphiu, pgphiv , pgphif, & !          
    34            &               pe1t  , pe1u  , pe1v   , pe1f  , & ! scale factors (required) 
    35            &               pe2t  , pe2u  , pe2v   , pe2f  , & ! 
    36            &               ke1e2u_v                       )   ! u- & v-surfaces (if gridsize reduction is used in strait(s)) 
    37       !!------------------------------------------------------------------------------------------------- 
     30   SUBROUTINE usr_def_hgr( kbench, k_cfg , kff    , pff   , & ! Coriolis parameter  (if domain not on the sphere) 
     31      &                    pglamt, pglamu, pglamv , pglamf, & ! gridpoints position (required) 
     32      &                    pgphit, pgphiu, pgphiv , pgphif, & !          
     33      &                    pe1t  , pe1u  , pe1v   , pe1f  , & ! scale factors (required) 
     34      &                    pe2t  , pe2u  , pe2v   , pe2f  , & ! 
     35      &                    ke1e2u_v                       )   ! u- & v-surfaces (if gridsize reduction is used in strait(s)) 
     36      !!---------------------------------------------------------------------- 
    3837      !!                  ***  ROUTINE usr_def_hgr  *** 
    3938      !! 
     
    5251      !!              - define i- & j-scale factors at t-, u-, v- and f-points (in meters) 
    5352      !!              - define u- & v-surfaces (if gridsize reduction is used in some straits) (in m2) 
    54       !!------------------------------------------------------------------------------------------------- 
    55  
    56       !!---------------------------------------------------------------------- 
    57       INTEGER                 , INTENT(in   ) ::   nbench, jp_cfg   ! parameter of namelist for benchmark, and dimension of GYRE 
    58       INTEGER                 , INTENT(  out) ::   kff              ! =1 Coriolis parameter computed here, =0 otherwise 
    59       REAL(wp), DIMENSION(:,:), INTENT(  out) ::   pff              ! Coriolis factor at f-point                  [1/s] 
     53      !!---------------------------------------------------------------------- 
     54      INTEGER                 , INTENT(in   ) ::   kbench, k_cfg   ! parameter of namelist for benchmark, and dimension of GYRE 
     55      INTEGER                 , INTENT(  out) ::   kff             ! =1 Coriolis parameter computed here, =0 otherwise 
     56      REAL(wp), DIMENSION(:,:), INTENT(  out) ::   pff             ! Coriolis factor at f-point                  [1/s] 
    6057      REAL(wp), DIMENSION(:,:), INTENT(  out) ::   pglamt, pglamu, pglamv, pglamf !  longitude outputs        [degrees] 
    6158      REAL(wp), DIMENSION(:,:), INTENT(  out) ::   pgphit, pgphiu, pgphiv, pgphif !  latitude outputs         [degrees] 
     
    7673      IF(lwp) WRITE(numout,*) '          beta-plane with regular grid-spacing and rotated domain (GYRE configuration)' 
    7774      ! 
    78       ! angle 45deg and ze1=106.e+3 / jp_cfg forced -> zlam1 = -85deg, zphi1 = 29degN 
     75      ! angle 45deg and ze1=106.e+3 / k_cfg forced -> zlam1 = -85deg, zphi1 = 29degN 
    7976      zlam1 = -85._wp 
    8077      zphi1 =  29._wp 
    8178      ! resolution in meters 
    82       ze1 = 106000. / REAL( jp_cfg , wp ) 
     79      ze1 = 106000. / REAL( k_cfg , wp ) 
    8380      ! benchmark: forced the resolution to be about 100 km 
     81            IF( kbench /= 0 )   ze1 = 106000._wp    
     82      zsin_alpha = - SQRT( 2._wp ) * 0.5_wp 
     83      zcos_alpha =   SQRT( 2._wp ) * 0.5_wp 
     84      ze1deg = ze1 / (ra * rad) 
     85      IF( kbench /= 0 )   ze1deg = ze1deg / REAL( jp_cfg , wp )   ! benchmark: keep the lat/+lon 
     86      !                                                           ! at the right jp_cfg resolution 
     87      zlam0 = zlam1 + zcos_alpha * ze1deg * REAL( jpjglo-2 , wp ) 
     88      zphi0 = zphi1 + zsin_alpha * ze1deg * REAL( jpjglo-2 , wp ) 
     89      !    
     90      IF( nprint==1 .AND. lwp )   THEN 
     91         WRITE(numout,*) '          ze1', ze1, 'cosalpha', zcos_alpha, 'sinalpha', zsin_alpha 
     92         WRITE(numout,*) '          ze1deg', ze1deg, 'zlam0', zlam0, 'zphi0', zphi0 
     93      ENDIF 
     94      !    
     95      DO jj = 1, jpj  
     96         DO ji = 1, jpi  
     97            zim1 = REAL( ji + nimpp - 1 ) - 1.   ;   zim05 = REAL( ji + nimpp - 1 ) - 1.5  
     98            zjm1 = REAL( jj + njmpp - 1 ) - 1.   ;   zjm05 = REAL( jj + njmpp - 1 ) - 1.5  
     99            !    
     100            !glamt(i,j) longitude at T-point 
     101            !gphit(i,j) latitude at T-point   
     102            pglamt(ji,jj) = zlam0 + zim05 * ze1deg * zcos_alpha + zjm05 * ze1deg * zsin_alpha 
     103            pgphit(ji,jj) = zphi0 - zim05 * ze1deg * zsin_alpha + zjm05 * ze1deg * zcos_alpha 
     104            !    
     105            !glamu(i,j) longitude at U-point 
     106            !gphiu(i,j) latitude at U-point 
     107            pglamu(ji,jj) = zlam0 + zim1  * ze1deg * zcos_alpha + zjm05 * ze1deg * zsin_alpha 
     108            pgphiu(ji,jj) = zphi0 - zim1  * ze1deg * zsin_alpha + zjm05 * ze1deg * zcos_alpha 
     109            !    
     110            !glamv(i,j) longitude at V-point 
     111            !gphiv(i,j) latitude at V-point 
     112            pglamv(ji,jj) = zlam0 + zim05 * ze1deg * zcos_alpha + zjm1  * ze1deg * zsin_alpha 
     113            pgphiv(ji,jj) = zphi0 - zim05 * ze1deg * zsin_alpha + zjm1  * ze1deg * zcos_alpha 
     114            ! 
     115            !glamf(i,j) longitude at F-point 
     116            !gphif(i,j) latitude at F-point  
     117            pglamf(ji,jj) = zlam0 + zim1  * ze1deg * zcos_alpha + zjm1  * ze1deg * zsin_alpha 
     118            pgphif(ji,jj) = zphi0 - zim1  * ze1deg * zsin_alpha + zjm1  * ze1deg * zcos_alpha 
     119         END DO 
     120      END DO 
     121      ! 
     122      !       !== Horizontal scale factors ==! (in meters) 
     123      !                      
     124      !                             ! constant grid spacing 
     125      pe1t(:,:) =  ze1     ;      pe2t(:,:) = ze1 
     126      pe1u(:,:) =  ze1     ;      pe2u(:,:) = ze1 
     127      pe1v(:,:) =  ze1     ;      pe2v(:,:) = ze1 
     128      pe1f(:,:) =  ze1     ;      pe2f(:,:) = ze1 
     129      !                             ! NO reduction of grid size in some straits  
     130      ke1e2u_v = 0                  !    ==>> u_ & v_surfaces will be computed in dom_ghr routine 
     131      ! 
     132      ! 
     133 
     134      !                      !==  Coriolis parameter  ==! 
     135      kff = 1                                                           !  indicate not to compute ff afterward 
     136      ! 
     137      zbeta = 2. * omega * COS( rad * zphi1 ) / ra                      ! beta at latitude zphi1 
     138      !SF we overwrite zphi0 (south point in latitude) used just above to define pgphif (value of zphi0=15.5190567531966) 
     139      !SF for computation of coriolis we keep the parameter of Hazeleger, W., and S. S. Drijfhout, JPO 1998. 
     140      zphi0 = 15._wp                                                    !  latitude of the most southern grid point   
     141      zf0   = 2. * omega * SIN( rad * zphi0 )                           !  compute f0 1st point south 
     142      ! 
     143      pff(:,:) = ( zf0 + zbeta * ABS( gphif(:,:) - zphi0 ) * rad * ra ) ! f = f0 +beta* y ( y=0 at south) 
     144      ! 
     145      IF(lwp) WRITE(numout,*) '                           beta-plane used. beta = ', zbeta, ' 1/(s.m)' 
     146      ! 
     147      IF( nn_timing == 1 )  CALL timing_stop('usr_def_hgr') 
    84148      ! 
    85149   END SUBROUTINE usr_def_hgr 
     
    101165      !!              - set salinity   field 
    102166      !!---------------------------------------------------------------------- 
    103       REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(  out) ::   ptsd   ! T & S data 
     167      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(  out) ::   pts   ! T & S data 
    104168      ! 
    105169      INTEGER :: ji, jj, jk  ! dummy loop indices 
Note: See TracChangeset for help on using the changeset viewer.