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 8152 for branches/2016/v3_6_CMIP6_ice_diagnostics/NEMOGCM/NEMO/LIM_SRC_3/limrhg.F90 – NEMO

Ignore:
Timestamp:
2017-06-08T12:43:44+02:00 (7 years ago)
Author:
vancop
Message:

SIMIP diagnostics, phase 2, commit#3

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/v3_6_CMIP6_ice_diagnostics/NEMOGCM/NEMO/LIM_SRC_3/limrhg.F90

    r8151 r8152  
    149149                                                                             !   ocean surface (ssh_m) if ice is not embedded 
    150150                                                                             !   ice top surface if ice is embedded    
    151       REAL(wp), POINTER, DIMENSION(:,:) ::   zCorx, zCory                    ! Coriolis stress array (SIMIP) 
     151      REAL(wp), POINTER, DIMENSION(:,:) ::   zCorx, zCory                    ! Coriolis stress array 
     152      REAL(wp), POINTER, DIMENSION(:,:) ::   ztaux_oi, ztauy_oi              ! Ocean-to-ice stress array 
     153 
    152154      REAL(wp), POINTER, DIMENSION(:,:) ::   zswitchU, zswitchV              ! dummy arrays 
    153155      REAL(wp), POINTER, DIMENSION(:,:) ::   zmaskU, zmaskV                  ! mask for ice presence 
     
    165167      CALL wrk_alloc( jpi,jpj, zswitchU, zswitchV, zmaskU, zmaskV, zfmask, zwf ) 
    166168      CALL wrk_alloc( jpi,jpj, zCorx, zCory) 
     169      CALL wrk_alloc( jpi,jpj, ztaux_oi, ztauy_oi) 
    167170 
    168171#if  defined key_lim2 && ! defined key_lim2_vp 
     
    448451                     &                             + ( u_iceV(ji,jj) - u_oceV(ji,jj) ) * ( u_iceV(ji,jj) - u_oceV(ji,jj) ) ) 
    449452 
     453                  ! Ocean-to-Ice stress 
     454                  ztauy_oi(ji,jj) = zTauO * ( v_oce(ji,jj) - v_ice(ji,jj) ) 
     455 
    450456                  ! Coriolis at V-points (energy conserving formulation) 
    451457                  zCory(ji,jj)  = - 0.25_wp * r1_e2v(ji,jj) *  & 
     
    454460 
    455461                  ! Sum of external forces (explicit solution) = F + tau_ia + Coriolis + spg + tau_io 
    456                   zTauE = zfV(ji,jj) + zTauV_ia(ji,jj) + zCory(ji,jj) + zspgV(ji,jj) + zTauO * ( v_oce(ji,jj) - v_ice(ji,jj) ) 
     462                  zTauE = zfV(ji,jj) + zTauV_ia(ji,jj) + zCory(ji,jj) + zspgV(ji,jj) + ztauy_oi(ji,jj) 
    457463                   
    458464                  ! ice velocity using implicit formulation (cf Madec doc & Bouillon 2009) 
     
    479485                     &                             + ( v_iceU(ji,jj) - v_oceU(ji,jj) ) * ( v_iceU(ji,jj) - v_oceU(ji,jj) ) ) 
    480486 
     487                  ! Ocean-to-Ice stress 
     488                  ztaux_oi(ji,jj) = zTauO * ( u_oce(ji,jj) - u_ice(ji,jj) ) 
     489 
    481490                  ! Coriolis at U-points (energy conserving formulation) 
    482491                  zCorx(ji,jj)  =   0.25_wp * r1_e1u(ji,jj) *  & 
    483492                     &    ( zmf(ji  ,jj) * ( e1v(ji  ,jj) * v_ice(ji  ,jj) + e1v(ji  ,jj-1) * v_ice(ji  ,jj-1) )  & 
    484493                     &    + zmf(ji+1,jj) * ( e1v(ji+1,jj) * v_ice(ji+1,jj) + e1v(ji+1,jj-1) * v_ice(ji+1,jj-1) ) ) 
    485                    
     494 
    486495                  ! Sum of external forces (explicit solution) = F + tau_ia + Coriolis + spg + tau_io 
    487                   zTauE = zfU(ji,jj) + zTauU_ia(ji,jj) + zCorx(ji,jj) + zspgU(ji,jj) + zTauO * ( u_oce(ji,jj) - u_ice(ji,jj) ) 
     496                  zTauE = zfU(ji,jj) + zTauU_ia(ji,jj) + zCorx(ji,jj) + zspgU(ji,jj) + ztaux_oi(ji,jj) 
    488497 
    489498                  ! ice velocity using implicit formulation (cf Madec doc & Bouillon 2009) 
     
    512521                     &                             + ( v_iceU(ji,jj) - v_oceU(ji,jj) ) * ( v_iceU(ji,jj) - v_oceU(ji,jj) ) ) 
    513522 
     523                  ! Ocean-to-Ice stress 
     524                  ztaux_oi(ji,jj) = zTauO * ( u_oce(ji,jj) - u_ice(ji,jj) ) 
     525                   
    514526                  ! Coriolis at U-points (energy conserving formulation) 
    515527                  zCorx(ji,jj)  =   0.25_wp * r1_e1u(ji,jj) *  & 
    516528                     &    ( zmf(ji  ,jj) * ( e1v(ji  ,jj) * v_ice(ji  ,jj) + e1v(ji  ,jj-1) * v_ice(ji  ,jj-1) )  & 
    517529                     &    + zmf(ji+1,jj) * ( e1v(ji+1,jj) * v_ice(ji+1,jj) + e1v(ji+1,jj-1) * v_ice(ji+1,jj-1) ) ) 
    518                    
     530 
    519531                  ! Sum of external forces (explicit solution) = F + tau_ia + Coriolis + spg + tau_io 
    520                   zTauE = zfU(ji,jj) + zTauU_ia(ji,jj) + zCorx(ji,jj) + zspgU(ji,jj) + zTauO * ( u_oce(ji,jj) - u_ice(ji,jj) ) 
     532                  zTauE = zfU(ji,jj) + zTauU_ia(ji,jj) + zCorx(ji,jj) + zspgU(ji,jj) + ztaux_oi(ji,jj) 
    521533 
    522534                  ! ice velocity using implicit formulation (cf Madec doc & Bouillon 2009) 
     
    543555                     &                             + ( u_iceV(ji,jj) - u_oceV(ji,jj) ) * ( u_iceV(ji,jj) - u_oceV(ji,jj) ) ) 
    544556 
     557                  ! Ocean-to-Ice stress 
     558                  ztauy_oi(ji,jj) = zTauO * ( v_oce(ji,jj) - v_ice(ji,jj) ) 
     559 
    545560                  ! Coriolis at V-points (energy conserving formulation) 
    546561                  zCory(ji,jj)  = - 0.25_wp * r1_e2v(ji,jj) *  & 
     
    549564 
    550565                  ! Sum of external forces (explicit solution) = F + tau_ia + Coriolis + spg + tau_io 
    551                   zTauE = zfV(ji,jj) + zTauV_ia(ji,jj) + zCory(ji,jj) + zspgV(ji,jj) + zTauO * ( v_oce(ji,jj) - v_ice(ji,jj) ) 
     566                  zTauE = zfV(ji,jj) + zTauV_ia(ji,jj) + zCory(ji,jj) + zspgV(ji,jj) + ztauy_oi(ji,jj) 
    552567                   
    553568                  ! ice velocity using implicit formulation (cf Madec doc & Bouillon 2009) 
     
    632647      stress12_i(:,:) = zs12(:,:) 
    633648 
    634       ! SIMIP diagnostics: sea surface sloop stress, coriolis and internal stress terms (N/m2)  
    635       !                    stress tensor invariants (normal and shear stress N/m) 
     649      !------------------------------------------------------------------------------! 
     650      ! 5) SIMIP diagnostics 
     651      !------------------------------------------------------------------------------! 
     652                            
    636653      DO jj = k_j1+1, k_jpj-1 
    637654         DO ji = 2, jpim1 
    638655             zswi  = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi06 ) ) ! 1 if ice, 0 if no ice 
    639656 
     657             ! Stress tensor invariants (normal and shear stress N/m) 
    640658             diag_sig1(ji,jj) = ( zs1(ji,jj) + zs2(ji,jj) ) * zswi                                 ! normal stress 
    641659             diag_sig2(ji,jj) = SQRT( ( zs1(ji,jj) - zs2(ji,jj) )**2 + 4*zs12(ji,jj)**2 ) * zswi   ! shear stress 
    642660 
     661             ! Stress terms of the momentum equation (N/m2) 
    643662             diag_dssh_dx(ji,jj) = zspgU(ji,jj) * zswi    ! sea surface slope stress term 
    644663             diag_dssh_dy(ji,jj) = zspgV(ji,jj) * zswi 
     
    649668             diag_intstrx(ji,jj) = zfU(ji,jj)   * zswi    ! internal stress term 
    650669             diag_intstry(ji,jj) = zfV(ji,jj)   * zswi 
     670            
     671             diag_utau_oi(ji,jj) = ztaux_oi(ji,jj) * zswi  ! oceanic stress 
     672             diag_vtau_oi(ji,jj) = ztauy_oi(ji,jj) * zswi 
    651673 
    652674         END DO 
     
    656678                 &        diag_dssh_dx, 'U', -1., diag_dssh_dy, 'V', -1., & 
    657679                 &        diag_corstrx, 'U', -1., diag_corstry, 'V', -1., &  
    658                  &        diag_intstrx, 'U', -1., diag_intstry, 'V', -1.  ) 
    659  
    660 !     CALL lbc_lnk( diag_dssh_dx, 'U', -1. ) 
    661 !     CALL lbc_lnk( diag_dssh_dy, 'V', -1. ) 
    662  
    663 !     CALL lbc_lnk( diag_intstrx, 'U', -1. ) 
    664 !     CALL lbc_lnk( diag_intstry, 'V', -1. ) 
    665  
    666 !     CALL lbc_lnk( diag_corstrx, 'U', -1. ) 
    667 !     CALL lbc_lnk( diag_corstry, 'V', -1. ) 
    668              
    669       ! 
    670       !------------------------------------------------------------------------------! 
    671       ! 5) Control prints of residual and charge ellipse 
     680                 &        diag_intstrx, 'U', -1., diag_intstry, 'V', -1.  & 
     681                 &        diag_utau_oi, 'U', -1., diag_vtau_oi, 'V', -1.    ) 
     682 
     683      ! 
     684      !------------------------------------------------------------------------------! 
     685      ! 6) Control prints of residual and charge ellipse 
    672686      !------------------------------------------------------------------------------! 
    673687      ! 
     
    710724      CALL wrk_dealloc( jpi,jpj, zds, zs1, zs2, zs12, zu_ice, zv_ice, zresr, zpice ) 
    711725      CALL wrk_dealloc( jpi,jpj, zswitchU, zswitchV, zmaskU, zmaskV, zfmask, zwf ) 
    712       CALL wrk_dealloc( jpi,jpj, zCorx, zCory) 
     726      CALL wrk_dealloc( jpi,jpj, zCorx, zCory ) 
     727      CALL wrk_dealloc( jpi,jpj, ztaux_oi, ztauy_oi ) 
    713728 
    714729   END SUBROUTINE lim_rhg 
Note: See TracChangeset for help on using the changeset viewer.