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 5260 for branches/2014/dev_r4650_UKMO10_Tidally_Meaned_Diagnostics/NEMOGCM/NEMO/OPA_SRC/DIA/diawri.F90 – NEMO

Ignore:
Timestamp:
2015-05-12T12:37:15+02:00 (9 years ago)
Author:
deazer
Message:

Merged branch with Trunk at revision 5253.
Checked with SETTE, passes modified iodef.xml for AMM12 experiment

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4650_UKMO10_Tidally_Meaned_Diagnostics/NEMOGCM/NEMO/OPA_SRC/DIA/diawri.F90

    r4756 r5260  
    4444   USE in_out_manager  ! I/O manager 
    4545   USE diadimg         ! dimg direct access file format output 
    46    USE diaar5, ONLY :   lk_diaar5 
    47    USE dynadv, ONLY :   ln_dynadv_vec 
    4846   USE diatmb          ! Top,middle,bottom output 
    4947   USE dia25h          ! 25h Mean output 
     
    8280   !!---------------------------------------------------------------------- 
    8381   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    84    !! $Id $ 
     82   !! $Id$ 
    8583   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    8684   !!---------------------------------------------------------------------- 
     
    9189      INTEGER, DIMENSION(2) :: ierr 
    9290      !!---------------------------------------------------------------------- 
    93       ! 
    9491      ierr = 0 
    95       ! 
    9692      ALLOCATE( ndex_hT(jpi*jpj) , ndex_T(jpi*jpj*jpk) ,     & 
    9793         &      ndex_hU(jpi*jpj) , ndex_U(jpi*jpj*jpk) ,     & 
     
    133129      REAL(wp)                     ::   zztmp, zztmpx, zztmpy   !  
    134130      !! 
    135       REAL(wp), POINTER, DIMENSION(:,:)   :: z2d       ! 2D workspace 
     131      REAL(wp), POINTER, DIMENSION(:,:)   :: z2d      ! 2D workspace 
    136132      REAL(wp), POINTER, DIMENSION(:,:,:) :: z3d      ! 3D workspace 
    137133      !!---------------------------------------------------------------------- 
     
    148144      ENDIF 
    149145 
    150       IF( lk_vvl ) THEN 
    151          z3d(:,:,:) = tsn(:,:,:,jp_tem) * fse3t_n(:,:,:) 
    152          CALL iom_put( "toce" , z3d                        )   ! heat content 
    153          CALL iom_put( "sst"  , z3d(:,:,1)                 )   ! sea surface heat content 
    154          z3d(:,:,1) = tsn(:,:,1,jp_tem) * z3d(:,:,1) 
    155          CALL iom_put( "sst2" , z3d(:,:,1)                 )   ! sea surface content of squared temperature 
    156          z3d(:,:,:) = tsn(:,:,:,jp_sal) * fse3t_n(:,:,:)             
    157          CALL iom_put( "soce" , z3d                        )   ! salinity content 
    158          CALL iom_put( "sss"  , z3d(:,:,1)                 )   ! sea surface salinity content 
    159          z3d(:,:,1) = tsn(:,:,1,jp_sal) * z3d(:,:,1) 
    160          CALL iom_put( "sss2" , z3d(:,:,1)                 )   ! sea surface content of squared salinity 
    161       ELSE 
    162          CALL iom_put( "toce" , tsn(:,:,:,jp_tem)          )   ! temperature 
    163          CALL iom_put( "sst"  , tsn(:,:,1,jp_tem)          )   ! sea surface temperature 
    164          CALL iom_put( "sst2" , tsn(:,:,1,jp_tem) * tsn(:,:,1,jp_tem) ) ! square of sea surface temperature 
    165          CALL iom_put( "soce" , tsn(:,:,:,jp_sal)          )   ! salinity 
    166          CALL iom_put( "sss"  , tsn(:,:,1,jp_sal)          )   ! sea surface salinity 
    167          CALL iom_put( "sss2" , tsn(:,:,1,jp_sal) * tsn(:,:,1,jp_sal) ) ! square of sea surface salinity 
    168       END IF 
    169       IF( lk_vvl .AND. (.NOT. ln_dynadv_vec) ) THEN 
    170          CALL iom_put( "uoce" , un(:,:,:) * fse3u_n(:,:,:) )    ! i-transport 
    171          CALL iom_put( "voce" , vn(:,:,:) * fse3v_n(:,:,:) )    ! j-transport 
    172       ELSE 
    173          CALL iom_put( "uoce" , un                         )    ! i-current 
    174          CALL iom_put( "voce" , vn                         )    ! j-current 
    175       END IF 
    176       CALL iom_put(    "avt"  , avt                        )    ! T vert. eddy diff. coef. 
    177       CALL iom_put(    "avm"  , avmu                       )    ! T vert. eddy visc. coef. 
    178       IF( lk_zdfddm ) THEN 
    179          CALL iom_put( "avs" , fsavs(:,:,:)                          )    ! S vert. eddy diff. coef. 
    180       ENDIF 
    181  
    182       DO jj = 2, jpjm1                                    ! sst gradient 
    183          DO ji = fs_2, fs_jpim1   ! vector opt. 
    184             zztmp      = tsn(ji,jj,1,jp_tem) 
    185             zztmpx     = ( tsn(ji+1,jj  ,1,jp_tem) - zztmp ) / e1u(ji,jj) + ( zztmp - tsn(ji-1,jj  ,1,jp_tem) ) / e1u(ji-1,jj  ) 
    186             zztmpy     = ( tsn(ji  ,jj+1,1,jp_tem) - zztmp ) / e2v(ji,jj) + ( zztmp - tsn(ji  ,jj-1,1,jp_tem) ) / e2v(ji  ,jj-1) 
    187             z2d(ji,jj) = 0.25 * ( zztmpx * zztmpx + zztmpy * zztmpy )   & 
    188                &              * umask(ji,jj,1) * umask(ji-1,jj,1) * vmask(ji,jj,1) * umask(ji,jj-1,1) 
    189          END DO 
    190       END DO 
    191       CALL lbc_lnk( z2d, 'T', 1. ) 
    192       CALL iom_put( "sstgrad2",  z2d               )    ! square of module of sst gradient 
    193 !CDIR NOVERRCHK 
    194       z2d(:,:) = SQRT( z2d(:,:) ) 
    195       CALL iom_put( "sstgrad" ,  z2d               )    ! module of sst gradient 
    196  
    197       IF( lk_diaar5 ) THEN 
     146      IF( .NOT.lk_vvl ) THEN 
     147         CALL iom_put( "e3t" , fse3t_n(:,:,:) ) 
     148         CALL iom_put( "e3u" , fse3u_n(:,:,:) ) 
     149         CALL iom_put( "e3v" , fse3v_n(:,:,:) ) 
     150         CALL iom_put( "e3w" , fse3w_n(:,:,:) ) 
     151      ENDIF 
     152       
     153      CALL iom_put( "toce", tsn(:,:,:,jp_tem) )    ! 3D temperature 
     154      CALL iom_put(  "sst", tsn(:,:,1,jp_tem) )    ! surface temperature 
     155      IF ( iom_use("sbt") ) THEN 
     156         DO jj = 1, jpj 
     157            DO ji = 1, jpi 
     158               z2d(ji,jj) = tsn(ji,jj,MAX(mbathy(ji,jj),1),jp_tem) 
     159            END DO 
     160         END DO 
     161         CALL iom_put( "sbt", z2d )                ! bottom temperature 
     162      ENDIF 
     163       
     164      CALL iom_put( "soce", tsn(:,:,:,jp_sal) )    ! 3D salinity 
     165      CALL iom_put(  "sss", tsn(:,:,1,jp_sal) )    ! surface salinity 
     166      IF ( iom_use("sbs") ) THEN 
     167         DO jj = 1, jpj 
     168            DO ji = 1, jpi 
     169               z2d(ji,jj) = tsn(ji,jj,MAX(mbathy(ji,jj),1),jp_sal) 
     170            END DO 
     171         END DO 
     172         CALL iom_put( "sbs", z2d )                ! bottom salinity 
     173      ENDIF 
     174          
     175      CALL iom_put( "uoce", un(:,:,:)         )    ! 3D i-current 
     176      CALL iom_put(  "ssu", un(:,:,1)         )    ! surface i-current 
     177      IF ( iom_use("sbu") ) THEN 
     178         DO jj = 1, jpj 
     179            DO ji = 1, jpi 
     180               z2d(ji,jj) = un(ji,jj,MAX(mbathy(ji,jj),1)) 
     181            END DO 
     182         END DO 
     183         CALL iom_put( "sbu", z2d )                ! bottom i-current 
     184      ENDIF 
     185       
     186      CALL iom_put( "voce", vn(:,:,:)         )    ! 3D j-current 
     187      CALL iom_put(  "ssv", vn(:,:,1)         )    ! surface j-current 
     188      IF ( iom_use("sbv") ) THEN 
     189         DO jj = 1, jpj 
     190            DO ji = 1, jpi 
     191               z2d(ji,jj) = vn(ji,jj,MAX(mbathy(ji,jj),1)) 
     192            END DO 
     193         END DO 
     194         CALL iom_put( "sbv", z2d )                ! bottom j-current 
     195      ENDIF 
     196 
     197      CALL iom_put( "avt" , avt                        )    ! T vert. eddy diff. coef. 
     198      CALL iom_put( "avm" , avmu                       )    ! T vert. eddy visc. coef. 
     199      CALL iom_put( "avs" , fsavs(:,:,:)               )    ! S vert. eddy diff. coef. (useful only with key_zdfddm) 
     200 
     201      IF ( iom_use("sstgrad") .OR. iom_use("sstgrad2") ) THEN 
     202         DO jj = 2, jpjm1                                    ! sst gradient 
     203            DO ji = fs_2, fs_jpim1   ! vector opt. 
     204               zztmp      = tsn(ji,jj,1,jp_tem) 
     205               zztmpx     = ( tsn(ji+1,jj  ,1,jp_tem) - zztmp ) / e1u(ji,jj) + ( zztmp - tsn(ji-1,jj  ,1,jp_tem) ) / e1u(ji-1,jj  ) 
     206               zztmpy     = ( tsn(ji  ,jj+1,1,jp_tem) - zztmp ) / e2v(ji,jj) + ( zztmp - tsn(ji  ,jj-1,1,jp_tem) ) / e2v(ji  ,jj-1) 
     207               z2d(ji,jj) = 0.25 * ( zztmpx * zztmpx + zztmpy * zztmpy )   & 
     208                  &              * umask(ji,jj,1) * umask(ji-1,jj,1) * vmask(ji,jj,1) * umask(ji,jj-1,1) 
     209            END DO 
     210         END DO 
     211         CALL lbc_lnk( z2d, 'T', 1. ) 
     212         CALL iom_put( "sstgrad2",  z2d               )    ! square of module of sst gradient 
     213         z2d(:,:) = SQRT( z2d(:,:) ) 
     214         CALL iom_put( "sstgrad" ,  z2d               )    ! module of sst gradient 
     215      ENDIF 
     216          
     217      ! clem: heat and salt content 
     218      IF( iom_use("heatc") ) THEN 
     219         z2d(:,:)  = 0._wp  
     220         DO jk = 1, jpkm1 
     221            DO jj = 1, jpj 
     222               DO ji = 1, jpi 
     223                  z2d(ji,jj) = z2d(ji,jj) + fse3t(ji,jj,jk) * tsn(ji,jj,jk,jp_tem) * tmask(ji,jj,jk) 
     224               END DO 
     225            END DO 
     226         END DO 
     227         CALL iom_put( "heatc", (rau0 * rcp) * z2d )    ! vertically integrated heat content (J/m2) 
     228      ENDIF 
     229 
     230      IF( iom_use("saltc") ) THEN 
     231         z2d(:,:)  = 0._wp  
     232         DO jk = 1, jpkm1 
     233            DO jj = 1, jpj 
     234               DO ji = 1, jpi 
     235                  z2d(ji,jj) = z2d(ji,jj) + fse3t(ji,jj,jk) * tsn(ji,jj,jk,jp_sal) * tmask(ji,jj,jk) 
     236               END DO 
     237            END DO 
     238         END DO 
     239         CALL iom_put( "saltc", rau0 * z2d )   ! vertically integrated salt content (PSU*kg/m2) 
     240      ENDIF 
     241      ! 
     242      IF ( iom_use("eken") ) THEN 
     243         rke(:,:,jk) = 0._wp                               !      kinetic energy  
     244         DO jk = 1, jpkm1 
     245            DO jj = 2, jpjm1 
     246               DO ji = fs_2, fs_jpim1   ! vector opt. 
     247                  zztmp   = 1._wp / ( e1e2t(ji,jj) * fse3t(ji,jj,jk) ) 
     248                  zztmpx  = 0.5 * (  un(ji-1,jj,jk) * un(ji-1,jj,jk) * e2u(ji-1,jj) * fse3u(ji-1,jj,jk)    & 
     249                     &             + un(ji  ,jj,jk) * un(ji  ,jj,jk) * e2u(ji  ,jj) * fse3u(ji  ,jj,jk) )  & 
     250                     &          *  zztmp  
     251                  ! 
     252                  zztmpy  = 0.5 * (  vn(ji,jj-1,jk) * vn(ji,jj-1,jk) * e1v(ji,jj-1) * fse3v(ji,jj-1,jk)    & 
     253                     &             + vn(ji,jj  ,jk) * vn(ji,jj  ,jk) * e1v(ji,jj  ) * fse3v(ji,jj  ,jk) )  & 
     254                     &          *  zztmp  
     255                  ! 
     256                  rke(ji,jj,jk) = 0.5_wp * ( zztmpx + zztmpy ) 
     257                  ! 
     258               ENDDO 
     259            ENDDO 
     260         ENDDO 
     261         CALL lbc_lnk( rke, 'T', 1. ) 
     262         CALL iom_put( "eken", rke )            
     263      ENDIF 
     264          
     265      IF( iom_use("u_masstr") .OR. iom_use("u_heattr") .OR. iom_use("u_salttr") ) THEN 
    198266         z3d(:,:,jpk) = 0.e0 
    199267         DO jk = 1, jpkm1 
    200             z3d(:,:,jk) = rau0 * un(:,:,jk) * e2u(:,:) * fse3u(:,:,jk) 
     268            z3d(:,:,jk) = rau0 * un(:,:,jk) * e2u(:,:) * fse3u(:,:,jk) * umask(:,:,jk) 
    201269         END DO 
    202270         CALL iom_put( "u_masstr", z3d )                  ! mass transport in i-direction 
    203          zztmp = 0.5 * rcp 
     271      ENDIF 
     272       
     273      IF( iom_use("u_heattr") ) THEN 
    204274         z2d(:,:) = 0.e0  
    205275         DO jk = 1, jpkm1 
    206276            DO jj = 2, jpjm1 
    207277               DO ji = fs_2, fs_jpim1   ! vector opt. 
    208                   z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * zztmp * ( tsn(ji,jj,jk,jp_tem) + tsn(ji+1,jj,jk,jp_tem) ) 
     278                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_tem) + tsn(ji+1,jj,jk,jp_tem) ) 
    209279               END DO 
    210280            END DO 
    211281         END DO 
    212282         CALL lbc_lnk( z2d, 'U', -1. ) 
    213          CALL iom_put( "u_heattr", z2d )                  ! heat transport in i-direction 
    214          DO jk = 1, jpkm1 
    215             z3d(:,:,jk) = rau0 * vn(:,:,jk) * e1v(:,:) * fse3v(:,:,jk) 
    216          END DO 
    217          CALL iom_put( "v_masstr", z3d )                  ! mass transport in j-direction 
     283         CALL iom_put( "u_heattr", (0.5 * rcp) * z2d )    ! heat transport in i-direction 
     284      ENDIF 
     285 
     286      IF( iom_use("u_salttr") ) THEN 
    218287         z2d(:,:) = 0.e0  
    219288         DO jk = 1, jpkm1 
    220289            DO jj = 2, jpjm1 
    221290               DO ji = fs_2, fs_jpim1   ! vector opt. 
    222                   z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * zztmp * ( tsn(ji,jj,jk,jp_tem) + tsn(ji,jj+1,jk,jp_tem) ) 
     291                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_sal) + tsn(ji+1,jj,jk,jp_sal) ) 
    223292               END DO 
    224293            END DO 
    225294         END DO 
     295         CALL lbc_lnk( z2d, 'U', -1. ) 
     296         CALL iom_put( "u_salttr", 0.5 * z2d )            ! heat transport in i-direction 
     297      ENDIF 
     298 
     299       
     300      IF( iom_use("v_masstr") .OR. iom_use("v_heattr") .OR. iom_use("v_salttr") ) THEN 
     301         z3d(:,:,jpk) = 0.e0 
     302         DO jk = 1, jpkm1 
     303            z3d(:,:,jk) = rau0 * vn(:,:,jk) * e1v(:,:) * fse3v(:,:,jk) * vmask(:,:,jk) 
     304         END DO 
     305         CALL iom_put( "v_masstr", z3d )                  ! mass transport in j-direction 
     306      ENDIF 
     307       
     308      IF( iom_use("v_heattr") ) THEN 
     309         z2d(:,:) = 0.e0  
     310         DO jk = 1, jpkm1 
     311            DO jj = 2, jpjm1 
     312               DO ji = fs_2, fs_jpim1   ! vector opt. 
     313                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_tem) + tsn(ji,jj+1,jk,jp_tem) ) 
     314               END DO 
     315            END DO 
     316         END DO 
    226317         CALL lbc_lnk( z2d, 'V', -1. ) 
    227          CALL iom_put( "v_heattr", z2d )                  !  heat transport in i-direction 
     318         CALL iom_put( "v_heattr", (0.5 * rcp) * z2d )    !  heat transport in j-direction 
     319      ENDIF 
     320 
     321      IF( iom_use("v_salttr") ) THEN 
     322         z2d(:,:) = 0.e0  
     323         DO jk = 1, jpkm1 
     324            DO jj = 2, jpjm1 
     325               DO ji = fs_2, fs_jpim1   ! vector opt. 
     326                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_sal) + tsn(ji,jj+1,jk,jp_sal) ) 
     327               END DO 
     328            END DO 
     329         END DO 
     330         CALL lbc_lnk( z2d, 'V', -1. ) 
     331         CALL iom_put( "v_salttr", 0.5 * z2d )            !  heat transport in j-direction 
    228332      ENDIF 
    229333      ! 
     
    500604         ENDIF 
    501605 
    502 #if ! defined key_coupled  
    503          CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
    504             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    505          CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp 
    506             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    507          CALL histdef( nid_T, "sosafldp", "Surface salt flux: damping"         , "Kg/m2/s",   &  ! erp * sn 
    508             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    509 #endif 
    510  
    511  
    512  
    513 #if ( defined key_coupled && ! defined key_lim3 && ! defined key_lim2 )  
    514          CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
    515             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    516          CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp 
    517             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    518          CALL histdef( nid_T, "sosafldp", "Surface salt flux: Damping"         , "Kg/m2/s",   &  ! erp * sn 
    519             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    520 #endif 
     606         IF( .NOT. lk_cpl ) THEN 
     607            CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
     608               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     609            CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp 
     610               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     611            CALL histdef( nid_T, "sosafldp", "Surface salt flux: damping"         , "Kg/m2/s",   &  ! erp * sn 
     612               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     613         ENDIF 
     614 
     615         IF( lk_cpl .AND. nn_ice <= 1 ) THEN 
     616            CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
     617               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     618            CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp 
     619               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     620            CALL histdef( nid_T, "sosafldp", "Surface salt flux: Damping"         , "Kg/m2/s",   &  ! erp * sn 
     621               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     622         ENDIF 
     623          
    521624         clmx ="l_max(only(x))"    ! max index on a period 
    522625         CALL histdef( nid_T, "sobowlin", "Bowl Index"                         , "W-point",   &  ! bowl INDEX  
     
    533636#endif 
    534637 
    535 #if defined key_coupled  
    536 # if defined key_lim3 
    537          Must be adapted to LIM3 
    538 # endif  
    539 # if defined key_lim2 
    540          CALL histdef( nid_T,"soicetem" , "Ice Surface Temperature"            , "K"      ,   &  ! tn_ice 
    541             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    542          CALL histdef( nid_T,"soicealb" , "Ice Albedo"                         , "[0,1]"  ,   &  ! alb_ice 
    543             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    544 # endif  
    545 #endif  
     638         IF( lk_cpl .AND. nn_ice == 2 ) THEN 
     639            CALL histdef( nid_T,"soicetem" , "Ice Surface Temperature"            , "K"      ,   &  ! tn_ice 
     640               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     641            CALL histdef( nid_T,"soicealb" , "Ice Albedo"                         , "[0,1]"  ,   &  ! alb_ice 
     642               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     643         ENDIF 
    546644 
    547645         CALL histend( nid_T, snc4chunks=snc4set ) 
     
    634732      ENDIF 
    635733 
    636       ! Write fields on T grid 
    637734      IF( lk_vvl ) THEN 
    638735         CALL histwrite( nid_T, "votemper", it, tsn(:,:,:,jp_tem) * fse3t_n(:,:,:) , ndim_T , ndex_T  )   ! heat content 
     
    645742         CALL histwrite( nid_T, "sosstsst", it, tsn(:,:,1,jp_tem) , ndim_hT, ndex_hT )   ! sea surface temperature 
    646743         CALL histwrite( nid_T, "sosaline", it, tsn(:,:,1,jp_sal) , ndim_hT, ndex_hT )   ! sea surface salinity 
    647  
    648744      ENDIF 
    649745      IF( lk_vvl ) THEN 
     
    695791      ENDIF 
    696792 
    697 #if ! defined key_coupled 
    698       CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
    699       CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
    700       IF( ln_ssr ) zw2d(:,:) = erp(:,:) * tsn(:,:,1,jp_sal) * tmask(:,:,1) 
    701       CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
    702 #endif 
    703 #if ( defined key_coupled && ! defined key_lim3 && ! defined key_lim2 )  
    704       CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
    705       CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
     793      IF( .NOT. lk_cpl ) THEN 
     794         CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
     795         CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
    706796         IF( ln_ssr ) zw2d(:,:) = erp(:,:) * tsn(:,:,1,jp_sal) * tmask(:,:,1) 
    707       CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
    708 #endif 
    709       zw2d(:,:) = FLOAT( nmln(:,:) ) * tmask(:,:,1) 
    710       CALL histwrite( nid_T, "sobowlin", it, zw2d          , ndim_hT, ndex_hT )   ! ??? 
     797         CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
     798      ENDIF 
     799      IF( lk_cpl .AND. nn_ice <= 1 ) THEN 
     800         CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
     801         CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
     802         IF( ln_ssr ) zw2d(:,:) = erp(:,:) * tsn(:,:,1,jp_sal) * tmask(:,:,1) 
     803         CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
     804      ENDIF 
     805!      zw2d(:,:) = FLOAT( nmln(:,:) ) * tmask(:,:,1) 
     806!      CALL histwrite( nid_T, "sobowlin", it, zw2d          , ndim_hT, ndex_hT )   ! ??? 
    711807 
    712808#if defined key_diahth 
     
    717813#endif 
    718814 
    719 #if defined key_coupled  
    720 # if defined key_lim3 
    721       Must be adapted for LIM3 
    722       CALL histwrite( nid_T, "soicetem", it, tn_ice        , ndim_hT, ndex_hT )   ! surf. ice temperature 
    723       CALL histwrite( nid_T, "soicealb", it, alb_ice       , ndim_hT, ndex_hT )   ! ice albedo 
    724 # endif 
    725 # if defined key_lim2 
    726       CALL histwrite( nid_T, "soicetem", it, tn_ice(:,:,1) , ndim_hT, ndex_hT )   ! surf. ice temperature 
    727       CALL histwrite( nid_T, "soicealb", it, alb_ice(:,:,1), ndim_hT, ndex_hT )   ! ice albedo 
    728 # endif 
    729 #endif 
    730          ! Write fields on U grid 
     815      IF( lk_cpl .AND. nn_ice == 2 ) THEN 
     816         CALL histwrite( nid_T, "soicetem", it, tn_ice(:,:,1) , ndim_hT, ndex_hT )   ! surf. ice temperature 
     817         CALL histwrite( nid_T, "soicealb", it, alb_ice(:,:,1), ndim_hT, ndex_hT )   ! ice albedo 
     818      ENDIF 
     819 
    731820      CALL histwrite( nid_U, "vozocrtx", it, un            , ndim_U , ndex_U )    ! i-current 
    732821      IF( ln_traldf_gdia ) THEN 
     
    750839      CALL histwrite( nid_U, "sozotaux", it, utau          , ndim_hU, ndex_hU )   ! i-wind stress 
    751840 
    752          ! Write fields on V grid 
    753841      CALL histwrite( nid_V, "vomecrty", it, vn            , ndim_V , ndex_V  )   ! j-current 
    754842      IF( ln_traldf_gdia ) THEN 
     
    765853      CALL histwrite( nid_V, "sometauy", it, vtau          , ndim_hV, ndex_hV )   ! j-wind stress 
    766854 
    767          ! Write fields on W grid 
    768855      CALL histwrite( nid_W, "vovecrtz", it, wn             , ndim_T, ndex_T )    ! vert. current 
    769856      IF( ln_traldf_gdia ) THEN 
Note: See TracChangeset for help on using the changeset viewer.