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 465 for trunk/NEMO/OPA_SRC – NEMO

Changeset 465 for trunk/NEMO/OPA_SRC


Ignore:
Timestamp:
2006-05-10T19:38:46+02:00 (18 years ago)
Author:
opalod
Message:

nemo_v1_update_056:RB: updatye OBC with new coordinate

Location:
trunk/NEMO/OPA_SRC/OBC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/OBC/obc_oce.F90

    r367 r465  
    44   !! Open Boundary Cond. :   define related variables 
    55   !!============================================================================== 
     6   !!  OPA 9.0 , LOCEAN-IPSL (2005)  
     7   !! $Header$  
     8   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)  
     9   !!---------------------------------------------------------------------- 
    610#if defined key_obc 
    711   !!---------------------------------------------------------------------- 
     
    2731   IMPLICIT NONE 
    2832   PUBLIC 
    29    !!---------------------------------------------------------------------- 
    30    !!  OPA 9.0 , LOCEAN-IPSL (2005)  
    31    !! $Header$  
    32    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
    33    !!---------------------------------------------------------------------- 
    3433 
    3534   !!---------------------------------------------------------------------- 
     
    6766      !                       !  scale are set to 0 in the namelist, for both inflow and outflow). 
    6867 
    69    REAL(wp), DIMENSION(jpi,jpj) :: &  !: 
    70       obctmsk                !: mask array identical to tmask, execpt along OBC where it is set to 0 
     68   REAL(wp), PUBLIC ::    &  !: 
     69      obcsurftot       !: Total lateral surface of open boundaries 
     70    
     71   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: &  !: 
     72      obctmsk,            &  !: mask array identical to tmask, execpt along OBC where it is set to 0 
    7173      !                      !  it used to calculate the cumulate flux E-P in the obcvol.F90 routine 
    72           
     74      obcumask, obcvmask     !: u-, v- Force filtering mask for the open 
     75      !                      !  boundary condition on grad D 
     76 
    7377   !!---------------- 
    7478   !! Rigid lid case: 
  • trunk/NEMO/OPA_SRC/OBC/obccli.F90

    r367 r465  
    11MODULE obccli 
    2    !!=================================================================================== 
     2   !!====================================================================== 
    33   !!                       ***  MODULE  obccli  *** 
    4    !! Ocean dynamics:   Baroclinic componant of velocities on each open boundary 
    5    !!=================================================================================== 
     4   !! Ocean dynamics:   Baroclinic velocities on each open boundary 
     5   !!====================================================================== 
     6   !! History : 
     7   !!   8.5  !  02-10 (C. Talandier, A-M. Treguier) Free surface, F90 
     8   !!   9.0  !  06-04 (R.Benshila, G. Madec)  zco, zps, sco coordinate 
     9   !!---------------------------------------------------------------------- 
    610#if defined key_obc && defined key_dynspg_rl 
    7    !!----------------------------------------------------------------------------------- 
    8    !!   'key_obc'               and  
    9    !!   'key_dynspg_rl' 
    10    !!----------------------------------------------------------------------------------- 
    11    !!   obc_cli_dyn : Compute the baroclinic componant after the radiation phase 
    12    !!   obc_cli_dta : Compute the baroclinic componant for the climatological velocities 
    13    !!----------------------------------------------------------------------------------- 
     11   !!---------------------------------------------------------------------- 
     12   !!   'key_obc' and 'key_dynspg_rl' open boundary condition and rigid-lid 
     13   !!---------------------------------------------------------------------- 
     14   !!   obc_cli_dyn : baroclinic componant after the radiation phase 
     15   !!   obc_cli_dta : baroclinic componant for the climatological velocities 
     16   !!---------------------------------------------------------------------- 
    1417   !! * Modules used 
    1518   USE oce             ! ocean dynamics and tracers    
     
    3033   !! * Substitutions 
    3134#  include "domzgr_substitute.h90" 
    32    !!----------------------------------------------------------------------------------- 
     35   !!---------------------------------------------------------------------- 
    3336   !!   OPA 9.0 , LOCEAN-IPSL (2005)  
    3437   !! $Header$  
    35    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
    36    !!----------------------------------------------------------------------------------- 
     38   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     39   !!---------------------------------------------------------------------- 
    3740 
    3841CONTAINS 
    3942 
    4043   SUBROUTINE obc_cli_dyn( obvel, velcli, obd, obf, obtyp, obl) 
    41       !!-------------------------------------------------------------------------------- 
     44      !!---------------------------------------------------------------------- 
    4245      !!                 ***  SUBROUTINE obc_cli_dyn  *** 
    4346      !!                    
     
    5154      !!      - obl is the lenght of the OB (jpi or jpj)  
    5255      !! 
    53       !! History : 
    54       !!   8.5  !  02-10 (C. Talandier, A-M. Treguier) Free surface, F90 
    55       !!-------------------------------------------------------------------------------- 
     56      !!----------------------------------------------------------------------- 
    5657      !! * Arguments 
    5758      INTEGER, INTENT( in ) ::   & ! OB localization:jpieob or jpiwob for East or West  
     
    7475         zmskob,                    & ! Velocity mask 
    7576         zvel                         ! 2D Local velocity on OB 
    76 # if defined key_partial_steps 
    7777      REAL(wp), DIMENSION(obl,jpk) ::   & 
    7878         ze3ob                        ! Vertical scale factor 
    79 # else 
    80       REAL(wp), DIMENSION(jpk) ::   & 
    81          ze3ob                        ! Vertical scale factor 
    82 # endif 
    8379      !!-------------------------------------------------------------------------------- 
    8480 
     
    8682      ! ----------------------- 
    8783 
    88       zhinv(:) = 0.e0 
     84      zhinv (:)  = 0.e0 
    8985      zmskob(:,:) = 0.e0 
    90       zvel(:,:) = 0.e0 
    91 # if defined key_partial_steps 
    92       ze3ob(:,:) = 0.e0 
    93 # else 
    94       ze3ob(:) = 0.e0 
    95 # endif 
     86      zvel  (:,:) = 0.e0 
     87      ze3ob (:,:) = 0.e0 
    9688 
    9789      IF( obtyp == 0 ) THEN            ! Meridional Open Boundary ( East or West OB ) 
    9890         DO ji = obd, obf 
    99             zhinv(:) = hur(ji,:) 
     91            zhinv (:)   = hur  (ji,:) 
    10092            zmskob(:,:) = umask(ji,:,:) 
    101             zvel(:,:) = obvel(ji,:,:) 
    102 # if defined key_partial_steps 
    103             ze3ob(:,:) = fse3u(ji,:,:) 
    104 # else 
    105             ze3ob(:) = fse3u(:,:,:) 
    106 # endif 
     93            zvel  (:,:) = obvel(ji,:,:) 
     94            ze3ob (:,:) = fse3u(ji,:,:) 
    10795         END DO 
    10896      ELSE                             ! Zonal Open Boundary ( North or South OB ) 
    10997         DO jj = obd, obf 
    110             zhinv(:) = hvr(:,jj) 
     98            zhinv (:)   = hvr  (:,jj) 
    11199            zmskob(:,:) = vmask(:,jj,:) 
    112             zvel(:,:) = obvel(:,jj,:) 
    113 # if defined key_partial_steps 
    114             ze3ob(:,:) = fse3v(:,jj,:) 
    115 # else 
    116             ze3ob(:) = fse3v(:,:,:) 
    117 # endif 
     100            zvel  (:,:) = obvel(:,jj,:) 
     101            ze3ob (:,:) = fse3v(:,jj,:) 
    118102         END DO 
    119103      END IF 
    120104 
    121       zvelbtpe(:) = 0.e0 
    122105 
    123106      ! 1. vertical sum 
    124107      ! ---------------- 
    125 # if defined key_vectopt_loop 
     108      zvelbtpe(1) = 0.e0 
    126109!CDIR NOLOOPCHG 
    127 # endif 
    128       DO jol = obd, obf ! Vector opt. 
    129          DO jk = 1, jpkm1 
    130             DO jle = 1, obl 
    131                zvelbtpe(jle) = zvelbtpe(jle) + zvel(jle,jk)*zmskob(jle,jk) & 
    132 # if defined key_partial_steps 
    133                                            * ze3ob(jol,jle,jk) 
    134 # else 
    135                                            * ze3ob(jk) 
    136 # endif 
    137             END DO 
     110      DO jk = 1, jpkm1 
     111         DO jle = 1, obl 
     112            zvelbtpe(jle) = zvelbtpe(jle) + zvel(jle,jk) * zmskob(jle,jk) * ze3ob(jle,jk) 
    138113         END DO 
    139114      END DO 
     
    141116      ! 2. divide by the depth 
    142117      ! ----------------------- 
    143       DO jle = 1, obl 
    144          zvelbtpe(jle) = zvelbtpe(jle) * zhinv(jle) * zmskob(jle,1)  
    145       END DO 
     118      zvelbtpe(:) = zvelbtpe(:) * zhinv(:) * zmskob(:,1)  
    146119 
    147120      ! 3. substract zvelbtpe to the total velocity 
     
    149122      ! ------------------------------------------------ 
    150123      DO jk = 1, jpkm1 
    151          DO jle = 1, obl 
    152             zcbl = zvel(jle,jk) - zvelbtpe(jle)*zmskob(jle,jk) 
    153             velcli(jle,jk) = zcbl * zmskob(jle,jk) 
    154          END DO 
     124         velcli(:,jk) = ( zvel(:,jk) - zvelbtpe(:) ) * zmskob(:,jk) 
    155125      END DO 
    156126 
     
    172142      !!      - obl is the lenght of the OB (jpi or jpj)  
    173143      !! 
    174       !! History : 
    175       !!   8.5  !  02-10 (C. Talandier, A-M. Treguier) Free surface, F90 
    176144      !!-------------------------------------------------------------------------------- 
    177145      !! * Arguments 
     
    195163      REAL(wp), DIMENSION(obl,jpk) ::   & 
    196164         zmskob                       ! Velocity mask 
    197 # if defined key_partial_steps 
    198165      REAL(wp), DIMENSION(obl,jpk) ::   & 
    199166         ze3ob                        ! Vertical scale factor 
    200 # else 
    201       REAL(wp), DIMENSION(jpk) ::   & 
    202          ze3ob                        ! Vertical scale factor 
    203 # endif 
    204167      !!-------------------------------------------------------------------------------- 
    205168 
     
    207170      ! ----------------------- 
    208171 
    209       zhinv(:) = 0.e0 
     172      zhinv (:)  = 0.e0 
    210173      zmskob(:,:) = 0.e0 
    211 # if defined key_partial_steps 
    212       ze3ob(:,:) = 0.e0 
    213 # else 
    214       ze3ob(:) = 0.e0 
    215 # endif 
     174      ze3ob (:,:) = 0.e0 
    216175 
    217176      IF( obtyp == 0 ) THEN            ! Meridional Open Boundary ( East or West OB ) 
    218177         DO ji = obd, obf 
    219             zhinv(:) = hur(ji,:) 
     178            zhinv (:)   = hur  (ji,:) 
    220179            zmskob(:,:) = umask(ji,:,:) 
    221 # if defined key_partial_steps 
    222             ze3ob(:,:) = fse3u(ji,:,:) 
    223 # else 
    224             ze3ob(:) = fse3u(:,:,:) 
    225 # endif 
     180            ze3ob (:,:) = fse3u(ji,:,:) 
    226181         END DO 
    227182      ELSE                             ! Zonal Open Boundary ( North or South OB ) 
    228183         DO jj = obd, obf 
    229             zhinv(:) = hvr(:,jj) 
     184            zhinv (:)   = hvr  (:,jj) 
    230185            zmskob(:,:) = vmask(:,jj,:) 
    231 # if defined key_partial_steps 
    232             ze3ob(:,:) = fse3v(:,jj,:) 
    233 # else 
    234             ze3ob(:) = fse3v(:,:,:) 
    235 # endif 
     186            ze3ob (:,:) = fse3v(:,jj,:) 
    236187         END DO 
    237188      END IF 
    238  
    239       zvelbtpe(:) = 0.e0 
    240189 
    241190      ! 1. vertical sum 
    242191      ! ---------------- 
    243 # if defined key_vectopt_loop 
     192      zvelbtpe(1) = 0.e0 
    244193!CDIR NOLOOPCHG 
    245 # endif 
    246       DO jol = obd, obf ! Vector opt. 
    247          DO jk = 1, jpkm1 
    248             DO jle = 1, obl 
    249                ij = jle -1 + mpp 
    250                zvelbtpe(jle) = zvelbtpe(jle) + obvel(ij,jk,1)*zmskob(jle,jk) & 
    251 # if defined key_partial_steps 
    252                                            * ze3ob(jol,jle,jk) 
    253 # else 
    254                                            * ze3ob(jk) 
    255 # endif 
    256             END DO 
     194      DO jk = 1, jpkm1 
     195         DO jle = 1, obl 
     196            ij = jle -1 + mpp 
     197            zvelbtpe(jle) = zvelbtpe(jle) + obvel(ij,jk,1)*zmskob(jle,jk) * ze3ob(jle,jk) 
    257198         END DO 
    258199      END DO 
     
    260201      ! 2. divide by the depth 
    261202      ! ----------------------- 
    262       DO jle = 1, obl 
    263          zvelbtpe(jle) = zvelbtpe(jle) * zhinv(jle) * zmskob(jle,1)  
    264       END DO  
     203         zvelbtpe(:) = zvelbtpe(:) * zhinv(:) * zmskob(:,1)  
    265204 
    266205      ! 3. substract zvelbtpe to the total velocity 
  • trunk/NEMO/OPA_SRC/OBC/obcdta.F90

    r418 r465  
    44   !! Open boundary data : read the data for the open boundaries. 
    55   !!============================================================================== 
     6   !! History : 
     7   !!        !  98-05 (J.M. Molines) Original code 
     8   !!   8.5  !  02-10 (C. Talandier, A-M. Treguier) Free surface, F90 
     9   !!   9.0  !  04-06 (F. Durand, A-M. Treguier) Netcdf BC files on input 
     10   !!------------------------------------------------------------------------------ 
    611#if defined key_obc 
    712   !!------------------------------------------------------------------------------ 
     
    2227   USE dynspg_oce      ! choice/control of key cpp for surface pressure gradient 
    2328   USE ioipsl 
    24 #  if defined key_dynspg_rl 
    25    USE obccli 
    26 #  endif 
     29   USE obccli          ! climatological obc, use only in rigid-lid case 
    2730 
    2831   IMPLICIT NONE 
     
    5356CONTAINS 
    5457 
    55    SUBROUTINE obc_dta (kt) 
     58   SUBROUTINE obc_dta( kt ) 
    5659      !!-------------------------------------------------------------------- 
    5760      !!              ***  SUBROUTINE obc_dta  *** 
    5861      !!                    
    59       !! ** Purpose : 
    60       !!   Find the climatological boundary arrays for the specified date, 
     62      !! ** Purpose :   Find the climatological boundary arrays for the specified date, 
    6163      !!   The boundary arrays are netcdf files. Three possible cases: 
    6264      !!   - one time frame only in the file (time dimension = 1). 
     
    7072      !!     attribute of variable time_counter). 
    7173      !! 
    72       !! History : 
    73       !!        !  98-05 (J.M. Molines) Original code 
    74       !!   8.5  !  02-10 (C. Talandier, A-M. Treguier) Free surface, F90 
    75       !!   9.0  !  04-06 (F. Durand, A-M. Treguier) Netcdf BC files on input 
    7674      !!-------------------------------------------------------------------- 
    7775      !! * Arguments 
     
    9694 
    9795      IF( lk_dynspg_rl )  THEN 
    98          CALL obc_dta_psi (kt)     ! update bsf data at open boundaries 
    99          IF( nobc_dta == 1 .AND. kt == nit000 )   THEN 
     96         CALL obc_dta_psi( kt )     ! update bsf data at open boundaries 
     97         IF( nobc_dta == 1 .AND. kt == nit000 ) THEN 
    10098            IF(lwp) WRITE(numout,*) ' time-variable psi boundary data not allowed yet' 
    10199            STOP 
     
    103101      ENDIF 
    104102       
    105       CALL ipslnlf (new_number=numout) 
     103      CALL ipslnlf( new_number=numout ) 
    106104      
    107105      ! 1.   First call: check time frames available in files. 
     
    11791177   !!   Default option 
    11801178   !!----------------------------------------------------------------------------- 
    1181    SUBROUTINE obc_dta_bt ( kt, kbt )       ! Empty routine 
    1182       !! * Arguments 
    1183       INTEGER,INTENT(in) :: kt 
    1184       INTEGER, INTENT( in ) ::   kbt         ! barotropic ocean time-step index 
    1185       WRITE(*,*) 'obc_dta_bt: You should not have seen this print! error?', kt 
    1186       WRITE(*,*) 'obc_dta_bt: You should not have seen this print! error?', kbt 
     1179   SUBROUTINE obc_dta_bt( kt, kbt )       ! Empty routine 
     1180      INTEGER,INTENT(in) ::   kt, kbt 
     1181      WRITE(*,*) 'obc_dta_bt: You should not have seen this print! error?', kt, kbt 
    11871182   END SUBROUTINE obc_dta_bt 
    11881183#endif 
Note: See TracChangeset for help on using the changeset viewer.