Changeset 8285
- Timestamp:
- 2017-07-06T08:40:51+02:00 (7 years ago)
- Location:
- branches/2016/v3_6_CMIP6_ice_diagnostics/NEMOGCM/NEMO/LIM_SRC_3
- Files:
-
- 3 edited
Legend:
- Unmodified
- Added
- Removed
-
branches/2016/v3_6_CMIP6_ice_diagnostics/NEMOGCM/NEMO/LIM_SRC_3/ice.F90
r8175 r8285 423 423 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_dmi_dyn !: Change in ice mass due to ice dynamics (kg/m2/s) 424 424 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_dms_dyn !: Change in snow mass due to ice dynamics (kg/m2/s) 425 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_xmtrp_ice !: X-component of ice mass transport (kg/s)426 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_ymtrp_ice !: Y-component of ice mass transport (kg/s)427 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_xmtrp_snw !: X-component of snow mass transport (kg/s)428 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_ymtrp_snw !: Y-component of snow mass transport (kg/s)429 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_xatrp !: X-component of area transport (m2/s)430 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_yatrp !: Y-component of area transport (m2/s)431 425 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_fc_bo !: Bottom conduction flux (W/m2) 432 426 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_fc_su !: Surface conduction flux (W/m2) 433 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_utau_oi !: X-direction ocean-ice stress434 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_vtau_oi !: Y-direction ocean-ice stress435 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_dssh_dx !: X-direction sea-surface tilt term (N/m2)436 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_dssh_dy !: X-direction sea-surface tilt term (N/m2)437 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_corstrx !: X-direction coriolis stress (N/m2)438 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_corstry !: Y-direction coriolis stress (N/m2)439 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_intstrx !: X-direction internal stress (N/m2)440 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_intstry !: Y-direction internal stress (N/m2)441 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_sig1 !: Average normal stress in sea ice442 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_sig2 !: Maximum shear stress in sea ice443 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: diag_shear !: Maximum shear of sea-ice velocity field444 427 445 428 ! … … 544 527 ALLOCATE( t_si (jpi,jpj,jpl) , tm_si(jpi,jpj) , & 545 528 diag_dmi_dyn(jpi,jpj) , diag_dms_dyn(jpi,jpj) , & 546 diag_xmtrp_ice(jpi,jpj), diag_ymtrp_ice(jpi,jpj), &547 diag_xmtrp_snw(jpi,jpj), diag_ymtrp_snw(jpi,jpj), &548 diag_xatrp(jpi,jpj) , diag_yatrp(jpi,jpj) , &549 529 diag_fc_bo(jpi,jpj) , diag_fc_su(jpi,jpj) , & 550 diag_utau_oi(jpi,jpj) , diag_vtau_oi(jpi,jpj) , &551 diag_dssh_dx(jpi,jpj) , diag_dssh_dy(jpi,jpj) , &552 diag_corstrx(jpi,jpj) , diag_corstry(jpi,jpj) , &553 diag_intstrx(jpi,jpj) , diag_intstry(jpi,jpj) , &554 diag_sig1(jpi,jpj) , diag_sig2(jpi,jpj) , &555 530 STAT = ierr(ii) ) 556 531 -
branches/2016/v3_6_CMIP6_ice_diagnostics/NEMOGCM/NEMO/LIM_SRC_3/limrhg.F90
r8172 r8285 38 38 USE in_out_manager ! I/O manager 39 39 USE prtctl ! Print control 40 USE iom 40 41 USE lib_fortran ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 41 42 #if defined key_agrif && defined key_lim2 … … 129 130 REAL(wp) :: zresm ! Maximal error on ice velocity 130 131 REAL(wp) :: zintb, zintn ! dummy argument 131 REAL(wp) :: z swi, zfac_x, zfac_y132 REAL(wp) :: zfac_x, zfac_y 132 133 133 134 REAL(wp), POINTER, DIMENSION(:,:) :: zpresh ! temporary array for ice strength … … 156 157 REAL(wp), POINTER, DIMENSION(:,:) :: zfmask, zwf ! mask at F points for the ice 157 158 159 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_xmtrp_ice ! X-component of ice mass transport (kg/s) 160 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_ymtrp_ice ! Y-component of ice mass transport (kg/s) 161 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_xmtrp_snw ! X-component of snow mass transport (kg/s) 162 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_ymtrp_snw ! Y-component of snow mass transport (kg/s) 163 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_xatrp ! X-component of area transport (m2/s) 164 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_yatrp ! Y-component of area transport (m2/s) 165 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_utau_oi ! X-direction ocean-ice stress 166 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_vtau_oi ! Y-direction ocean-ice stress 167 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_dssh_dx ! X-direction sea-surface tilt term (N/m2) 168 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_dssh_dy ! X-direction sea-surface tilt term (N/m2) 169 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_corstrx ! X-direction coriolis stress (N/m2) 170 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_corstry ! Y-direction coriolis stress (N/m2) 171 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_intstrx ! X-direction internal stress (N/m2) 172 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_intstry ! Y-direction internal stress (N/m2) 173 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_sig1 ! Average normal stress in sea ice 174 REAL(wp), POINTER, DIMENSION(:,:) :: zdiag_sig2 ! Maximum shear stress in sea ice 175 176 REAL(wp), POINTER, DIMENSION(:,:) :: zswi, zmiss ! Switch & missing value array 177 158 178 REAL(wp), PARAMETER :: zepsi = 1.0e-20_wp ! tolerance parameter 159 179 REAL(wp), PARAMETER :: zmmin = 1._wp ! ice mass (kg/m2) below which ice velocity equals ocean velocity 160 180 REAL(wp), PARAMETER :: zshlat = 2._wp ! boundary condition for sea-ice velocity (2=no slip ; 0=free slip) 181 REAL(wp), PARAMETER :: zmiss_val = 1.0e+20 ! missing value for outputs 182 161 183 !!------------------------------------------------------------------- 162 184 … … 168 190 CALL wrk_alloc( jpi,jpj, zCorx, zCory) 169 191 CALL wrk_alloc( jpi,jpj, ztaux_oi, ztauy_oi) 192 193 CALL wrk_alloc( jpi,jpj, zdiag_xmtrp_ice, zdiag_ymtrp_ice ) 194 CALL wrk_alloc( jpi,jpj, zdiag_xmtrp_snw, zdiag_ymtrp_snw ) 195 CALL wrk_alloc( jpi,jpj, zdiag_xatrp , zdiag_yatrp ) 196 CALL wrk_alloc( jpi,jpj, zdiag_utau_oi , zdiag_vtau_oi ) 197 CALL wrk_alloc( jpi,jpj, zdiag_dssh_dx , zdiag_dssh_dy ) 198 CALL wrk_alloc( jpi,jpj, zdiag_corstrx , zdiag_corstry ) 199 CALL wrk_alloc( jpi,jpj, zdiag_intstrx , zdiag_intstry ) 200 CALL wrk_alloc( jpi,jpj, zdiag_sig1 , zdiag_sig2 ) 201 CALL wrk_alloc( jpi,jpj, zswi , zmiss ) 170 202 171 203 #if defined key_lim2 && ! defined key_lim2_vp … … 650 682 ! 5) SIMIP diagnostics 651 683 !------------------------------------------------------------------------------! 684 685 DO jj = 1, jpj 686 DO ji = 1, jpi 687 zswi(ji,jj) = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi06 ) ) ! 1 if ice, 0 if no ice 688 END DO 689 END DO 690 691 zmiss(:,:) = zmiss_val * ( 1. - zswi(:,:) ) 652 692 653 693 DO jj = k_j1+1, k_jpj-1 654 694 DO ji = 2, jpim1 655 zswi = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi06 ) ) ! 1 if ice, 0 if no ice656 695 657 696 ! Stress tensor invariants (normal and shear stress N/m) 658 diag_sig1(ji,jj) = ( zs1(ji,jj) + zs2(ji,jj) ) * zswi! normal stress659 diag_sig2(ji,jj) = SQRT( ( zs1(ji,jj) - zs2(ji,jj) )**2 + 4*zs12(ji,jj)**2 ) * zswi! shear stress697 zdiag_sig1(ji,jj) = ( zs1(ji,jj) + zs2(ji,jj) ) * zswi(ji,jj) ! normal stress 698 zdiag_sig2(ji,jj) = SQRT( ( zs1(ji,jj) - zs2(ji,jj) )**2 + 4*zs12(ji,jj)**2 ) * zswi(ji,jj) ! shear stress 660 699 661 700 ! Stress terms of the momentum equation (N/m2) 662 diag_dssh_dx(ji,jj) = zspgU(ji,jj) * zswi! sea surface slope stress term663 diag_dssh_dy(ji,jj) = zspgV(ji,jj) * zswi664 665 diag_corstrx(ji,jj) = zCorx(ji,jj) * zswi! Coriolis stress term666 diag_corstry(ji,jj) = zCory(ji,jj) * zswi667 668 diag_intstrx(ji,jj) = zfU(ji,jj) * zswi! internal stress term669 diag_intstry(ji,jj) = zfV(ji,jj) * zswi701 zdiag_dssh_dx(ji,jj) = zspgU(ji,jj) * zswi(ji,jj) ! sea surface slope stress term 702 zdiag_dssh_dy(ji,jj) = zspgV(ji,jj) * zswi(ji,jj) 703 704 zdiag_corstrx(ji,jj) = zCorx(ji,jj) * zswi(ji,jj) ! Coriolis stress term 705 zdiag_corstry(ji,jj) = zCory(ji,jj) * zswi(ji,jj) 706 707 zdiag_intstrx(ji,jj) = zfU(ji,jj) * zswi(ji,jj) ! internal stress term 708 zdiag_intstry(ji,jj) = zfV(ji,jj) * zswi(ji,jj) 670 709 671 diag_utau_oi(ji,jj) = ztaux_oi(ji,jj) * zswi! oceanic stress672 diag_vtau_oi(ji,jj) = ztauy_oi(ji,jj) * zswi710 zdiag_utau_oi(ji,jj) = ztaux_oi(ji,jj) * zswi(ji,jj) ! oceanic stress 711 zdiag_vtau_oi(ji,jj) = ztauy_oi(ji,jj) * zswi(ji,jj) 673 712 674 713 ! 2D ice mass, snow mass, area transport arrays (X, Y) 675 zfac_x = 0.5 * u_ice(ji,jj) * e2u(ji,jj) * zswi 676 zfac_y = 0.5 * v_ice(ji,jj) * e1v(ji,jj) * zswi 677 678 diag_xmtrp_ice(ji,jj) = rhoic * zfac_x * ( vt_i(ji+1,jj) + vt_i(ji,jj) ) ! ice mass transport, X-component679 diag_ymtrp_ice(ji,jj) = rhoic * zfac_y * ( vt_i(ji,jj+1) + vt_i(ji,jj) ) ! '' Y- ''680 681 diag_xmtrp_snw(ji,jj) = rhosn * zfac_x * ( vt_s(ji+1,jj) + vt_s(ji,jj) ) ! snow mass transport, X-component682 diag_ymtrp_snw(ji,jj) = rhosn * zfac_y * ( vt_s(ji,jj+1) + vt_s(ji,jj) ) ! '' Y- ''683 684 diag_xatrp(ji,jj) = zfac_x * ( at_i(ji+1,jj) + at_i(ji,jj) ) ! area transport, X-component685 diag_yatrp(ji,jj) = zfac_y * ( at_i(ji,jj+1) + at_i(ji,jj) )! '' Y- ''714 zfac_x = 0.5 * u_ice(ji,jj) * e2u(ji,jj) * zswi(ji,jj) 715 zfac_y = 0.5 * v_ice(ji,jj) * e1v(ji,jj) * zswi(ji,jj) 716 717 zdiag_xmtrp_ice(ji,jj) = rhoic * zfac_x * ( vt_i(ji+1,jj) + vt_i(ji,jj) ) ! ice mass transport, X-component (kg/s) 718 zdiag_ymtrp_ice(ji,jj) = rhoic * zfac_y * ( vt_i(ji,jj+1) + vt_i(ji,jj) ) ! '' Y- '' 719 720 zdiag_xmtrp_snw(ji,jj) = rhosn * zfac_x * ( vt_s(ji+1,jj) + vt_s(ji,jj) ) ! snow mass transport, X-component 721 zdiag_ymtrp_snw(ji,jj) = rhosn * zfac_y * ( vt_s(ji,jj+1) + vt_s(ji,jj) ) ! '' Y- '' 722 723 zdiag_xatrp(ji,jj) = zfac_x * ( at_i(ji+1,jj) + at_i(ji,jj) ) ! area transport, X-component (m2/s) 724 zdiag_yatrp(ji,jj) = zfac_y * ( at_i(ji,jj+1) + at_i(ji,jj) ) ! '' Y- '' 686 725 687 726 END DO 688 727 END DO 689 728 690 CALL lbc_lnk_multi( diag_sig1 , 'T', 1., diag_sig2 , 'T', 1., & 691 & diag_dssh_dx, 'U', -1., diag_dssh_dy, 'V', -1., & 692 & diag_corstrx, 'U', -1., diag_corstry, 'V', -1., & 693 & diag_intstrx, 'U', -1., diag_intstry, 'V', -1. ) 694 695 CALL lbc_lnk_multi( diag_utau_oi, 'U', -1., diag_vtau_oi, 'V', -1. ) 729 CALL lbc_lnk_multi( zdiag_sig1 , 'T', 1., zdiag_sig2 , 'T', 1., & 730 & zdiag_dssh_dx, 'U', -1., zdiag_dssh_dy, 'V', -1., & 731 & zdiag_corstrx, 'U', -1., zdiag_corstry, 'V', -1., & 732 & zdiag_intstrx, 'U', -1., zdiag_intstry, 'V', -1. ) 733 734 CALL lbc_lnk_multi( zdiag_utau_oi, 'U', -1., zdiag_vtau_oi, 'V', -1. ) 735 736 CALL lbc_lnk_multi( zdiag_xmtrp_ice, 'U', -1., zdiag_xmtrp_snw, 'U', -1., & 737 & zdiag_xatrp , 'U', -1., zdiag_ymtrp_ice, 'V', -1., & 738 & zdiag_ymtrp_snw, 'V', -1., zdiag_yatrp , 'V', -1. ) 739 740 IF ( iom_use( "xmtrpice" ) ) CALL iom_put( "xmtrpice" , zdiag_xmtrp_ice(:,:) ) ! X-component of sea-ice mass transport (kg/s) 741 IF ( iom_use( "ymtrpice" ) ) CALL iom_put( "ymtrpice" , zdiag_ymtrp_ice(:,:) ) ! Y-component of sea-ice mass transport 742 743 IF ( iom_use( "xmtrpsnw" ) ) CALL iom_put( "xmtrpsnw" , zdiag_xmtrp_snw(:,:) ) ! X-component of snow mass transport (kg/s) 744 IF ( iom_use( "ymtrpsnw" ) ) CALL iom_put( "ymtrpsnw" , zdiag_ymtrp_snw(:,:) ) ! Y-component of snow mass transport 745 746 IF ( iom_use( "xatrp" ) ) CALL iom_put( "xatrp" , zdiag_xatrp(:,:) ) ! X-component of ice area transport 747 IF ( iom_use( "yatrp" ) ) CALL iom_put( "yatrp" , zdiag_yatrp(:,:) ) ! Y-component of ice area transport 748 749 IF ( iom_use( "utau_ice" ) ) CALL iom_put( "utau_ice" , utau_ice(:,:) * zswi(:,:) + zmiss(:,:) ) ! Wind stress term in force balance (x) 750 IF ( iom_use( "vtau_ice" ) ) CALL iom_put( "vtau_ice" , vtau_ice(:,:) * zswi(:,:) + zmiss(:,:) ) ! Wind stress term in force balance (y) 751 752 IF ( iom_use( "utau_oi" ) ) CALL iom_put( "utau_oi" , zdiag_utau_oi(:,:) * zswi(:,:) + zmiss(:,:) ) ! Ocean stress term in force balance (x) 753 IF ( iom_use( "vtau_oi" ) ) CALL iom_put( "vtau_oi" , zdiag_vtau_oi(:,:) * zswi(:,:) + zmiss(:,:) ) ! Ocean stress term in force balance (y) 754 755 IF ( iom_use( "dssh_dx" ) ) CALL iom_put( "dssh_dx" , zdiag_dssh_dx(:,:) * zswi(:,:) + zmiss(:,:) ) ! Sea-surface tilt term in force balance (x) 756 IF ( iom_use( "dssh_dy" ) ) CALL iom_put( "dssh_dy" , zdiag_dssh_dy(:,:) * zswi(:,:) + zmiss(:,:) ) ! Sea-surface tilt term in force balance (y) 757 758 IF ( iom_use( "corstrx" ) ) CALL iom_put( "corstrx" , zdiag_corstrx(:,:) * zswi(:,:) + zmiss(:,:) ) ! Coriolis force term in force balance (x) 759 IF ( iom_use( "corstry" ) ) CALL iom_put( "corstry" , zdiag_corstry(:,:) * zswi(:,:) + zmiss(:,:) ) ! Coriolis force term in force balance (y) 760 761 IF ( iom_use( "intstrx" ) ) CALL iom_put( "intstrx" , zdiag_intstrx(:,:) * zswi(:,:) + zmiss(:,:) ) ! Internal force term in force balance (x) 762 IF ( iom_use( "intstry" ) ) CALL iom_put( "intstry" , zdiag_intstry(:,:) * zswi(:,:) + zmiss(:,:) ) ! Internal force term in force balance (y) 763 764 IF ( iom_use( "normstr" ) ) CALL iom_put( "normstr" , zdiag_sig1(:,:) * zswi(:,:) + zmiss(:,:) ) ! Normal stress 765 IF ( iom_use( "sheastr" ) ) CALL iom_put( "sheastr" , zdiag_sig2(:,:) * zswi(:,:) + zmiss(:,:) ) ! Shear stress 696 766 697 767 ! … … 740 810 CALL wrk_dealloc( jpi,jpj, zCorx, zCory ) 741 811 CALL wrk_dealloc( jpi,jpj, ztaux_oi, ztauy_oi ) 812 813 CALL wrk_dealloc( jpi,jpj, zdiag_xmtrp_ice, zdiag_ymtrp_ice ) 814 CALL wrk_dealloc( jpi,jpj, zdiag_xmtrp_snw, zdiag_ymtrp_snw ) 815 CALL wrk_dealloc( jpi,jpj, zdiag_xatrp , zdiag_yatrp ) 816 CALL wrk_dealloc( jpi,jpj, zdiag_utau_oi , zdiag_vtau_oi ) 817 CALL wrk_dealloc( jpi,jpj, zdiag_dssh_dx , zdiag_dssh_dy ) 818 CALL wrk_dealloc( jpi,jpj, zdiag_corstrx , zdiag_corstry ) 819 CALL wrk_dealloc( jpi,jpj, zdiag_intstrx , zdiag_intstry ) 820 CALL wrk_dealloc( jpi,jpj, zdiag_sig1 , zdiag_sig2 ) 821 CALL wrk_dealloc( jpi,jpj, zswi , zmiss ) 742 822 743 823 END SUBROUTINE lim_rhg -
branches/2016/v3_6_CMIP6_ice_diagnostics/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90
r8271 r8285 300 300 IF ( iom_use( "uice_mv" ) ) CALL iom_put( "uice_mv" , u_ice(:,:) * zswi(:,:) + zmiss(:,:) ) ! ice velocity u component 301 301 IF ( iom_use( "vice_mv" ) ) CALL iom_put( "vice_mv" , v_ice(:,:) * zswi(:,:) + zmiss(:,:) ) ! ice velocity v component 302 303 IF ( iom_use( "xmtrpice" ) ) CALL iom_put( "xmtrpice" , diag_xmtrp_ice(:,:) ) ! X-component of sea-ice mass transport (kg/s)304 IF ( iom_use( "ymtrpice" ) ) CALL iom_put( "ymtrpice" , diag_ymtrp_ice(:,:) ) ! Y-component of sea-ice mass transport305 306 IF ( iom_use( "xmtrpsnw" ) ) CALL iom_put( "xmtrpsnw" , diag_xmtrp_snw(:,:) ) ! X-component of snow mass transport (kg/s)307 IF ( iom_use( "ymtrpsnw" ) ) CALL iom_put( "ymtrpsnw" , diag_ymtrp_snw(:,:) ) ! Y-component of snow mass transport308 309 IF ( iom_use( "xatrp" ) ) CALL iom_put( "xatrp" , diag_xatrp(:,:) ) ! X-component of ice area transport310 IF ( iom_use( "yatrp" ) ) CALL iom_put( "yatrp" , diag_yatrp(:,:) ) ! Y-component of ice area transport311 312 IF ( iom_use( "utau_ice" ) ) CALL iom_put( "utau_ice" , utau_ice(:,:) * zswi(:,:) + zmiss(:,:) ) ! Wind stress term in force balance (x)313 IF ( iom_use( "vtau_ice" ) ) CALL iom_put( "vtau_ice" , vtau_ice(:,:) * zswi(:,:) + zmiss(:,:) ) ! Wind stress term in force balance (y)314 315 IF ( iom_use( "utau_oi" ) ) CALL iom_put( "utau_oi" , diag_utau_oi(:,:) * zswi(:,:) + zmiss(:,:) ) ! Ocean stress term in force balance (x)316 IF ( iom_use( "vtau_oi" ) ) CALL iom_put( "vtau_oi" , diag_vtau_oi(:,:) * zswi(:,:) + zmiss(:,:) ) ! Ocean stress term in force balance (y)317 302 318 303 IF ( iom_use( "icestr" ) ) CALL iom_put( "icestr" , strength(:,:) * zswi(:,:) + zmiss(:,:) ) ! Ice strength 319 320 IF ( iom_use( "dssh_dx" ) ) CALL iom_put( "dssh_dx" , diag_dssh_dx(:,:) * zswi(:,:) + zmiss(:,:) ) ! Sea-surface tilt term in force balance (x)321 IF ( iom_use( "dssh_dy" ) ) CALL iom_put( "dssh_dy" , diag_dssh_dy(:,:) * zswi(:,:) + zmiss(:,:) ) ! Sea-surface tilt term in force balance (y)322 323 IF ( iom_use( "corstrx" ) ) CALL iom_put( "corstrx" , diag_corstrx(:,:) * zswi(:,:) + zmiss(:,:) ) ! Coriolis force term in force balance (x)324 IF ( iom_use( "corstry" ) ) CALL iom_put( "corstry" , diag_corstry(:,:) * zswi(:,:) + zmiss(:,:) ) ! Coriolis force term in force balance (y)325 326 IF ( iom_use( "intstrx" ) ) CALL iom_put( "intstrx" , diag_intstrx(:,:) * zswi(:,:) + zmiss(:,:) ) ! Internal force term in force balance (x)327 IF ( iom_use( "intstry" ) ) CALL iom_put( "intstry" , diag_intstry(:,:) * zswi(:,:) + zmiss(:,:) ) ! Internal force term in force balance (y)328 329 IF ( iom_use( "normstr" ) ) CALL iom_put( "normstr" , diag_sig1(:,:) * zswi(:,:) + zmiss(:,:) ) ! Normal stress330 IF ( iom_use( "sheastr" ) ) CALL iom_put( "sheastr" , diag_sig2(:,:) * zswi(:,:) + zmiss(:,:) ) ! Shear stress331 304 332 305 !--------------------------------
Note: See TracChangeset
for help on using the changeset viewer.