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 4990 for trunk/NEMOGCM/NEMO/LIM_SRC_3/limdyn.F90 – NEMO

Ignore:
Timestamp:
2014-12-15T17:42:49+01:00 (9 years ago)
Author:
timgraham
Message:

Merged branches/2014/dev_MERGE_2014 back onto the trunk as follows:

In the working copy of branch ran:
svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk@HEAD
1 conflict in LIM_SRC_3/limdiahsb.F90
Resolved by keeping the version from dev_MERGE_2014 branch
and commited at r4989

In working copy run:
svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
to switch working copy

Run:
svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2014/dev_MERGE_2014
to merge the branch into the trunk - no conflicts at this stage.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/LIM_SRC_3/limdyn.F90

    r4872 r4990  
    6464      INTEGER  ::   i_j1, i_jpj       ! Starting/ending j-indices for rheology 
    6565      REAL(wp) ::   zcoef             ! local scalar 
    66       REAL(wp), POINTER, DIMENSION(:)   ::   zind           ! i-averaged indicator of sea-ice 
     66      REAL(wp), POINTER, DIMENSION(:)   ::   zswitch        ! i-averaged indicator of sea-ice 
    6767      REAL(wp), POINTER, DIMENSION(:)   ::   zmsk           ! i-averaged of tmask 
    6868      REAL(wp), POINTER, DIMENSION(:,:) ::   zu_io, zv_io   ! ice-ocean velocity 
     
    7474 
    7575      CALL wrk_alloc( jpi, jpj, zu_io, zv_io ) 
    76       CALL wrk_alloc( jpj, zind, zmsk ) 
     76      CALL wrk_alloc( jpj, zswitch, zmsk ) 
    7777 
    7878      IF( kt == nit000 )   CALL lim_dyn_init   ! Initialization (first time-step only) 
     
    100100            ! 
    101101            DO jj = 1, jpj 
    102                zind(jj) = SUM( 1.0 - at_i(:,jj) )   ! = REAL(jpj) if ocean everywhere on a j-line 
     102               zswitch(jj) = SUM( 1.0 - at_i(:,jj) )   ! = REAL(jpj) if ocean everywhere on a j-line 
    103103               zmsk(jj) = SUM( tmask(:,jj,1)    )   ! = 0         if land  everywhere on a j-line 
    104104            END DO 
     
    110110               i_j1  = njeq 
    111111               i_jpj = jpj 
    112                DO WHILE ( i_j1 <= jpj .AND. zind(i_j1) == FLOAT(jpi) .AND. zmsk(i_j1) /=0 ) 
     112               DO WHILE ( i_j1 <= jpj .AND. zswitch(i_j1) == FLOAT(jpi) .AND. zmsk(i_j1) /=0 ) 
    113113                  i_j1 = i_j1 + 1 
    114114               END DO 
     
    120120               i_j1  =  1 
    121121               i_jpj = njeq 
    122                DO WHILE ( i_jpj >= 1 .AND. zind(i_jpj) == FLOAT(jpi) .AND. zmsk(i_jpj) /=0 ) 
     122               DO WHILE ( i_jpj >= 1 .AND. zswitch(i_jpj) == FLOAT(jpi) .AND. zmsk(i_jpj) /=0 ) 
    123123                  i_jpj = i_jpj - 1 
    124124               END DO 
     
    132132               !                                 ! latitude strip 
    133133               i_j1  = 1 
    134                DO WHILE ( i_j1 <= jpj .AND. zind(i_j1) == FLOAT(jpi) .AND. zmsk(i_j1) /=0 ) 
     134               DO WHILE ( i_j1 <= jpj .AND. zswitch(i_j1) == FLOAT(jpi) .AND. zmsk(i_j1) /=0 ) 
    135135                  i_j1 = i_j1 + 1 
    136136               END DO 
     
    138138 
    139139               i_jpj  = jpj 
    140                DO WHILE ( i_jpj >= 1  .AND. zind(i_jpj) == FLOAT(jpi) .AND. zmsk(i_jpj) /=0 ) 
     140               DO WHILE ( i_jpj >= 1  .AND. zswitch(i_jpj) == FLOAT(jpi) .AND. zmsk(i_jpj) /=0 ) 
    141141                  i_jpj = i_jpj - 1 
    142142               END DO 
     
    221221      ! 
    222222      CALL wrk_dealloc( jpi, jpj, zu_io, zv_io ) 
    223       CALL wrk_dealloc( jpj, zind, zmsk ) 
     223      CALL wrk_dealloc( jpj, zswitch, zmsk ) 
    224224      ! 
    225225      IF( nn_timing == 1 )  CALL timing_stop('limdyn') 
     
    241241      !!------------------------------------------------------------------- 
    242242      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    243       NAMELIST/namicedyn/ epsd, om, cw, angvg, pstar,   & 
     243      NAMELIST/namicedyn/ epsd, om, cw, pstar,   & 
    244244         &                c_rhg, creepl, ecc, ahi0,     & 
    245245         &                nevp, relast, alphaevp, hminrhg 
     
    262262         WRITE(numout,*) '   relaxation constant                              om     = ', om 
    263263         WRITE(numout,*) '   drag coefficient for oceanic stress              cw     = ', cw 
    264          WRITE(numout,*) '   turning angle for oceanic stress                 angvg  = ', angvg 
    265264         WRITE(numout,*) '   first bulk-rheology parameter                    pstar  = ', pstar 
    266265         WRITE(numout,*) '   second bulk-rhelogy parameter                    c_rhg  = ', c_rhg 
     
    274273      ENDIF 
    275274      ! 
    276       IF( angvg /= 0._wp ) THEN 
    277          CALL ctl_warn( 'lim_dyn_init: turning angle for oceanic stress not properly coded for EVP ',   & 
    278             &           '(see limsbc module). We force  angvg = 0._wp'  ) 
    279          angvg = 0._wp 
    280       ENDIF 
    281        
    282275      usecc2 = 1._wp / ( ecc * ecc ) 
    283276      rhoco  = rau0  * cw 
    284       angvg  = angvg * rad 
    285       sangvg = SIN( angvg ) 
    286       cangvg = COS( angvg ) 
    287       pstarh = pstar * 0.5_wp 
    288277 
    289278      ! elastic damping 
Note: See TracChangeset for help on using the changeset viewer.