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 2253 – NEMO

Changeset 2253


Ignore:
Timestamp:
2010-10-13T15:01:11+02:00 (14 years ago)
Author:
rfurner
Message:

Updates to BDY naming of namelist variables and routines

Location:
branches/devukmo2010/NEMO/OPA_SRC
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • branches/devukmo2010/NEMO/OPA_SRC/BDY/bdy_oce.F90

    r2128 r2253  
    2121   !! Namelist variables 
    2222   !!---------------------------------------------------------------------- 
    23    CHARACTER(len=80) ::   filbdy_mask        !: Name of unstruct. bdy mask file 
    24    CHARACTER(len=80) ::   filbdy_data_T      !: Name of unstruct. bdy data file at T points 
    25    CHARACTER(len=80) ::   filbdy_data_U      !: Name of unstruct. bdy data file at U points 
    26    CHARACTER(len=80) ::   filbdy_data_V      !: Name of unstruct. bdy data file at V points 
    27    CHARACTER(len=80) ::   filbdy_data_bt_T   !: Name of unstruct. bdy data file at T points for barotropic variables 
    28    CHARACTER(len=80) ::   filbdy_data_bt_U   !: Name of unstruct. bdy data file at U points for barotropic variables 
    29    CHARACTER(len=80) ::   filbdy_data_bt_V   !: Name of unstruct. bdy data file at V points for barotropic variables 
     23   CHARACTER(len=80) ::   cn_mask        !: Name of unstruct. bdy mask file 
     24   CHARACTER(len=80) ::   cn_dta_frs_T   !: Name of unstruct. bdy data file at T points for FRS conditions 
     25   CHARACTER(len=80) ::   cn_dta_frs_U   !: Name of unstruct. bdy data file at U points for FRS conditions 
     26   CHARACTER(len=80) ::   cn_dta_frs_V   !: Name of unstruct. bdy data file at V points for FRS conditions 
     27   CHARACTER(len=80) ::   cn_dta_fla_T   !: Name of unstruct. bdy data file at T points for Flather scheme 
     28   CHARACTER(len=80) ::   cn_dta_fla_U   !: Name of unstruct. bdy data file at U points for Flather scheme 
     29   CHARACTER(len=80) ::   cn_dta_fla_V   !: Name of unstruct. bdy data file at V points for Flather scheme 
    3030   ! 
    31    LOGICAL ::   ln_bdy_tides = .false.  !: =T apply tidal harmonic forcing along open boundaries 
    32    LOGICAL ::   ln_bdy_vol  = .false.   !: =T volume correction              
    33    LOGICAL ::   ln_bdy_mask = .false.   !: =T read bdymask from file 
    34    LOGICAL ::   ln_bdy_clim = .false.   !: if true, we assume that bdy data files contain  
     31   LOGICAL ::   ln_tides = .false.    !: =T apply tidal harmonic forcing along open boundaries 
     32   LOGICAL ::   ln_vol  = .false.     !: =T volume correction              
     33   LOGICAL ::   ln_mask = .false.     !: =T read bdymask from file 
     34   LOGICAL ::   ln_clim = .false.     !: if true, we assume that bdy data files contain  
    3535   !                                    !  1 time dump  (-->bdy forcing will be constant)  
    3636   !                                    !  or 12 months (-->bdy forcing will be cyclic)  
    37    LOGICAL ::   ln_bdy_dyn_fla  = .false. !: =T Flather boundary conditions on barotropic velocities 
    38    LOGICAL ::   ln_bdy_dyn_frs  = .false. !: =T FRS boundary conditions on velocities 
    39    LOGICAL ::   ln_bdy_tra_frs  = .false. !: =T FRS boundary conditions on tracers (T and S) 
    40    LOGICAL ::   ln_bdy_ice_frs  = .false. !: =T FRS boundary conditions on seaice (leads fraction, ice depth, snow depth) 
     37   LOGICAL ::   ln_dyn_fla  = .false. !: =T Flather boundary conditions on barotropic velocities 
     38   LOGICAL ::   ln_dyn_frs  = .false. !: =T FRS boundary conditions on velocities 
     39   LOGICAL ::   ln_tra_frs  = .false. !: =T FRS boundary conditions on tracers (T and S) 
     40   LOGICAL ::   ln_ice_frs  = .false. !: =T FRS boundary conditions on seaice (leads fraction, ice depth, snow depth) 
    4141   ! 
    42    INTEGER ::   nb_rimwidth = 7         !: boundary rim width 
    43    INTEGER ::   nbdy_dta    = 1          !: = 0 use the initial state as bdy dta or = 1 read it in a NetCDF file 
    44    INTEGER ::   volbdy      = 1         !: = 0 the total volume will have the variability of the surface Flux E-P  
     42   INTEGER ::   nn_rimwidth = 7         !: boundary rim width 
     43   INTEGER ::   nn_dtactl   = 1          !: = 0 use the initial state as bdy dta or = 1 read it in a NetCDF file 
     44   INTEGER ::   nn_volctl   = 1         !: = 0 the total volume will have the variability of the surface Flux E-P  
    4545   !                                    !  = 1 the volume will be constant during all the integration. 
    4646 
     
    8484   !!   Dummy module                NO Unstructured Open Boundary Condition 
    8585   !!---------------------------------------------------------------------- 
    86    LOGICAL ::   ln_bdy_tides = .false.  !: =T apply tidal harmonic forcing along open boundaries 
     86   LOGICAL ::   ln_tides = .false.  !: =T apply tidal harmonic forcing along open boundaries 
    8787#endif 
    8888 
  • branches/devukmo2010/NEMO/OPA_SRC/BDY/bdydta.F90

    r2185 r2253  
    66   !! History :  1.0  !  2005-01  (J. Chanut, A. Sellar)  Original code 
    77   !!             -   !  2007-01  (D. Storkey) Update to use IOM module 
    8    !!             -   !  2007-07  (D. Storkey) add bdy_dta_bt 
     8   !!             -   !  2007-07  (D. Storkey) add bdy_dta_fla 
    99   !!            3.0  !  2008-04  (NEMO team)  add in the reference version 
    1010   !!            3.3  !  2010-09  (E.O'Dea) modifications for Shelf configurations  
     
    1515   !!   'key_bdy'                     Unstructured Open Boundary Conditions 
    1616   !!---------------------------------------------------------------------- 
    17    !!   bdy_dta    : read u, v, t, s data along open boundaries 
    18    !!   bdy_dta_bt : read depth-mean velocities and elevation along open boundaries         
     17   !!   bdy_dta_frs    : read u, v, t, s data along open boundaries 
     18   !!   bdy_dta_fla : read depth-mean velocities and elevation along open boundaries         
    1919   !!---------------------------------------------------------------------- 
    2020   USE oce             ! ocean dynamics and tracers 
     
    3333   PRIVATE 
    3434 
    35    PUBLIC   bdy_dta      ! routines called by step.F90 
    36    PUBLIC   bdy_dta_bt  
     35   PUBLIC   bdy_dta_frs      ! routines called by step.F90 
     36   PUBLIC   bdy_dta_fla  
    3737 
    3838   INTEGER ::   numbdyt, numbdyu, numbdyv                      ! logical units for T-, U-, & V-points data file, resp. 
     
    6565CONTAINS 
    6666 
    67    SUBROUTINE bdy_dta( kt ) 
     67   SUBROUTINE bdy_dta_frs( kt ) 
    6868      !!---------------------------------------------------------------------- 
    69       !!                   ***  SUBROUTINE bdy_dta  *** 
     69      !!                   ***  SUBROUTINE bdy_dta_frs  *** 
    7070      !!                     
    7171      !! ** Purpose :   Read unstructured boundary data for FRS condition. 
     
    101101 
    102102 
    103       IF( ln_bdy_dyn_frs .OR. ln_bdy_tra_frs    & 
    104          &               .OR. ln_bdy_ice_frs ) THEN  ! If these are both false then this routine does nothing 
     103      IF( ln_dyn_frs .OR. ln_tra_frs    & 
     104         &               .OR. ln_ice_frs ) THEN  ! If these are both false then this routine does nothing 
    105105 
    106106      ! -------------------- ! 
     
    139139 
    140140         IF(lwp) WRITE(numout,*) 
    141          IF(lwp) WRITE(numout,*)    'bdy_dta : Initialize unstructured boundary data' 
     141         IF(lwp) WRITE(numout,*)    'bdy_dta_frs : Initialize unstructured boundary data' 
    142142         IF(lwp) WRITE(numout,*)    '~~~~~~~'  
    143143 
    144          IF     ( nbdy_dta == 0 ) THEN 
     144         IF     ( nn_dtactl == 0 ) THEN 
    145145            ! 
    146146            IF(lwp) WRITE(numout,*) '          Bdy data are taken from initial conditions' 
    147147            ! 
    148          ELSEIF (nbdy_dta == 1) THEN 
     148         ELSEIF (nn_dtactl == 1) THEN 
    149149            ! 
    150150            IF(lwp) WRITE(numout,*) '          Bdy data are read in netcdf files' 
     
    155155            !                                                 ! necessary time dumps in file are included 
    156156            ! 
    157             clfile(1) = filbdy_data_T 
    158             clfile(2) = filbdy_data_U 
    159             clfile(3) = filbdy_data_V 
     157            clfile(1) = cn_dta_frs_T 
     158            clfile(2) = cn_dta_frs_U 
     159            clfile(3) = cn_dta_frs_V 
    160160            !                                                   
    161161            ! how many files are we to read in? 
    162162            igrd_start = 1 
    163163            igrd_end   = 3 
    164             IF(.NOT. ln_bdy_tra_frs .AND. .NOT. ln_bdy_ice_frs) THEN       ! No T-grid file. 
     164            IF(.NOT. ln_tra_frs .AND. .NOT. ln_ice_frs) THEN       ! No T-grid file. 
    165165               igrd_start = 2 
    166             ELSEIF ( .NOT. ln_bdy_dyn_frs ) THEN                           ! No U-grid or V-grid file. 
     166            ELSEIF ( .NOT. ln_dyn_frs ) THEN                           ! No U-grid or V-grid file. 
    167167               igrd_end   = 1          
    168168            ENDIF 
     
    273273 
    274274            ! Check number of time dumps:               
    275             IF( ntimes_bdy == 1 .AND. .NOT. ln_bdy_clim ) THEN 
     275            IF( ntimes_bdy == 1 .AND. .NOT. ln_clim ) THEN 
    276276              CALL ctl_stop( 'There is only one time dump in data files',   & 
    277                  &           'Choose ln_bdy_clim=.true. in namelist for constant bdy forcing.' ) 
     277                 &           'Choose ln_clim=.true. in namelist for constant bdy forcing.' ) 
    278278            ENDIF 
    279279 
    280             IF( ln_bdy_clim ) THEN 
     280            IF( ln_clim ) THEN 
    281281              IF( ntimes_bdy /= 1 .AND. ntimes_bdy /= 12 ) THEN 
    282                  CALL ctl_stop( 'For climatological boundary forcing (ln_bdy_clim=.true.),',   & 
     282                 CALL ctl_stop( 'For climatological boundary forcing (ln_clim=.true.),',   & 
    283283                    &           'bdy data files must contain 1 or 12 time dumps.' ) 
    284284              ELSEIF( ntimes_bdy ==  1 ) THEN 
     
    301301            IF(lwp) WRITE(numout,*) 'First record to read is ',nbdy_b 
    302302 
    303          ENDIF ! endif (nbdy_dta == 1) 
    304  
    305  
    306          ! 1.2  Read first record in file if necessary (ie if nbdy_dta == 1) 
     303         ENDIF ! endif (nn_dtactl == 1) 
     304 
     305 
     306         ! 1.2  Read first record in file if necessary (ie if nn_dtactl == 1) 
    307307         ! ***************************************************************** 
    308308 
    309          IF( nbdy_dta == 0 ) THEN      ! boundary data arrays are filled with initial conditions 
     309         IF( nn_dtactl == 0 ) THEN      ! boundary data arrays are filled with initial conditions 
    310310            ! 
    311             IF (ln_bdy_tra_frs) THEN 
     311            IF (ln_tra_frs) THEN 
    312312               igrd = 1            ! T-points data  
    313313               DO ib = 1, nblen(igrd) 
     
    321321            ENDIF 
    322322 
    323             IF(ln_bdy_dyn_frs) THEN 
     323            IF(ln_dyn_frs) THEN 
    324324               igrd = 2            ! U-points data  
    325325               DO ib = 1, nblen(igrd) 
     
    342342            ! 
    343343#if defined key_lim2 
    344             IF( ln_bdy_ice_frs ) THEN 
     344            IF( ln_ice_frs ) THEN 
    345345               igrd = 1            ! T-points data 
    346346               DO ib = 1, nblen(igrd) 
     
    351351            ENDIF 
    352352#endif 
    353          ELSEIF( nbdy_dta == 1 ) THEN    ! Set first record in the climatological case:    
     353         ELSEIF( nn_dtactl == 1 ) THEN    ! Set first record in the climatological case:    
    354354            ! 
    355             IF( ln_bdy_clim .AND. ntimes_bdy == 1 ) THEN 
     355            IF( ln_clim .AND. ntimes_bdy == 1 ) THEN 
    356356               nbdy_a = 1 
    357             ELSEIF( ln_bdy_clim .AND. ntimes_bdy == iman ) THEN 
     357            ELSEIF( ln_clim .AND. ntimes_bdy == iman ) THEN 
    358358               nbdy_b = 0 
    359359               nbdy_a = imois 
     
    368368            ipi  = nblendta(igrd) 
    369369 
    370             IF(ln_bdy_tra_frs) THEN 
     370            IF(ln_tra_frs) THEN 
    371371               ! 
    372372               igrd = 1                                           ! Temperature 
     
    399399                  END DO 
    400400               END DO 
    401             ENDIF  ! ln_bdy_tra_frs 
     401            ENDIF  ! ln_tra_frs 
    402402  
    403             IF( ln_bdy_dyn_frs ) THEN 
     403            IF( ln_dyn_frs ) THEN 
    404404               ! 
    405405               igrd = 2                                           ! u-velocity 
     
    430430                  END DO 
    431431               END DO 
    432             ENDIF ! ln_bdy_dyn_frs 
     432            ENDIF ! ln_dyn_frs 
    433433 
    434434#if defined key_lim2 
    435             IF( ln_bdy_ice_frs ) THEN 
     435            IF( ln_ice_frs ) THEN 
    436436              ! 
    437437              igrd=1                                              ! leads fraction 
     
    458458                hsnif_bdydta(ib,2) =  zdta(nbmap(ib,igrd),1,1) 
    459459              END DO 
    460             ENDIF ! just if ln_bdy_ice_frs is set 
     460            ENDIF ! just if ln_ice_frs is set 
    461461#endif 
    462462 
    463             IF( .NOT.ln_bdy_clim .AND. istep(1) > 0 ) THEN     ! First data time is after start of run 
     463            IF( .NOT.ln_clim .AND. istep(1) > 0 ) THEN     ! First data time is after start of run 
    464464               nbdy_b = nbdy_a                                 ! Put first value in both time levels 
    465                IF( ln_bdy_tra_frs ) THEN 
     465               IF( ln_tra_frs ) THEN 
    466466                 tbdydta(:,:,1) = tbdydta(:,:,2) 
    467467                 sbdydta(:,:,1) = sbdydta(:,:,2) 
    468468               ENDIF 
    469                IF( ln_bdy_dyn_frs ) THEN 
     469               IF( ln_dyn_frs ) THEN 
    470470                 ubdydta(:,:,1) = ubdydta(:,:,2) 
    471471                 vbdydta(:,:,1) = vbdydta(:,:,2) 
    472472               ENDIF 
    473473#if defined key_lim2 
    474                IF( ln_bdy_ice_frs ) THEN 
     474               IF( ln_ice_frs ) THEN 
    475475                  frld_bdydta (:,1) =  frld_bdydta(:,2) 
    476476                  hicif_bdydta(:,1) = hicif_bdydta(:,2) 
     
    480480            END IF 
    481481            ! 
    482          END IF   ! nbdy_dta == 0/1 
     482         END IF   ! nn_dtactl == 0/1 
    483483  
    484484         ! In the case of constant boundary forcing fill bdy arrays once for all 
    485          IF( ln_bdy_clim .AND. ntimes_bdy == 1 ) THEN 
    486             IF( ln_bdy_tra_frs ) THEN 
     485         IF( ln_clim .AND. ntimes_bdy == 1 ) THEN 
     486            IF( ln_tra_frs ) THEN 
    487487               tbdy  (:,:) = tbdydta  (:,:,2) 
    488488               sbdy  (:,:) = sbdydta  (:,:,2) 
    489489            ENDIF 
    490             IF( ln_bdy_dyn_frs) THEN 
     490            IF( ln_dyn_frs) THEN 
    491491               ubdy  (:,:) = ubdydta  (:,:,2) 
    492492               vbdy  (:,:) = vbdydta  (:,:,2) 
    493493            ENDIF 
    494494#if defined key_lim2 
    495             IF( ln_bdy_ice_frs ) THEN 
     495            IF( ln_ice_frs ) THEN 
    496496               frld_bdy (:) = frld_bdydta (:,2) 
    497497               hicif_bdy(:) = hicif_bdydta(:,2) 
     
    500500#endif 
    501501 
    502             IF( ln_bdy_tra_frs .OR. ln_bdy_ice_frs) CALL iom_close( numbdyt ) 
    503             IF( ln_bdy_dyn_frs                    ) CALL iom_close( numbdyu ) 
    504             IF( ln_bdy_dyn_frs                    ) CALL iom_close( numbdyv ) 
     502            IF( ln_tra_frs .OR. ln_ice_frs) CALL iom_close( numbdyt ) 
     503            IF( ln_dyn_frs                    ) CALL iom_close( numbdyu ) 
     504            IF( ln_dyn_frs                    ) CALL iom_close( numbdyv ) 
    505505         END IF 
    506506         ! 
     
    509509 
    510510      !                                                !---------------------! 
    511       IF( nbdy_dta == 1 .AND. ntimes_bdy > 1 ) THEN    !  at each time step  ! 
     511      IF( nn_dtactl == 1 .AND. ntimes_bdy > 1 ) THEN    !  at each time step  ! 
    512512         !                                             !---------------------! 
    513513         ! Read one more record if necessary 
    514514         !********************************** 
    515515 
    516          IF( ln_bdy_clim .AND. imois /= nbdy_b ) THEN      ! remember that nbdy_b=0 for kt=nit000 
     516         IF( ln_clim .AND. imois /= nbdy_b ) THEN      ! remember that nbdy_b=0 for kt=nit000 
    517517            nbdy_b = imois 
    518518            nbdy_a = imois + 1 
     
    520520            nbdy_a = MOD( nbdy_a, iman )   ;   IF( nbdy_a == 0 ) nbdy_a = iman 
    521521            lect=.true. 
    522          ELSEIF( .NOT.ln_bdy_clim .AND. itimer >= istep(nbdy_a) ) THEN 
     522         ELSEIF( .NOT.ln_clim .AND. itimer >= istep(nbdy_a) ) THEN 
    523523 
    524524            IF( nbdy_a < ntimes_bdy ) THEN 
     
    530530               ! put the last data time into both time levels 
    531531               nbdy_b = nbdy_a 
    532                IF(ln_bdy_tra_frs) THEN 
     532               IF(ln_tra_frs) THEN 
    533533                  tbdydta(:,:,1) =  tbdydta(:,:,2) 
    534534                  sbdydta(:,:,1) =  sbdydta(:,:,2) 
    535535               ENDIF 
    536                IF(ln_bdy_dyn_frs) THEN 
     536               IF(ln_dyn_frs) THEN 
    537537                  ubdydta(:,:,1) =  ubdydta(:,:,2) 
    538538                  vbdydta(:,:,1) =  vbdydta(:,:,2) 
    539539               ENDIF 
    540540#if defined key_lim2 
    541                IF(ln_bdy_ice_frs) THEN 
     541               IF(ln_ice_frs) THEN 
    542542                  frld_bdydta (:,1) =  frld_bdydta (:,2) 
    543543                  hicif_bdydta(:,1) =  hicif_bdydta(:,2) 
     
    550550          
    551551        IF( lect ) THEN           ! Swap arrays 
    552            IF( ln_bdy_tra_frs ) THEN 
     552           IF( ln_tra_frs ) THEN 
    553553             tbdydta(:,:,1) =  tbdydta(:,:,2) 
    554554             sbdydta(:,:,1) =  sbdydta(:,:,2) 
    555555           ENDIF 
    556            IF( ln_bdy_dyn_frs ) THEN 
     556           IF( ln_dyn_frs ) THEN 
    557557             ubdydta(:,:,1) =  ubdydta(:,:,2) 
    558558             vbdydta(:,:,1) =  vbdydta(:,:,2) 
    559559           ENDIF 
    560560#if defined key_lim2 
    561            IF( ln_bdy_ice_frs ) THEN 
     561           IF( ln_ice_frs ) THEN 
    562562             frld_bdydta (:,1) =  frld_bdydta (:,2) 
    563563             hicif_bdydta(:,1) =  hicif_bdydta(:,2) 
     
    569569           ipk  = jpk 
    570570 
    571            IF( ln_bdy_tra_frs ) THEN 
     571           IF( ln_tra_frs ) THEN 
    572572              !  
    573573              igrd = 1                                   ! temperature 
     
    588588                 END DO 
    589589              END DO 
    590            ENDIF ! ln_bdy_tra_frs 
    591  
    592            IF(ln_bdy_dyn_frs) THEN 
     590           ENDIF ! ln_tra_frs 
     591 
     592           IF(ln_dyn_frs) THEN 
    593593              ! 
    594594              igrd = 2                                   ! u-velocity 
     
    609609                 END DO 
    610610              END DO 
    611            ENDIF ! ln_bdy_dyn_frs 
     611           ENDIF ! ln_dyn_frs 
    612612           ! 
    613613#if defined key_lim2 
    614            IF(ln_bdy_ice_frs) THEN 
     614           IF(ln_ice_frs) THEN 
    615615             ! 
    616616             igrd = 1                                    ! ice concentration 
     
    634634               hsnif_bdydta(ib,2) =  zdta( nbmap(ib,igrd), 1, 1 ) 
    635635             END DO 
    636            ENDIF ! ln_bdy_ice_frs 
     636           ENDIF ! ln_ice_frs 
    637637#endif 
    638638           ! 
    639            IF(lwp) WRITE(numout,*) 'bdy_dta : first record file used nbdy_b ',nbdy_b 
     639           IF(lwp) WRITE(numout,*) 'bdy_dta_frs : first record file used nbdy_b ',nbdy_b 
    640640           IF(lwp) WRITE(numout,*) '~~~~~~~~  last  record file used nbdy_a ',nbdy_a 
    641            IF (.NOT.ln_bdy_clim) THEN 
     641           IF (.NOT.ln_clim) THEN 
    642642              IF(lwp) WRITE(numout,*) 'first  record time (s): ', istep(nbdy_b) 
    643643              IF(lwp) WRITE(numout,*) 'model time (s)        : ', itimer 
     
    651651       ! ******************** 
    652652       !  
    653        IF( ln_bdy_clim ) THEN   ;   zxy = REAL( nday                   ) / REAL( nmonth_len(nbdy_b) ) + 0.5 - i15 
     653       IF( ln_clim ) THEN   ;   zxy = REAL( nday                   ) / REAL( nmonth_len(nbdy_b) ) + 0.5 - i15 
    654654       ELSEIF( istep(nbdy_b) == istep(nbdy_a) ) THEN  
    655655                                    zxy = 0.0_wp 
     
    657657       END IF 
    658658 
    659           IF(ln_bdy_tra_frs) THEN 
     659          IF(ln_tra_frs) THEN 
    660660             igrd = 1                                   ! temperature & salinity 
    661661             DO ib = 1, nblen(igrd) 
     
    667667          ENDIF 
    668668 
    669           IF(ln_bdy_dyn_frs) THEN 
     669          IF(ln_dyn_frs) THEN 
    670670             igrd = 2                                   ! u-velocity 
    671671             DO ib = 1, nblen(igrd) 
     
    684684 
    685685#if defined key_lim2 
    686           IF(ln_bdy_ice_frs) THEN 
     686          IF(ln_ice_frs) THEN 
    687687            igrd=1 
    688688            DO ib=1, nblen(igrd) 
     
    691691              hsnif_bdy(ib) = zxy * hsnif_bdydta(ib,2) + (1.-zxy) * hsnif_bdydta(ib,1) 
    692692            END DO 
    693           ENDIF ! just if ln_bdy_ice_frs is true 
     693          ENDIF ! just if ln_ice_frs is true 
    694694#endif 
    695695 
    696       END IF                       !end if ((nbdy_dta==1).AND.(ntimes_bdy>1)) 
     696      END IF                       !end if ((nn_dtactl==1).AND.(ntimes_bdy>1)) 
    697697     
    698698 
     
    701701      !                                                !---------------------! 
    702702      IF( kt == nitend ) THEN 
    703           IF(ln_bdy_tra_frs .or. ln_bdy_ice_frs) CALL iom_close( numbdyt )              ! Closing of the 3 files 
    704           IF(ln_bdy_dyn_frs) CALL iom_close( numbdyu ) 
    705           IF(ln_bdy_dyn_frs) CALL iom_close( numbdyv ) 
     703          IF(ln_tra_frs .or. ln_ice_frs) CALL iom_close( numbdyt )              ! Closing of the 3 files 
     704          IF(ln_dyn_frs) CALL iom_close( numbdyu ) 
     705          IF(ln_dyn_frs) CALL iom_close( numbdyv ) 
    706706      ENDIF 
    707707      ! 
    708       ENDIF ! ln_bdy_dyn_frs .OR. ln_bdy_tra_frs 
     708      ENDIF ! ln_dyn_frs .OR. ln_tra_frs 
    709709      ! 
    710    END SUBROUTINE bdy_dta 
    711  
    712  
    713    SUBROUTINE bdy_dta_bt( kt, jit, icycl ) 
     710   END SUBROUTINE bdy_dta_frs 
     711 
     712 
     713   SUBROUTINE bdy_dta_fla( kt, jit, icycl ) 
    714714      !!--------------------------------------------------------------------------- 
    715       !!                      ***  SUBROUTINE bdy_dta_bt  *** 
     715      !!                      ***  SUBROUTINE bdy_dta_fla  *** 
    716716      !!                     
    717717      !! ** Purpose :   Read unstructured boundary data for Flather condition 
     
    749749      !!--------------------------------------------------------------------------- 
    750750 
    751 !!gm   add here the same style as in bdy_dta 
    752 !!gm      clearly bdy_dta_bt and bdy_dta  can be combined...    
     751!!gm   add here the same style as in bdy_dta_frs 
     752!!gm      clearly bdy_dta_fla and bdy_dta_frs  can be combined...    
    753753!!gm      too many things duplicated in the read of data...   simplification can be done 
    754754 
     
    777777      itimer = itimer + jit*rdt/REAL(nn_baro,wp)      ! in non-climatological case 
    778778 
    779       IF ( ln_bdy_tides ) THEN 
     779      IF ( ln_tides ) THEN 
    780780 
    781781         ! -------------------------------------! 
     
    787787      ENDIF 
    788788 
    789       IF ( ln_bdy_dyn_fla ) THEN 
     789      IF ( ln_dyn_fla ) THEN 
    790790 
    791791         ! -------------------------------------! 
     
    804804 
    805805        IF(lwp) WRITE(numout,*) 
    806         IF(lwp) WRITE(numout,*)    'bdy_dta_bt :Initialize unstructured boundary data for barotropic variables.' 
     806        IF(lwp) WRITE(numout,*)    'bdy_dta_fla :Initialize unstructured boundary data for barotropic variables.' 
    807807        IF(lwp) WRITE(numout,*)    '~~~~~~~'  
    808808 
    809         IF( nbdy_dta == 0 ) THEN 
     809        IF( nn_dtactl == 0 ) THEN 
    810810          IF(lwp) WRITE(numout,*)  'Bdy data are taken from initial conditions' 
    811811 
    812         ELSEIF (nbdy_dta == 1) THEN 
     812        ELSEIF (nn_dtactl == 1) THEN 
    813813          IF(lwp) WRITE(numout,*)  'Bdy data are read in netcdf files' 
    814814 
     
    818818                                                     ! necessary time dumps in file are included 
    819819 
    820           clfile(4) = filbdy_data_bt_T 
    821           clfile(5) = filbdy_data_bt_U 
    822           clfile(6) = filbdy_data_bt_V 
     820          clfile(4) = cn_dta_fla_T 
     821          clfile(5) = cn_dta_fla_U 
     822          clfile(6) = cn_dta_fla_V 
    823823 
    824824          DO igrd = 4,6 
     
    872872            END DO 
    873873 
    874             IF ( .NOT. ln_bdy_clim ) THEN 
     874            IF ( .NOT. ln_clim ) THEN 
    875875               ! Check that times in file span model run time: 
    876876 
     
    886886               IF ( ntimes_bdy_bt == 1 ) CALL ctl_stop( & 
    887887                    'There is only one time dump in data files', & 
    888                     'Set ln_bdy_clim=.true. in namelist for constant bdy forcing.' ) 
     888                    'Set ln_clim=.true. in namelist for constant bdy forcing.' ) 
    889889 
    890890               zinterval_s = zstepr(2) - zstepr(1) 
     
    899899                     CALL ctl_stop( 'Last time dump in bdy file is before model final time', ctmp1 ) 
    900900               END IF 
    901             END IF ! .NOT. ln_bdy_clim 
     901            END IF ! .NOT. ln_clim 
    902902 
    903903            IF ( igrd .EQ. 4) THEN 
     
    938938 
    939939      ! Check number of time dumps:               
    940           IF (ln_bdy_clim) THEN 
     940          IF (ln_clim) THEN 
    941941            SELECT CASE ( ntimes_bdy_bt ) 
    942942            CASE( 1 ) 
     
    950950            CASE DEFAULT 
    951951              CALL ctl_stop( & 
    952                 'For climatological boundary forcing (ln_bdy_clim=.true.),',& 
     952                'For climatological boundary forcing (ln_clim=.true.),',& 
    953953                'bdy data files must contain 1 or 12 time dumps.' ) 
    954954            END SELECT 
     
    966966          IF(lwp) WRITE(numout,*) 'First record to read is ',nbdy_b_bt 
    967967 
    968         ENDIF ! endif (nbdy_dta == 1) 
    969  
    970       ! 1.2  Read first record in file if necessary (ie if nbdy_dta == 1) 
     968        ENDIF ! endif (nn_dtactl == 1) 
     969 
     970      ! 1.2  Read first record in file if necessary (ie if nn_dtactl == 1) 
    971971      ! ***************************************************************** 
    972972 
    973         IF ( nbdy_dta == 0) THEN 
     973        IF ( nn_dtactl == 0) THEN 
    974974          ! boundary data arrays are filled with initial conditions 
    975975          igrd = 5            ! U-points data  
     
    988988          END DO 
    989989 
    990         ELSEIF (nbdy_dta == 1) THEN 
     990        ELSEIF (nn_dtactl == 1) THEN 
    991991  
    992992        ! Set first record in the climatological case:    
    993           IF ((ln_bdy_clim).AND.(ntimes_bdy_bt==1)) THEN 
     993          IF ((ln_clim).AND.(ntimes_bdy_bt==1)) THEN 
    994994            nbdy_a_bt = 1 
    995           ELSEIF ((ln_bdy_clim).AND.(ntimes_bdy_bt==iman)) THEN 
     995          ELSEIF ((ln_clim).AND.(ntimes_bdy_bt==iman)) THEN 
    996996            nbdy_b_bt = 0 
    997997            nbdy_a_bt = imois 
     
    10021002         ! Open Netcdf files: 
    10031003 
    1004           CALL iom_open ( filbdy_data_bt_T, numbdyt_bt ) 
    1005           CALL iom_open ( filbdy_data_bt_U, numbdyu_bt ) 
    1006           CALL iom_open ( filbdy_data_bt_V, numbdyv_bt ) 
     1004          CALL iom_open ( cn_dta_fla_T, numbdyt_bt ) 
     1005          CALL iom_open ( cn_dta_fla_U, numbdyu_bt ) 
     1006          CALL iom_open ( cn_dta_fla_V, numbdyv_bt ) 
    10071007 
    10081008         ! Read first record: 
     
    10591059  
    10601060        ! In the case of constant boundary forcing fill bdy arrays once for all 
    1061         IF ((ln_bdy_clim).AND.(ntimes_bdy_bt==1)) THEN 
     1061        IF ((ln_clim).AND.(ntimes_bdy_bt==1)) THEN 
    10621062 
    10631063          ubtbdy  (:) = ubtbdydta  (:,2) 
     
    10771077      ! -------------------- ! 
    10781078 
    1079       IF ((nbdy_dta==1).AND.(ntimes_bdy_bt>1)) THEN  
     1079      IF ((nn_dtactl==1).AND.(ntimes_bdy_bt>1)) THEN  
    10801080 
    10811081      ! 2.1 Read one more record if necessary 
    10821082      !************************************** 
    10831083 
    1084         IF ( (ln_bdy_clim).AND.(imois/=nbdy_b_bt) ) THEN ! remember that nbdy_b_bt=0 for kt=nit000 
     1084        IF ( (ln_clim).AND.(imois/=nbdy_b_bt) ) THEN ! remember that nbdy_b_bt=0 for kt=nit000 
    10851085         nbdy_b_bt = imois 
    10861086         nbdy_a_bt = imois+1 
     
    10911091         lect=.true. 
    10921092 
    1093         ELSEIF ((.NOT.ln_bdy_clim).AND.(itimer >= istep_bt(nbdy_a_bt))) THEN 
     1093        ELSEIF ((.NOT.ln_clim).AND.(itimer >= istep_bt(nbdy_a_bt))) THEN 
    10941094          nbdy_b_bt=nbdy_a_bt 
    10951095          nbdy_a_bt=nbdy_a_bt+1 
     
    11431143 
    11441144 
    1145          IF(lwp) WRITE(numout,*) 'bdy_dta : first record file used nbdy_b_bt ',nbdy_b_bt 
     1145         IF(lwp) WRITE(numout,*) 'bdy_dta_fla : first record file used nbdy_b_bt ',nbdy_b_bt 
    11461146         IF(lwp) WRITE(numout,*) '~~~~~~~~  last  record file used nbdy_a_bt ',nbdy_a_bt 
    1147          IF (.NOT.ln_bdy_clim) THEN 
     1147         IF (.NOT.ln_clim) THEN 
    11481148           IF(lwp) WRITE(numout,*) 'first  record time (s): ', istep_bt(nbdy_b_bt) 
    11491149           IF(lwp) WRITE(numout,*) 'model time (s)        : ', itimer 
     
    11561156      ! *************************** 
    11571157     
    1158         IF (ln_bdy_clim) THEN 
     1158        IF (ln_clim) THEN 
    11591159          zxy = REAL( nday, wp ) / REAL( nmonth_len(nbdy_b_bt), wp ) + 0.5 - i15 
    11601160        ELSE           
     
    11811181 
    11821182 
    1183       END IF !end if ((nbdy_dta==1).AND.(ntimes_bdy_bt>1)) 
     1183      END IF !end if ((nn_dtactl==1).AND.(ntimes_bdy_bt>1)) 
    11841184     
    11851185      ! ------------------- ! 
     
    11941194      ENDIF 
    11951195 
    1196       ENDIF ! ln_bdy_dyn_frs 
    1197  
    1198       END SUBROUTINE bdy_dta_bt 
     1196      ENDIF ! ln_dyn_frs 
     1197 
     1198      END SUBROUTINE bdy_dta_fla 
    11991199 
    12001200 
     
    12041204   !!---------------------------------------------------------------------- 
    12051205CONTAINS 
    1206    SUBROUTINE bdy_dta( kt )              ! Empty routine 
    1207       WRITE(*,*) 'bdy_dta: You should not have seen this print! error?', kt 
    1208    END SUBROUTINE bdy_dta 
    1209    SUBROUTINE bdy_dta_bt( kt, kit, icycle )      ! Empty routine 
    1210       WRITE(*,*) 'bdy_dta: You should not have seen this print! error?', kt, kit 
    1211    END SUBROUTINE bdy_dta_bt 
     1206   SUBROUTINE bdy_dta_frs( kt )              ! Empty routine 
     1207      WRITE(*,*) 'bdy_dta_frs: You should not have seen this print! error?', kt 
     1208   END SUBROUTINE bdy_dta_frs 
     1209   SUBROUTINE bdy_dta_fla( kt, kit, icycle )      ! Empty routine 
     1210      WRITE(*,*) 'bdy_dta_frs: You should not have seen this print! error?', kt, kit 
     1211   END SUBROUTINE bdy_dta_fla 
    12121212#endif 
    12131213 
  • branches/devukmo2010/NEMO/OPA_SRC/BDY/bdydyn.F90

    r2185 r2253  
    6060      !!---------------------------------------------------------------------- 
    6161      ! 
    62       IF(ln_bdy_dyn_frs) THEN       ! If this is false, then this routine does nothing.  
     62      IF(ln_dyn_frs) THEN       ! If this is false, then this routine does nothing.  
    6363         ! 
    6464         IF( kt == nit000 ) THEN 
    6565            IF(lwp) WRITE(numout,*) 
    66             IF(lwp) WRITE(numout,*) 'bdy_dyn : Flow Relaxation Scheme on momentum' 
     66            IF(lwp) WRITE(numout,*) 'bdy_dyn_frs : Flow Relaxation Scheme on momentum' 
    6767            IF(lwp) WRITE(numout,*) '~~~~~~~' 
    6868         ENDIF 
     
    8989         CALL lbc_lnk( ua, 'U', -1. )   ;   CALL lbc_lnk( va, 'V', -1. )   ! Boundary points should be updated 
    9090         ! 
    91       ENDIF ! ln_bdy_dyn_frs 
     91      ENDIF ! ln_dyn_frs 
    9292      ! 
    9393   END SUBROUTINE bdy_dyn_frs 
     
    107107      !!              
    108108      !!              - Apply Flather boundary conditions on normal barotropic velocities  
    109       !!                (ln_bdy_dyn_fla=.true. or ln_bdy_tides=.true.) 
     109      !!                (ln_dyn_fla=.true. or ln_tides=.true.) 
    110110      !! 
    111111      !! ** WARNINGS about FLATHER implementation: 
     
    134134      ! ---------------------------------!  
    135135      
    136       IF(ln_bdy_dyn_fla .OR. ln_bdy_tides) THEN ! If these are both false, then this routine does nothing.  
     136      IF(ln_dyn_fla .OR. ln_tides) THEN ! If these are both false, then this routine does nothing.  
    137137 
    138138         ! Fill temporary array with ssh data (here spgu): 
     
    142142            ii = nbi(jb,igrd) 
    143143            ij = nbj(jb,igrd) 
    144             IF( ln_bdy_dyn_fla ) spgu(ii, ij) = sshbdy(jb) 
    145             IF( ln_bdy_tides )   spgu(ii, ij) = spgu(ii, ij) + sshtide(jb) 
     144            IF( ln_dyn_fla ) spgu(ii, ij) = sshbdy(jb) 
     145            IF( ln_tides )   spgu(ii, ij) = spgu(ii, ij) + sshtide(jb) 
    146146         END DO 
    147147         ! 
     
    175175         CALL lbc_lnk( va_e, 'V', -1. )   ! 
    176176         ! 
    177       ENDIF ! ln_bdy_dyn_fla .or. ln_bdy_tides 
     177      ENDIF ! ln_dyn_fla .or. ln_tides 
    178178      ! 
    179179   END SUBROUTINE bdy_dyn_fla 
  • branches/devukmo2010/NEMO/OPA_SRC/BDY/bdyice.F90

    r2185 r2253  
    1111   !!   'key_lim2'                                                 LIM-2 sea ice model 
    1212   !!---------------------------------------------------------------------- 
    13    !!   bdy_ice        : Relaxation of tracers on unstructured open boundaries 
     13   !!   bdy_ice_frs        : Relaxation of tracers on unstructured open boundaries 
    1414   !!---------------------------------------------------------------------- 
    1515   USE oce             ! ocean dynamics and tracers variables 
     
    2323   PRIVATE 
    2424 
    25    PUBLIC   bdy_ice    ! routine called in sbcmod 
     25   PUBLIC   bdy_ice_frs    ! routine called in sbcmod 
    2626 
    2727   !!---------------------------------------------------------------------- 
     
    3131CONTAINS 
    3232 
    33    SUBROUTINE bdy_ice( kt ) 
     33   SUBROUTINE bdy_ice_frs( kt ) 
    3434      !!------------------------------------------------------------------------------ 
    35       !!                 ***  SUBROUTINE bdy_ice  *** 
     35      !!                 ***  SUBROUTINE bdy_ice_frs  *** 
    3636      !!                     
    3737      !! ** Purpose : Apply the Flow Relaxation Scheme for sea-ice fields in the case  
     
    5050      jgrd = 1      ! Everything is at T-points here 
    5151      ! 
    52       IF( ln_bdy_ice_frs ) THEN     ! update ice fields by relaxation at the boundary 
     52      IF( ln_ice_frs ) THEN     ! update ice fields by relaxation at the boundary 
    5353         DO jb = 1, nblen(jgrd) 
    5454            DO jk = 1, jpkm1 
     
    6565         CALL lbc_lnk( hicif, 'T', 1. )   ;   CALL lbc_lnk( hsnif, 'T', 1. ) 
    6666         ! 
    67       ELSE                          ! we have called this routine without ln_bdy_ice_frs not set 
    68          IF( kt == nit000 )   CALL ctl_warn( 'E R R O R (possible) called bdy_ice when ln_bdy_ice_frs is false?' ) 
     67      ELSE                          ! we have called this routine without ln_ice_frs not set 
     68         IF( kt == nit000 )   CALL ctl_warn( 'E R R O R (possible) called bdy_ice_frs when ln_ice_frs is false?' ) 
    6969      ENDIF 
    7070      !       
    71    END SUBROUTINE bdy_ice 
     71   END SUBROUTINE bdy_ice_frs 
    7272#else 
    7373   !!--------------------------------------------------------------------------------- 
     
    7575   !!--------------------------------------------------------------------------------- 
    7676CONTAINS 
    77    SUBROUTINE bdy_ice( kt )      ! Empty routine 
    78       WRITE(*,*) 'bdy_ice: You should not have seen this print! error?', kt 
    79    END SUBROUTINE bdy_ice 
     77   SUBROUTINE bdy_ice_frs( kt )      ! Empty routine 
     78      WRITE(*,*) 'bdy_ice_frs: You should not have seen this print! error?', kt 
     79   END SUBROUTINE bdy_ice_frs 
    8080#endif 
    8181 
  • branches/devukmo2010/NEMO/OPA_SRC/BDY/bdyini.F90

    r2185 r2253  
    6666      CHARACTER(LEN=80),DIMENSION(6)      ::   clfile 
    6767      !! 
    68       NAMELIST/nambdy/filbdy_mask, filbdy_data_T, filbdy_data_U, filbdy_data_V,          & 
    69          &            filbdy_data_bt_T, filbdy_data_bt_U, filbdy_data_bt_V,              & 
    70          &            ln_bdy_tides, ln_bdy_clim, ln_bdy_vol, ln_bdy_mask,                & 
    71          &            ln_bdy_dyn_fla, ln_bdy_dyn_frs, ln_bdy_tra_frs,ln_bdy_ice_frs,     & 
    72          &            nbdy_dta, nb_rimwidth, volbdy 
     68      NAMELIST/nambdy/cn_mask, cn_dta_frs_T, cn_dta_frs_U, cn_dta_frs_V,          & 
     69         &            cn_dta_fla_T, cn_dta_fla_U, cn_dta_fla_V,              & 
     70         &            ln_tides, ln_clim, ln_vol, ln_mask,                & 
     71         &            ln_dyn_fla, ln_dyn_frs, ln_tra_frs,ln_ice_frs,     & 
     72         &            nn_dtactl, nn_rimwidth, nn_volctl 
    7373      !!---------------------------------------------------------------------- 
    7474 
     
    9090      IF(lwp) WRITE(numout,*) '         nambdy' 
    9191 
    92       !                                         ! check type of data used (nbdy_dta value) 
    93       IF(lwp) WRITE(numout,*) 'nbdy_dta =', nbdy_dta       
     92      !                                         ! check type of data used (nn_dtactl value) 
     93      IF(lwp) WRITE(numout,*) 'nn_dtactl =', nn_dtactl       
    9494      IF(lwp) WRITE(numout,*) 
    95       SELECT CASE( nbdy_dta )                   !  
     95      SELECT CASE( nn_dtactl )                   !  
    9696      CASE( 0 )      ;   IF(lwp) WRITE(numout,*) '      initial state used for bdy data'         
    9797      CASE( 1 )      ;   IF(lwp) WRITE(numout,*) '      boundary data taken from file' 
    98       CASE DEFAULT   ;   CALL ctl_stop( 'nbdy_dta must be 0 or 1' ) 
     98      CASE DEFAULT   ;   CALL ctl_stop( 'nn_dtactl must be 0 or 1' ) 
    9999      END SELECT 
    100100 
    101101      IF(lwp) WRITE(numout,*) 
    102       IF(lwp) WRITE(numout,*) 'Boundary rim width for the FRS nb_rimwidth = ', nb_rimwidth 
     102      IF(lwp) WRITE(numout,*) 'Boundary rim width for the FRS nn_rimwidth = ', nn_rimwidth 
    103103 
    104104      IF(lwp) WRITE(numout,*) 
    105       IF(lwp) WRITE(numout,*) '      volbdy = ', volbdy 
    106  
    107       IF( ln_bdy_vol ) THEN                     ! check volume conservation (volbdy value) 
    108          SELECT CASE ( volbdy ) 
     105      IF(lwp) WRITE(numout,*) '      nn_volctl = ', nn_volctl 
     106 
     107      IF( ln_vol ) THEN                     ! check volume conservation (nn_volctl value) 
     108         SELECT CASE ( nn_volctl ) 
    109109         CASE( 1 )      ;   IF(lwp) WRITE(numout,*) '      The total volume will be constant' 
    110110         CASE( 0 )      ;   IF(lwp) WRITE(numout,*) '      The total volume will vary according to the surface E-P flux' 
    111          CASE DEFAULT   ;   CALL ctl_stop( 'volbdy must be 0 or 1' ) 
     111         CASE DEFAULT   ;   CALL ctl_stop( 'nn_volctl must be 0 or 1' ) 
    112112         END SELECT 
    113113         IF(lwp) WRITE(numout,*) 
     
    117117      ENDIF 
    118118 
    119       IF( ln_bdy_tides ) THEN 
     119      IF( ln_tides ) THEN 
    120120        IF(lwp) WRITE(numout,*) 'Tidal harmonic forcing at unstructured open boundaries' 
    121121        IF(lwp) WRITE(numout,*) 
    122122      ENDIF 
    123123 
    124       IF( ln_bdy_dyn_fla ) THEN 
     124      IF( ln_dyn_fla ) THEN 
    125125        IF(lwp) WRITE(numout,*) 'Flather condition on U, V at unstructured open boundaries' 
    126126        IF(lwp) WRITE(numout,*) 
    127127      ENDIF 
    128128 
    129       IF( ln_bdy_dyn_frs ) THEN 
     129      IF( ln_dyn_frs ) THEN 
    130130        IF(lwp) WRITE(numout,*) 'FRS condition on U and V at unstructured open boundaries' 
    131131        IF(lwp) WRITE(numout,*) 
    132132      ENDIF 
    133133 
    134       IF( ln_bdy_tra_frs ) THEN 
     134      IF( ln_tra_frs ) THEN 
    135135        IF(lwp) WRITE(numout,*) 'FRS condition on T & S fields at unstructured open boundaries' 
    136136        IF(lwp) WRITE(numout,*) 
    137137      ENDIF 
    138138 
    139       IF( ln_bdy_ice_frs ) THEN 
     139      IF( ln_ice_frs ) THEN 
    140140        IF(lwp) WRITE(numout,*) 'FRS condition on ice fields at unstructured open boundaries' 
    141141        IF(lwp) WRITE(numout,*) 
    142142      ENDIF 
    143143 
    144       IF( ln_bdy_tides )   CALL tide_init      ! Read tides namelist  
     144      IF( ln_tides )   CALL tide_init      ! Read tides namelist  
    145145 
    146146 
     
    156156         zmask(         :                ,:) = 0.e0 
    157157         zmask(jpizoom+1:jpizoom+jpiglo-2,:) = 1.e0           
    158       ELSE IF( ln_bdy_mask ) THEN 
    159          CALL iom_open( filbdy_mask, inum ) 
     158      ELSE IF( ln_mask ) THEN 
     159         CALL iom_open( cn_mask, inum ) 
    160160         CALL iom_get ( inum, jpdom_data, 'bdy_msk', zmask(:,:) ) 
    161161         CALL iom_close( inum ) 
     
    190190      IF( cp_cfg == "eel" .AND. jp_cfg == 5 ) THEN 
    191191         icount = 0 
    192          DO ir = 1, nb_rimwidth                  ! Define west boundary (from ii=2 to ii=1+nb_rimwidth): 
     192         DO ir = 1, nn_rimwidth                  ! Define west boundary (from ii=2 to ii=1+nn_rimwidth): 
    193193            DO ij = 3, jpjglo-2 
    194194               icount = icount + 1 
     
    199199         END DO 
    200200         ! 
    201          DO ir = 1, nb_rimwidth                  ! Define east boundary (from ii=jpiglo-1 to ii=jpiglo-nb_rimwidth): 
     201         DO ir = 1, nn_rimwidth                  ! Define east boundary (from ii=jpiglo-1 to ii=jpiglo-nn_rimwidth): 
    202202            DO ij=3,jpjglo-2 
    203203               icount = icount + 1 
     
    211211      ELSE            ! Read indices and distances in unstructured boundary data files  
    212212         ! 
    213          IF( ln_bdy_tides ) THEN             ! Read tides input files for preference in case there are no bdydata files 
     213         IF( ln_tides ) THEN             ! Read tides input files for preference in case there are no bdydata files 
    214214            clfile(4) = TRIM(filtide)//TRIM(tide_cpt(1))//'_grid_T.nc' 
    215215            clfile(5) = TRIM(filtide)//TRIM(tide_cpt(1))//'_grid_U.nc' 
    216216            clfile(6) = TRIM(filtide)//TRIM(tide_cpt(1))//'_grid_V.nc' 
    217217         ENDIF 
    218          IF( ln_bdy_dyn_fla .AND. .NOT. ln_bdy_tides ) THEN  
    219             clfile(4) = filbdy_data_bt_T 
    220             clfile(5) = filbdy_data_bt_U 
    221             clfile(6) = filbdy_data_bt_V 
     218         IF( ln_dyn_fla .AND. .NOT. ln_tides ) THEN  
     219            clfile(4) = cn_dta_fla_T 
     220            clfile(5) = cn_dta_fla_U 
     221            clfile(6) = cn_dta_fla_V 
    222222         ENDIF 
    223223 
    224          IF( ln_bdy_tra_frs ) THEN  
    225             clfile(1) = filbdy_data_T 
    226             IF( .NOT. ln_bdy_dyn_frs ) THEN  
    227                clfile(2) = filbdy_data_T     ! Dummy read re read T file for sake of 6 files 
    228                clfile(3) = filbdy_data_T     ! 
     224         IF( ln_tra_frs ) THEN  
     225            clfile(1) = cn_dta_frs_T 
     226            IF( .NOT. ln_dyn_frs ) THEN  
     227               clfile(2) = cn_dta_frs_T     ! Dummy read re read T file for sake of 6 files 
     228               clfile(3) = cn_dta_frs_T     ! 
    229229            ENDIF 
    230230         ENDIF           
    231          IF( ln_bdy_dyn_frs ) THEN  
    232             IF( .NOT. ln_bdy_tra_frs )   clfile(1) = filbdy_data_U      ! Dummy Read  
    233             clfile(2) = filbdy_data_U 
    234             clfile(3) = filbdy_data_V  
     231         IF( ln_dyn_frs ) THEN  
     232            IF( .NOT. ln_tra_frs )   clfile(1) = cn_dta_frs_U      ! Dummy Read  
     233            clfile(2) = cn_dta_frs_U 
     234            clfile(3) = cn_dta_frs_V  
    235235         ENDIF 
    236236 
    237237         !                                   ! how many files are we to read in? 
    238          IF(ln_bdy_tides .OR. ln_bdy_dyn_fla)   igrd_start = 4 
    239          ! 
    240          IF(ln_bdy_tra_frs    ) THEN   ;   igrd_start = 1 
    241          ELSEIF(ln_bdy_dyn_frs) THEN   ;   igrd_start = 2 
     238         IF(ln_tides .OR. ln_dyn_fla)   igrd_start = 4 
     239         ! 
     240         IF(ln_tra_frs    ) THEN   ;   igrd_start = 1 
     241         ELSEIF(ln_dyn_frs) THEN   ;   igrd_start = 2 
    242242         ENDIF 
    243243         ! 
    244          IF( ln_bdy_tra_frs   )   igrd_end = 1 
    245          ! 
    246          IF(ln_bdy_dyn_fla .OR. ln_bdy_tides) THEN   ;   igrd_end = 6 
    247          ELSEIF( ln_bdy_dyn_frs             ) THEN   ;   igrd_end = 3 
     244         IF( ln_tra_frs   )   igrd_end = 1 
     245         ! 
     246         IF(ln_dyn_fla .OR. ln_tides) THEN   ;   igrd_end = 6 
     247         ELSEIF( ln_dyn_frs             ) THEN   ;   igrd_end = 3 
    248248         ENDIF 
    249249 
     
    274274               IF(lwp) WRITE(numout,*) 
    275275               IF(lwp) WRITE(numout,*) ' Maximum rimwidth in file is ', ibr_max 
    276                IF(lwp) WRITE(numout,*) ' nb_rimwidth from namelist is ', nb_rimwidth 
    277                IF (ibr_max < nb_rimwidth)   CALL ctl_stop( 'nb_rimwidth is larger than maximum rimwidth in file' ) 
     276               IF(lwp) WRITE(numout,*) ' nn_rimwidth from namelist is ', nn_rimwidth 
     277               IF (ibr_max < nn_rimwidth)   CALL ctl_stop( 'nn_rimwidth is larger than maximum rimwidth in file' ) 
    278278            ENDIF !Check igrd < 4 
    279279            ! 
     
    296296         nblenrim(igrd) = 0 
    297297         nblendta(igrd) = 0 
    298          DO ir=1, nb_rimwidth 
     298         DO ir=1, nn_rimwidth 
    299299            DO ib = 1, jpbdta 
    300300               ! check if point is in local domain and equals ir 
     
    327327         DO ib = 1, nblen(igrd) 
    328328            nbw(ib,igrd) = 1.- TANH( FLOAT( nbr(ib,igrd) - 1 ) *0.5 )                     ! tanh formulation 
    329 !           nbw(ib,igrd) = (FLOAT(nb_rimwidth+1-nbr(ib,igrd))/FLOAT(nb_rimwidth))**2      ! quadratic 
    330 !           nbw(ib,igrd) =  FLOAT(nb_rimwidth+1-nbr(ib,igrd))/FLOAT(nb_rimwidth)          ! linear 
     329!           nbw(ib,igrd) = (FLOAT(nn_rimwidth+1-nbr(ib,igrd))/FLOAT(nn_rimwidth))**2      ! quadratic 
     330!           nbw(ib,igrd) =  FLOAT(nn_rimwidth+1-nbr(ib,igrd))/FLOAT(nn_rimwidth)          ! linear 
    331331         END DO 
    332332      END DO  
     
    382382      CALL lbc_lnk( bdyumask(:,:), 'U', 1. )   ;   CALL lbc_lnk( bdyvmask(:,:), 'V', 1. ) 
    383383 
    384       IF( ln_bdy_vol .OR. ln_bdy_dyn_fla ) THEN      ! Indices and directions of rim velocity components 
     384      IF( ln_vol .OR. ln_dyn_fla ) THEN      ! Indices and directions of rim velocity components 
    385385         ! 
    386386         !flagu = -1 : u component is normal to the dynamical boundary but its direction is outward 
     
    431431      ! ---------------------------------------------------- 
    432432      bdysurftot = 0.e0  
    433       IF( ln_bdy_vol ) THEN   
     433      IF( ln_vol ) THEN   
    434434         igrd = 2      ! Lateral surface at U-points 
    435435         DO ib = 1, nblenrim(igrd) 
     
    468468      ! Read in tidal constituents and adjust for model start time 
    469469      ! ---------------------------------------------------------- 
    470       IF( ln_bdy_tides )   CALL tide_data 
     470      IF( ln_tides )   CALL tide_data 
    471471      ! 
    472472   END SUBROUTINE bdy_init 
  • branches/devukmo2010/NEMO/OPA_SRC/BDY/bdytra.F90

    r2185 r2253  
    1111   !!   'key_bdy'                     Unstructured Open Boundary Conditions 
    1212   !!---------------------------------------------------------------------- 
    13    !!   bdy_tra        : Relaxation of tracers on unstructured open boundaries 
     13   !!   bdy_tra_frs        : Relaxation of tracers on unstructured open boundaries 
    1414   !!---------------------------------------------------------------------- 
    1515   USE oce             ! ocean dynamics and tracers variables 
     
    2222   PRIVATE 
    2323 
    24    PUBLIC bdy_tra     ! routine called in tranxt.F90  
     24   PUBLIC bdy_tra_frs     ! routine called in tranxt.F90  
    2525 
    2626   !!---------------------------------------------------------------------- 
     
    3131CONTAINS 
    3232 
    33    SUBROUTINE bdy_tra( kt ) 
     33   SUBROUTINE bdy_tra_frs( kt ) 
    3434      !!---------------------------------------------------------------------- 
    35       !!                 ***  SUBROUTINE bdy_tra  *** 
     35      !!                 ***  SUBROUTINE bdy_tra_frs  *** 
    3636      !!                     
    3737      !! ** Purpose : Apply the Flow Relaxation Scheme for tracers in the   
     
    4747      !!---------------------------------------------------------------------- 
    4848      ! 
    49       IF(ln_bdy_tra_frs) THEN       ! If this is false, then this routine does nothing.  
     49      IF(ln_tra_frs) THEN       ! If this is false, then this routine does nothing.  
    5050         ! 
    5151         IF( kt == nit000 ) THEN 
    5252            IF(lwp) WRITE(numout,*) 
    53             IF(lwp) WRITE(numout,*) 'bdy_tra : Flow Relaxation Scheme for tracers' 
     53            IF(lwp) WRITE(numout,*) 'bdy_tra_frs : Flow Relaxation Scheme for tracers' 
    5454            IF(lwp) WRITE(numout,*) '~~~~~~~' 
    5555         ENDIF 
     
    6868         CALL lbc_lnk( ta, 'T', 1. )   ; CALL lbc_lnk( sa, 'T', 1. )    ! Boundary points should be updated 
    6969         ! 
    70       ENDIF ! ln_bdy_tra_frs 
     70      ENDIF ! ln_tra_frs 
    7171      ! 
    72    END SUBROUTINE bdy_tra 
     72   END SUBROUTINE bdy_tra_frs 
    7373    
    7474#else 
     
    7777   !!---------------------------------------------------------------------- 
    7878CONTAINS 
    79    SUBROUTINE bdy_tra(kt)      ! Empty routine 
    80       WRITE(*,*) 'bdy_tra: You should not have seen this print! error?', kt 
    81    END SUBROUTINE bdy_tra 
     79   SUBROUTINE bdy_tra_frs(kt)      ! Empty routine 
     80      WRITE(*,*) 'bdy_tra_frs: You should not have seen this print! error?', kt 
     81   END SUBROUTINE bdy_tra_frs 
    8282#endif 
    8383 
  • branches/devukmo2010/NEMO/OPA_SRC/BDY/bdyvol.F90

    r2185 r2253  
    6161      !!            zero (z_cflxemp=0) to calculate the correction velocity. So 
    6262      !!            it will only balance the flux through open boundaries. 
    63       !!            (set volbdy to 0 in tne namelist for this option) 
     63      !!            (set nn_volctl to 0 in tne namelist for this option) 
    6464      !!         2/ The volume is constant even with E-P flux. In this case 
    6565      !!            the correction velocity must balance both the flux  
    6666      !!            through open boundaries and the ones through the free 
    6767      !!            surface.  
    68       !!            (set volbdy to 1 in tne namelist for this option) 
     68      !!            (set nn_volctl to 1 in tne namelist for this option) 
    6969      !!---------------------------------------------------------------------- 
    7070      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
     
    7474      REAL(wp) ::   zubtpecor, z_cflxemp, ztranst 
    7575      !!----------------------------------------------------------------------------- 
     76 
     77      IF( ln_vol ) THEN 
    7678 
    7779      IF( kt == nit000 ) THEN  
     
    110112      ! The normal velocity correction 
    111113      ! ------------------------------ 
    112       IF( volbdy==1 ) THEN   ;   zubtpecor = ( zubtpecor - z_cflxemp) / bdysurftot  
     114      IF( nn_volctl==1 ) THEN   ;   zubtpecor = ( zubtpecor - z_cflxemp) / bdysurftot  
    113115      ELSE                   ;   zubtpecor =   zubtpecor             / bdysurftot 
    114116      END IF 
     
    149151      END IF  
    150152      ! 
     153      END IF ! ln_vol 
     154 
    151155   END SUBROUTINE bdy_vol 
    152156 
  • branches/devukmo2010/NEMO/OPA_SRC/DYN/dynspg_flt.F90

    r2128 r2253  
    190190#endif 
    191191#if defined key_bdy 
    192       ! Update velocities on unstructured boundary using the Flow Relaxation Scheme 
    193       CALL bdy_dyn_frs( kt ) 
    194  
    195       IF (ln_bdy_vol) THEN 
    196       ! Correction of the barotropic component velocity to control the volume of the system 
    197         CALL bdy_vol( kt ) 
    198       ENDIF 
     192      CALL bdy_dyn_frs( kt )       ! Update velocities on unstructured boundary using the Flow Relaxation Scheme 
     193      CALL bdy_vol( kt )           ! Correction of the barotropic component velocity to control the volume of the system 
    199194#endif 
    200195#if defined key_agrif 
  • branches/devukmo2010/NEMO/OPA_SRC/DYN/dynspg_ts.F90

    r2199 r2253  
    352352         !                                                !* Update the forcing (OBC, BDY and tides) 
    353353         !                                                !  ------------------ 
    354          IF( lk_obc                     )   CALL obc_dta_bt( kt, jn   ) 
    355          IF( lk_bdy  .OR.  ln_bdy_tides )   CALL bdy_dta_bt( kt, jn+1, icycle ) 
     354         IF( lk_obc )   CALL obc_dta_bt( kt, jn   ) 
     355         IF( lk_bdy )   CALL bdy_dta_bt( kt, jn+1, icycle ) 
    356356 
    357357         !                                                !* after ssh_e 
Note: See TracChangeset for help on using the changeset viewer.