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 7646 for trunk/NEMOGCM/NEMO/LIM_SRC_2 – NEMO

Ignore:
Timestamp:
2017-02-06T10:25:03+01:00 (7 years ago)
Author:
timgraham
Message:

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

Location:
trunk/NEMOGCM/NEMO/LIM_SRC_2
Files:
1 deleted
10 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/LIM_SRC_2/dom_ice_2.F90

    r3764 r7646  
    2727      !                                        !  (otherwise = jpj+10 (SH) or -10 (SH) ) 
    2828 
    29    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)         ::   fs2cor , fcor     !: coriolis factor and coeficient 
    3029   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)         ::   covrai            !: sine of geographic latitude 
    3130   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)         ::   area              !: surface of grid cell  
     
    4847      ierr(:) = 0 
    4948      ! 
    50       ALLOCATE( fs2cor(jpi,jpj)     , fcor(jpi,jpj) ,                                   & 
    51          &      covrai(jpi,jpj)     , area(jpi,jpj) , tms(jpi,jpj) , tmu(jpi,jpj) ,     & 
     49      ALLOCATE( covrai(jpi,jpj)     , area(jpi,jpj) , tms(jpi,jpj) , tmu(jpi,jpj) ,     & 
    5250         &      wght  (jpi,jpj,2,2)                                               , STAT=ierr(1) ) 
    5351         ! 
  • trunk/NEMOGCM/NEMO/LIM_SRC_2/iceini_2.F90

    r6140 r7646  
    8383      CALL ice_run_2                   ! read in namelist some run parameters 
    8484      !           
    85       rdt_ice = nn_fsbc * rdt           ! sea-ice time step 
     85      rdt_ice = nn_fsbc * rdt          ! sea-ice time step 
    8686      numit   = nit000 - 1 
    8787      ! 
  • trunk/NEMOGCM/NEMO/LIM_SRC_2/limdmp_2.F90

    r5836 r7646  
    144144       
    145145         resto_ice(:,:,:) = 0._wp 
    146          !      Re-calculate the North and South boundary restoring term 
    147          !      because those boundaries may change with the prescribed zoom area. 
    148146         ! 
    149147         irelax  = 16                     ! width of buffer zone with respect to close boundary 
     
    156154         ! REM: if there is no ice in the model and in the data,  
    157155         !      no restoring even with non zero resto_ice 
    158          DO jj = mj0(jpjzoom - 1 + 1), mj1(jpjzoom -1 + irelax) 
    159             zreltim = zdmpmin + zfactor * ( mjg(jj) - jpjzoom + 1 ) 
     156         DO jj = mj0(1), mj1( irelax) 
     157            zreltim = zdmpmin + zfactor * mjg(jj) 
    160158            resto_ice(:,jj,:) = 1._wp / ( zreltim * 86400._wp ) 
    161159         END DO 
    162160 
    163161         ! North boundary restoring term 
    164          DO jj =  mj0(jpjzoom -1 + jpjglo - irelax), mj1(jpjzoom - 1 + jpjglo) 
    165             zreltim = zdmpmin + zfactor * (jpjglo - ( mjg(jj) - jpjzoom + 1 )) 
     162         DO jj =  mj0(jpjglo - irelax), mj1(jpjglo) 
     163            zreltim = zdmpmin + zfactor * (jpjglo - mjg(jj)) 
    166164            resto_ice(:,jj,:) = 1.e0 / ( zreltim * 86400 ) 
    167165         END DO 
  • trunk/NEMOGCM/NEMO/LIM_SRC_2/limdyn_2.F90

    r5123 r7646  
    8787         ! --------------------------------------------------- 
    8888          
    89          IF( lk_mpp .OR. lk_mpp_rep ) THEN                    ! mpp: compute over the whole domain 
     89         IF( lk_mpp ) THEN                    ! mpp: compute over the whole domain 
    9090            i_j1 = 1    
    9191            i_jpj = jpj 
  • trunk/NEMOGCM/NEMO/LIM_SRC_2/limistate_2.F90

    r5541 r7646  
    6969      IF( .NOT. ln_limini ) THEN   
    7070          
    71          CALL eos_fzp( tsn(:,:,1,jp_sal), tfu(:,:) )       ! freezing/melting point of sea water [Celcius] 
     71         CALL eos_fzp( tsn(:,:,1,jp_sal), tfu(:,:) )       ! freezing/melting point of sea water [Celsius] 
    7272         tfu(:,:) = tfu(:,:) *  tmask(:,:,1) 
    7373 
     
    7979               ENDIF 
    8080               ! 
    81                IF( fcor(ji,jj) >= 0.e0 ) THEN     !--  Northern hemisphere. 
     81               IF( ff_t(ji,jj) >= 0._wp ) THEN     !--  Northern hemisphere. 
    8282                  hicif(ji,jj)   = zidto * hginn 
    8383                  frld(ji,jj)    = zidto * alinn + ( 1.0 - zidto ) * 1.0 
  • trunk/NEMOGCM/NEMO/LIM_SRC_2/limmsh_2.F90

    r3625 r7646  
    7070      ENDIF 
    7171       
    72       IF( jphgr_msh == 2 .OR. jphgr_msh == 3 .OR. jphgr_msh == 5 )   & 
    73           &      CALL ctl_stop(' Coriolis parameter in LIM not set for f- or beta-plane' ) 
    74  
    7572      !----------------------------------------------------------                           
    7673      !    Initialization of local and some global (common) variables  
     
    7976      njeq   = INT( jpj / 2 )   !i bug mpp potentiel 
    8077      njeqm1 = njeq - 1  
    81  
    82       fcor(:,:) = 2. * omega * SIN( gphit(:,:) * rad )   !  coriolis factor at T-point 
    8378  
    8479!i    DO jj = 1, jpj 
     
    8782!i    END DO 
    8883 
    89       IF( fcor(1,1) * fcor(1,nlcj) < 0.e0 ) THEN   ! local domain include both hemisphere 
     84      IF( ff_t(1,1) * ff_t(1,nlcj) < 0.e0 ) THEN   ! local domain include both hemisphere 
    9085         l_jeq = .TRUE. 
    9186         njeq  = 1 
    92          DO WHILE ( njeq <= jpj .AND. fcor(1,njeq) < 0.e0 ) 
     87         DO WHILE ( njeq <= jpj .AND. ff_t(1,njeq) < 0.e0 ) 
    9388            njeq = njeq + 1 
    9489         END DO 
    9590         IF(lwp ) WRITE(numout,*) '          the equator is inside the domain at about njeq = ', njeq 
    96       ELSEIF( fcor(1,1) < 0.e0 ) THEN 
     91      ELSEIF( ff_t(1,1) < 0.e0 ) THEN 
    9792         l_jeq = .FALSE. 
    9893         njeq = jpj 
  • trunk/NEMOGCM/NEMO/LIM_SRC_2/limrhg_2.F90

    r5836 r7646  
    163163         DO ji = 1 , jpi 
    164164            ! only the sinus changes its sign with the hemisphere 
    165             zsang(ji,jj)  = SIGN( 1._wp, fcor(ji,jj) ) * sangvg   ! only the sinus changes its sign with the hemisphere 
     165            zsang(ji,jj)  = SIGN( 1._wp, ff_t(ji,jj) ) * sangvg   ! only the sinus changes its sign with the hemisphere 
    166166            ! 
    167167            zmasst(ji,jj) = tms(ji,jj) * ( rhosn * hsnm(ji,jj) + rhoic * hicm(ji,jj) ) 
     
    198198               &           + zmasst(ji,jj-1) * wght(ji,jj,2,1) + zmasst(ji-1,jj-1) * wght(ji,jj,1,1) ) * zusw 
    199199            zcorl(ji,jj) = zmass(ji,jj) & 
    200                &           *( fcor(ji,jj  ) * wght(ji,jj,2,2) + fcor(ji-1,jj  )*wght(ji,jj,1,2)   & 
    201                &            + fcor(ji,jj-1) * wght(ji,jj,2,1) + fcor(ji-1,jj-1)*wght(ji,jj,1,1) ) * zusw 
     200               &           *( ff_t(ji,jj  ) * wght(ji,jj,2,2) + ff_t(ji-1,jj  )*wght(ji,jj,1,2)   & 
     201               &            + ff_t(ji,jj-1) * wght(ji,jj,2,1) + ff_t(ji-1,jj-1)*wght(ji,jj,1,1) ) * zusw 
    202202 
    203203            ! Wind stress. 
  • trunk/NEMOGCM/NEMO/LIM_SRC_2/limsbc_2.F90

    r6140 r7646  
    449449      soce_0(:,:) = soce                     ! constant SSS and ice salinity used in levitating sea-ice case 
    450450      sice_0(:,:) = sice 
    451       ! 
    452       IF( cp_cfg == "orca" ) THEN            ! decrease ocean & ice reference salinities in the Baltic sea  
    453          WHERE( 14._wp <= glamt(:,:) .AND. glamt(:,:) <= 32._wp .AND.   & 
    454             &   54._wp <= gphit(:,:) .AND. gphit(:,:) <= 66._wp         )  
    455             soce_0(:,:) = 4._wp 
    456             sice_0(:,:) = 2._wp 
    457          END WHERE 
    458       ENDIF 
     451      !                                      ! decrease ocean & ice reference salinities in the Baltic sea  
     452      WHERE( 14._wp <= glamt(:,:) .AND. glamt(:,:) <= 32._wp .AND.   & 
     453         &   54._wp <= gphit(:,:) .AND. gphit(:,:) <= 66._wp         )  
     454         soce_0(:,:) = 4._wp 
     455         sice_0(:,:) = 2._wp 
     456      END WHERE 
    459457      !                                      ! embedded sea ice 
    460458      IF( nn_ice_embd /= 0 ) THEN            ! mass exchanges between ice and ocean (case 1 or 2) set the snow+ice mass 
     
    473471!!gm 
    474472         IF( .NOT.ln_linssh ) THEN 
    475  
    476             do jk = 1,jpkm1                     ! adjust initial vertical scale factors 
     473            DO jk = 1,jpkm1                     ! adjust initial vertical scale factors 
    477474               e3t_n(:,:,jk) = e3t_0(:,:,jk)*( 1._wp + sshn(:,:)*tmask(:,:,1)/(ht_0(:,:) + 1.0 - tmask(:,:,1)) ) 
    478475               e3t_b(:,:,jk) = e3t_0(:,:,jk)*( 1._wp + sshb(:,:)*tmask(:,:,1)/(ht_0(:,:) + 1.0 - tmask(:,:,1)) ) 
    479             end do 
     476            END DO 
    480477            e3t_a(:,:,:) = e3t_b(:,:,:) 
    481478            ! Reconstruction of all vertical scale factors at now and before time steps 
  • trunk/NEMOGCM/NEMO/LIM_SRC_2/limthd_2.F90

    r6140 r7646  
    347347      ! Tricky trick : add 2 to frld in the Southern Hemisphere 
    348348      !-------------------------------------------------------- 
    349       IF( fcor(1,1) < 0.e0 ) THEN 
     349      IF( ff_t(1,1) < 0._wp ) THEN 
    350350         DO jj = 1, njeqm1 
    351351            DO ji = 1, jpi 
     
    479479 
    480480      !! Fram Strait sea-ice transport (sea-ice + snow)  (in ORCA2 = 5 points) 
    481       IF( iom_use('fram_trans') .and. cp_cfg == "orca" .AND. jp_cfg == 2 ) THEN    ! ORCA R2 configuration 
     481      IF( iom_use('fram_trans') .and. cn_cfg == "orca" .AND. nn_cfg == 2 ) THEN    ! ORCA R2 configuration 
    482482         DO jj = mj0(137), mj1(137) ! B grid 
    483483            IF( mj0(jj-1) >= nldj ) THEN 
  • trunk/NEMOGCM/NEMO/LIM_SRC_2/limtrp_2.F90

    r4624 r7646  
    234234         !-------------------------------------------------------------------! 
    235235         DO jj = 1, jpj 
    236             zindhe = MAX( 0.e0, SIGN( 1.e0, fcor(1,jj) ) )              ! = 0 for SH, =1 for NH 
     236            zindhe = MAX( 0._wp, SIGN( 1._wp, ff_t(1,jj) ) )              ! = 0 for SH, =1 for NH 
    237237            DO ji = 1, jpi 
    238238               ! 
Note: See TracChangeset for help on using the changeset viewer.