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

Ignore:
Timestamp:
2015-04-13T15:08:59+02:00 (9 years ago)
Author:
davestorkey
Message:

Merge in changes from trunk up to 5021.

File:
1 edited

Legend:

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

    r4761 r5208  
    4444   USE in_out_manager  ! I/O manager 
    4545   USE diadimg         ! dimg direct access file format output 
    46    USE diaar5, ONLY :   lk_diaar5 
    4746   USE iom 
    4847   USE ioipsl 
     
    8887      INTEGER, DIMENSION(2) :: ierr 
    8988      !!---------------------------------------------------------------------- 
    90       ! 
    9189      ierr = 0 
    92       ! 
    9390      ALLOCATE( ndex_hT(jpi*jpj) , ndex_T(jpi*jpj*jpk) ,     & 
    9491         &      ndex_hU(jpi*jpj) , ndex_U(jpi*jpj*jpk) ,     & 
     
    131128      !! 
    132129      REAL(wp), POINTER, DIMENSION(:,:)   :: z2d      ! 2D workspace 
    133       REAL(wp), POINTER, DIMENSION(:,:)   :: z2ds     ! 2D workspace 
    134130      REAL(wp), POINTER, DIMENSION(:,:,:) :: z3d      ! 3D workspace 
    135131      !!---------------------------------------------------------------------- 
     
    137133      IF( nn_timing == 1 )   CALL timing_start('dia_wri') 
    138134      !  
    139       CALL wrk_alloc( jpi , jpj      , z2d , z2ds ) 
     135      CALL wrk_alloc( jpi , jpj      , z2d ) 
    140136      CALL wrk_alloc( jpi , jpj, jpk , z3d ) 
    141137      ! 
     
    149145         z3d(:,:,:) = tsn(:,:,:,jp_tem) * fse3t_n(:,:,:) 
    150146         CALL iom_put( "toce" , z3d                        )   ! heat content 
    151          CALL iom_put( "sst"  , z3d(:,:,1)                 )   ! sea surface heat content 
    152          z3d(:,:,1) = tsn(:,:,1,jp_tem) * z3d(:,:,1) 
    153          CALL iom_put( "sst2" , z3d(:,:,1)                 )   ! sea surface content of squared temperature 
     147         DO jj = 1, jpj 
     148            DO ji = 1, jpi 
     149               z2d(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_tem) * fse3t_n(ji,jj,mikt(ji,jj)) 
     150            END DO 
     151         END DO   
     152         CALL iom_put( "sst"  , z2d(:,:)                 )   ! sea surface heat content       
     153         DO jj = 1, jpj 
     154            DO ji = 1, jpi 
     155               z2d(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_tem)**2 * fse3t_n(ji,jj,mikt(ji,jj)) 
     156            END DO 
     157         END DO   
     158         CALL iom_put( "sst2" , z2d(:,:)      )   ! sea surface content of squared temperature 
    154159         z3d(:,:,:) = tsn(:,:,:,jp_sal) * fse3t_n(:,:,:)             
    155160         CALL iom_put( "soce" , z3d                        )   ! salinity content 
    156          CALL iom_put( "sss"  , z3d(:,:,1)                 )   ! sea surface salinity content 
    157          z3d(:,:,1) = tsn(:,:,1,jp_sal) * z3d(:,:,1) 
    158          CALL iom_put( "sss2" , z3d(:,:,1)                 )   ! sea surface content of squared salinity 
     161         DO jj = 1, jpj 
     162            DO ji = 1, jpi 
     163               z2d(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_sal) * fse3t_n(ji,jj,mikt(ji,jj)) 
     164            END DO 
     165         END DO   
     166         CALL iom_put( "sss"  , z2d(:,:)                 )   ! sea surface salinity content 
     167         DO jj = 1, jpj 
     168            DO ji = 1, jpi 
     169               z2d(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_sal)**2 * fse3t_n(ji,jj,mikt(ji,jj)) 
     170            END DO 
     171         END DO   
     172         CALL iom_put( "sss2" , z2d(:,:)                 )   ! sea surface content of squared salinity 
    159173      ELSE 
    160          CALL iom_put( "toce" , tsn(:,:,:,jp_tem)          )   ! temperature 
    161          CALL iom_put( "sst"  , tsn(:,:,1,jp_tem)          )   ! sea surface temperature 
    162          CALL iom_put( "sst2" , tsn(:,:,1,jp_tem) * tsn(:,:,1,jp_tem) ) ! square of sea surface temperature 
     174         CALL iom_put( "toce" , tsn(:,:,:,jp_tem)        )   ! temperature 
     175         IF ( iom_use("sst") ) THEN 
     176            DO jj = 1, jpj 
     177               DO ji = 1, jpi 
     178                  z2d(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_tem) 
     179               END DO 
     180            END DO 
     181            CALL iom_put( "sst"  , z2d(:,:)            ) ! sea surface temperature 
     182         ENDIF 
     183         IF ( iom_use("sst2") )   CALL iom_put( "sst2" , z2d(:,:) * z2d(:,:) ) ! square of sea surface temperature 
    163184         CALL iom_put( "soce" , tsn(:,:,:,jp_sal)          )   ! salinity 
    164          CALL iom_put( "sss"  , tsn(:,:,1,jp_sal)          )   ! sea surface salinity 
    165          CALL iom_put( "sss2" , tsn(:,:,1,jp_sal) * tsn(:,:,1,jp_sal) ) ! square of sea surface salinity 
     185         IF ( iom_use("sss") ) THEN 
     186            DO jj = 1, jpj 
     187               DO ji = 1, jpi 
     188                  z2d(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_sal) 
     189               END DO 
     190            END DO 
     191            CALL iom_put( "sss"  , z2d(:,:)            ) ! sea surface salinity 
     192         ENDIF 
     193         CALL iom_put( "sss2" , z2d(:,:) * z2d(:,:) ) ! square of sea surface salinity 
    166194      END IF 
    167195      IF( lk_vvl .AND. (.NOT. ln_dynadv_vec) ) THEN 
    168          CALL iom_put( "uoce" , un(:,:,:) * fse3u_n(:,:,:) )    ! i-transport 
    169          CALL iom_put( "voce" , vn(:,:,:) * fse3v_n(:,:,:) )    ! j-transport 
     196         CALL iom_put( "uoce" , umask(:,:,:) * un(:,:,:) * fse3u_n(:,:,:) )    ! i-transport 
     197         CALL iom_put( "voce" , vmask(:,:,:) * vn(:,:,:) * fse3v_n(:,:,:) )    ! j-transport 
    170198      ELSE 
    171          CALL iom_put( "uoce" , un                         )    ! i-current 
    172          CALL iom_put( "voce" , vn                         )    ! j-current 
    173       END IF 
     199         CALL iom_put( "uoce" , umask(:,:,:) * un(:,:,:)                  )    ! i-current 
     200         CALL iom_put( "voce" , vmask(:,:,:) * vn(:,:,:)                  )    ! j-current 
     201         IF ( iom_use("ssu") ) THEN 
     202            DO jj = 1, jpj 
     203               DO ji = 1, jpi 
     204                  z2d(ji,jj) = un(ji,jj,miku(ji,jj)) 
     205               END DO 
     206            END DO 
     207            CALL iom_put( "ssu"   , z2d                                    )    ! i-current 
     208         ENDIF 
     209         IF ( iom_use("ssv") ) THEN 
     210            DO jj = 1, jpj 
     211               DO ji = 1, jpi 
     212                  z2d(ji,jj) = vn(ji,jj,mikv(ji,jj)) 
     213               END DO 
     214            END DO 
     215            CALL iom_put( "ssv"   , z2d                                    )    ! j-current 
     216         ENDIF 
     217      ENDIF 
    174218      CALL iom_put(    "avt"  , avt                        )    ! T vert. eddy diff. coef. 
    175219      CALL iom_put(    "avm"  , avmu                       )    ! T vert. eddy visc. coef. 
     
    178222      ENDIF 
    179223 
    180       DO jj = 2, jpjm1                                    ! sst gradient 
    181          DO ji = fs_2, fs_jpim1   ! vector opt. 
    182             zztmp      = tsn(ji,jj,1,jp_tem) 
    183             zztmpx     = ( tsn(ji+1,jj  ,1,jp_tem) - zztmp ) / e1u(ji,jj) + ( zztmp - tsn(ji-1,jj  ,1,jp_tem) ) / e1u(ji-1,jj  ) 
    184             zztmpy     = ( tsn(ji  ,jj+1,1,jp_tem) - zztmp ) / e2v(ji,jj) + ( zztmp - tsn(ji  ,jj-1,1,jp_tem) ) / e2v(ji  ,jj-1) 
    185             z2d(ji,jj) = 0.25 * ( zztmpx * zztmpx + zztmpy * zztmpy )   & 
    186                &              * umask(ji,jj,1) * umask(ji-1,jj,1) * vmask(ji,jj,1) * umask(ji,jj-1,1) 
    187          END DO 
    188       END DO 
    189       CALL lbc_lnk( z2d, 'T', 1. ) 
    190       CALL iom_put( "sstgrad2",  z2d               )    ! square of module of sst gradient 
    191 !CDIR NOVERRCHK 
    192       z2d(:,:) = SQRT( z2d(:,:) ) 
    193       CALL iom_put( "sstgrad" ,  z2d               )    ! module of sst gradient 
    194  
     224      IF ( iom_use("sstgrad2") .OR. iom_use("sstgrad2") ) THEN 
     225         DO jj = 2, jpjm1                                    ! sst gradient 
     226            DO ji = fs_2, fs_jpim1   ! vector opt. 
     227               zztmp      = tsn(ji,jj,1,jp_tem) 
     228               zztmpx     = ( tsn(ji+1,jj  ,1,jp_tem) - zztmp ) / e1u(ji,jj) + ( zztmp - tsn(ji-1,jj  ,1,jp_tem) ) / e1u(ji-1,jj  ) 
     229               zztmpy     = ( tsn(ji  ,jj+1,1,jp_tem) - zztmp ) / e2v(ji,jj) + ( zztmp - tsn(ji  ,jj-1,1,jp_tem) ) / e2v(ji  ,jj-1) 
     230               z2d(ji,jj) = 0.25 * ( zztmpx * zztmpx + zztmpy * zztmpy )   & 
     231                  &              * umask(ji,jj,1) * umask(ji-1,jj,1) * vmask(ji,jj,1) * umask(ji,jj-1,1) 
     232            END DO 
     233         END DO 
     234         CALL lbc_lnk( z2d, 'T', 1. ) 
     235         CALL iom_put( "sstgrad2",  z2d               )    ! square of module of sst gradient 
     236         !CDIR NOVERRCHK< 
     237         z2d(:,:) = SQRT( z2d(:,:) ) 
     238         CALL iom_put( "sstgrad" ,  z2d               )    ! module of sst gradient 
     239      ENDIF 
     240          
    195241      ! clem: heat and salt content 
    196       z2d(:,:)  = 0._wp  
    197       z2ds(:,:) = 0._wp  
    198       DO jk = 1, jpkm1 
    199          DO jj = 2, jpjm1 
    200             DO ji = fs_2, fs_jpim1   ! vector opt. 
    201                z2d(ji,jj) = z2d(ji,jj) + rau0 * rcp * fse3t(ji,jj,jk) * tsn(ji,jj,jk,jp_tem) * tmask(ji,jj,jk) 
    202                z2ds(ji,jj) = z2ds(ji,jj) + rau0 * fse3t(ji,jj,jk) * tsn(ji,jj,jk,jp_sal) * tmask(ji,jj,jk) 
    203             END DO 
    204          END DO 
    205       END DO 
    206       CALL lbc_lnk( z2d, 'T', 1. ) 
    207       CALL lbc_lnk( z2ds, 'T', 1. ) 
    208       CALL iom_put( "heatc", z2d )    ! vertically integrated heat content (J/m2) 
    209       CALL iom_put( "saltc", z2ds )   ! vertically integrated salt content (PSU*kg/m2) 
    210        
    211  
    212       IF( lk_diaar5 ) THEN 
     242      IF( iom_use("heatc") ) THEN 
     243         z2d(:,:)  = 0._wp  
     244         DO jk = 1, jpkm1 
     245            DO jj = 2, jpjm1 
     246               DO ji = fs_2, fs_jpim1   ! vector opt. 
     247                  z2d(ji,jj) = z2d(ji,jj) + fse3t(ji,jj,jk) * tsn(ji,jj,jk,jp_tem) * tmask(ji,jj,jk) 
     248               END DO 
     249            END DO 
     250         END DO 
     251         CALL lbc_lnk( z2d, 'T', 1. ) 
     252         CALL iom_put( "heatc", (rau0 * rcp) * z2d )    ! vertically integrated heat content (J/m2) 
     253      ENDIF 
     254 
     255      IF( iom_use("saltc") ) THEN 
     256         z2d(:,:)  = 0._wp  
     257         DO jk = 1, jpkm1 
     258            DO jj = 2, jpjm1 
     259               DO ji = fs_2, fs_jpim1   ! vector opt. 
     260                  z2d(ji,jj) = z2d(ji,jj) + fse3t(ji,jj,jk) * tsn(ji,jj,jk,jp_sal) * tmask(ji,jj,jk) 
     261               END DO 
     262            END DO 
     263         END DO 
     264         CALL lbc_lnk( z2d, 'T', 1. ) 
     265         CALL iom_put( "saltc", rau0 * z2d )   ! vertically integrated salt content (PSU*kg/m2) 
     266      ENDIF 
     267      ! 
     268      IF ( iom_use("eken") ) THEN 
     269         rke(:,:,jk) = 0._wp                               !      kinetic energy  
     270         DO jk = 1, jpkm1 
     271            DO jj = 2, jpjm1 
     272               DO ji = fs_2, fs_jpim1   ! vector opt. 
     273                  zztmp   = 1._wp / ( e1e2t(ji,jj) * fse3t(ji,jj,jk) ) 
     274                  zztmpx  = 0.5 * (  un(ji-1,jj,jk) * un(ji-1,jj,jk) * e2u(ji-1,jj) * fse3u(ji-1,jj,jk)    & 
     275                     &             + un(ji  ,jj,jk) * un(ji  ,jj,jk) * e2u(ji  ,jj) * fse3u(ji  ,jj,jk) )  & 
     276                     &          *  zztmp  
     277                  ! 
     278                  zztmpy  = 0.5 * (  vn(ji,jj-1,jk) * vn(ji,jj-1,jk) * e1v(ji,jj-1) * fse3v(ji,jj-1,jk)    & 
     279                     &             + vn(ji,jj  ,jk) * vn(ji,jj  ,jk) * e1v(ji,jj  ) * fse3v(ji,jj  ,jk) )  & 
     280                     &          *  zztmp  
     281                  ! 
     282                  rke(ji,jj,jk) = 0.5_wp * ( zztmpx + zztmpy ) 
     283                  ! 
     284               ENDDO 
     285            ENDDO 
     286         ENDDO 
     287         CALL lbc_lnk( rke, 'T', 1. ) 
     288         CALL iom_put( "eken", rke )            
     289      ENDIF 
     290          
     291      IF( iom_use("u_masstr") .OR. iom_use("u_heattr") .OR. iom_use("u_salttr") ) THEN 
    213292         z3d(:,:,jpk) = 0.e0 
    214293         DO jk = 1, jpkm1 
     
    216295         END DO 
    217296         CALL iom_put( "u_masstr", z3d )                  ! mass transport in i-direction 
    218  
    219          zztmp = 0.5 * rcp 
     297      ENDIF 
     298       
     299      IF( iom_use("u_heattr") ) THEN 
    220300         z2d(:,:) = 0.e0  
    221          z2ds(:,:) = 0.e0  
    222301         DO jk = 1, jpkm1 
    223302            DO jj = 2, jpjm1 
    224303               DO ji = fs_2, fs_jpim1   ! vector opt. 
    225                   z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * zztmp * ( tsn(ji,jj,jk,jp_tem) + tsn(ji+1,jj,jk,jp_tem) ) 
    226                   z2ds(ji,jj) = z2ds(ji,jj) + z3d(ji,jj,jk) * 0.5_wp * ( tsn(ji,jj,jk,jp_sal) + tsn(ji+1,jj,jk,jp_sal) ) 
     304                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_tem) + tsn(ji+1,jj,jk,jp_tem) ) 
    227305               END DO 
    228306            END DO 
    229307         END DO 
    230308         CALL lbc_lnk( z2d, 'U', -1. ) 
    231          CALL lbc_lnk( z2ds, 'U', -1. ) 
    232          CALL iom_put( "u_heattr", z2d )                  ! heat transport in i-direction 
    233          CALL iom_put( "u_salttr", z2ds )                 ! salt transport in i-direction 
    234  
     309         CALL iom_put( "u_heattr", (0.5 * rcp) * z2d )    ! heat transport in i-direction 
     310      ENDIF 
     311 
     312      IF( iom_use("u_salttr") ) THEN 
     313         z2d(:,:) = 0.e0  
     314         DO jk = 1, jpkm1 
     315            DO jj = 2, jpjm1 
     316               DO ji = fs_2, fs_jpim1   ! vector opt. 
     317                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_sal) + tsn(ji+1,jj,jk,jp_sal) ) 
     318               END DO 
     319            END DO 
     320         END DO 
     321         CALL lbc_lnk( z2d, 'U', -1. ) 
     322         CALL iom_put( "u_salttr", 0.5 * z2d )            ! heat transport in i-direction 
     323      ENDIF 
     324 
     325       
     326      IF( iom_use("v_masstr") .OR. iom_use("v_heattr") .OR. iom_use("v_salttr") ) THEN 
    235327         z3d(:,:,jpk) = 0.e0 
    236328         DO jk = 1, jpkm1 
     
    238330         END DO 
    239331         CALL iom_put( "v_masstr", z3d )                  ! mass transport in j-direction 
    240  
     332      ENDIF 
     333       
     334      IF( iom_use("v_heattr") ) THEN 
    241335         z2d(:,:) = 0.e0  
    242          z2ds(:,:) = 0.e0  
    243336         DO jk = 1, jpkm1 
    244337            DO jj = 2, jpjm1 
    245338               DO ji = fs_2, fs_jpim1   ! vector opt. 
    246                   z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * zztmp * ( tsn(ji,jj,jk,jp_tem) + tsn(ji,jj+1,jk,jp_tem) ) 
    247                   z2ds(ji,jj) = z2ds(ji,jj) + z3d(ji,jj,jk) * 0.5_wp * ( tsn(ji,jj,jk,jp_sal) + tsn(ji,jj+1,jk,jp_sal) ) 
     339                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_tem) + tsn(ji,jj+1,jk,jp_tem) ) 
    248340               END DO 
    249341            END DO 
    250342         END DO 
    251343         CALL lbc_lnk( z2d, 'V', -1. ) 
    252          CALL lbc_lnk( z2ds, 'V', -1. ) 
    253          CALL iom_put( "v_heattr", z2d )                  !  heat transport in j-direction 
    254          CALL iom_put( "v_salttr", z2ds )                 !  salt transport in j-direction 
    255       ENDIF 
    256       ! 
    257       CALL wrk_dealloc( jpi , jpj      , z2d , z2ds ) 
     344         CALL iom_put( "v_heattr", (0.5 * rcp) * z2d )    !  heat transport in j-direction 
     345      ENDIF 
     346 
     347      IF( iom_use("v_salttr") ) THEN 
     348         z2d(:,:) = 0.e0  
     349         DO jk = 1, jpkm1 
     350            DO jj = 2, jpjm1 
     351               DO ji = fs_2, fs_jpim1   ! vector opt. 
     352                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_sal) + tsn(ji,jj+1,jk,jp_sal) ) 
     353               END DO 
     354            END DO 
     355         END DO 
     356         CALL lbc_lnk( z2d, 'V', -1. ) 
     357         CALL iom_put( "v_salttr", 0.5 * z2d )            !  heat transport in j-direction 
     358      ENDIF 
     359      ! 
     360      CALL wrk_dealloc( jpi , jpj      , z2d ) 
    258361      CALL wrk_dealloc( jpi , jpj, jpk , z3d ) 
    259362      ! 
     
    518621         ENDIF 
    519622 
    520 #if ! defined key_coupled  
    521          CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
    522             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    523          CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp 
    524             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    525          CALL histdef( nid_T, "sosafldp", "Surface salt flux: damping"         , "Kg/m2/s",   &  ! erp * sn 
    526             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    527 #endif 
    528  
    529  
    530  
    531 #if ( defined key_coupled && ! defined key_lim3 && ! defined key_lim2 )  
    532          CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
    533             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    534          CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp 
    535             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    536          CALL histdef( nid_T, "sosafldp", "Surface salt flux: Damping"         , "Kg/m2/s",   &  ! erp * sn 
    537             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    538 #endif 
     623         IF( .NOT. lk_cpl ) THEN 
     624            CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
     625               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     626            CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp 
     627               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     628            CALL histdef( nid_T, "sosafldp", "Surface salt flux: damping"         , "Kg/m2/s",   &  ! erp * sn 
     629               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     630         ENDIF 
     631 
     632         IF( lk_cpl .AND. nn_ice <= 1 ) THEN 
     633            CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
     634               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     635            CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp 
     636               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     637            CALL histdef( nid_T, "sosafldp", "Surface salt flux: Damping"         , "Kg/m2/s",   &  ! erp * sn 
     638               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     639         ENDIF 
     640          
    539641         clmx ="l_max(only(x))"    ! max index on a period 
    540642         CALL histdef( nid_T, "sobowlin", "Bowl Index"                         , "W-point",   &  ! bowl INDEX  
     
    551653#endif 
    552654 
    553 #if defined key_coupled  
    554 # if defined key_lim3 
    555          Must be adapted to LIM3 
    556 # endif  
    557 # if defined key_lim2 
    558          CALL histdef( nid_T,"soicetem" , "Ice Surface Temperature"            , "K"      ,   &  ! tn_ice 
    559             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    560          CALL histdef( nid_T,"soicealb" , "Ice Albedo"                         , "[0,1]"  ,   &  ! alb_ice 
    561             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    562 # endif  
    563 #endif  
     655         IF( lk_cpl .AND. nn_ice == 2 ) THEN 
     656            CALL histdef( nid_T,"soicetem" , "Ice Surface Temperature"            , "K"      ,   &  ! tn_ice 
     657               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     658            CALL histdef( nid_T,"soicealb" , "Ice Albedo"                         , "[0,1]"  ,   &  ! alb_ice 
     659               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     660         ENDIF 
    564661 
    565662         CALL histend( nid_T, snc4chunks=snc4set ) 
     
    652749      ENDIF 
    653750 
    654       ! Write fields on T grid 
    655751      IF( lk_vvl ) THEN 
    656752         CALL histwrite( nid_T, "votemper", it, tsn(:,:,:,jp_tem) * fse3t_n(:,:,:) , ndim_T , ndex_T  )   ! heat content 
     
    663759         CALL histwrite( nid_T, "sosstsst", it, tsn(:,:,1,jp_tem) , ndim_hT, ndex_hT )   ! sea surface temperature 
    664760         CALL histwrite( nid_T, "sosaline", it, tsn(:,:,1,jp_sal) , ndim_hT, ndex_hT )   ! sea surface salinity 
    665  
    666761      ENDIF 
    667762      IF( lk_vvl ) THEN 
     
    713808      ENDIF 
    714809 
    715 #if ! defined key_coupled 
    716       CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
    717       CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
    718       IF( ln_ssr ) zw2d(:,:) = erp(:,:) * tsn(:,:,1,jp_sal) * tmask(:,:,1) 
    719       CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
    720 #endif 
    721 #if ( defined key_coupled && ! defined key_lim3 && ! defined key_lim2 )  
    722       CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
    723       CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
     810      IF( .NOT. lk_cpl ) THEN 
     811         CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
     812         CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
    724813         IF( ln_ssr ) zw2d(:,:) = erp(:,:) * tsn(:,:,1,jp_sal) * tmask(:,:,1) 
    725       CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
    726 #endif 
    727       zw2d(:,:) = FLOAT( nmln(:,:) ) * tmask(:,:,1) 
    728       CALL histwrite( nid_T, "sobowlin", it, zw2d          , ndim_hT, ndex_hT )   ! ??? 
     814         CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
     815      ENDIF 
     816      IF( lk_cpl .AND. nn_ice <= 1 ) THEN 
     817         CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
     818         CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
     819         IF( ln_ssr ) zw2d(:,:) = erp(:,:) * tsn(:,:,1,jp_sal) * tmask(:,:,1) 
     820         CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
     821      ENDIF 
     822!      zw2d(:,:) = FLOAT( nmln(:,:) ) * tmask(:,:,1) 
     823!      CALL histwrite( nid_T, "sobowlin", it, zw2d          , ndim_hT, ndex_hT )   ! ??? 
    729824 
    730825#if defined key_diahth 
     
    735830#endif 
    736831 
    737 #if defined key_coupled  
    738 # if defined key_lim3 
    739       Must be adapted for LIM3 
    740       CALL histwrite( nid_T, "soicetem", it, tn_ice        , ndim_hT, ndex_hT )   ! surf. ice temperature 
    741       CALL histwrite( nid_T, "soicealb", it, alb_ice       , ndim_hT, ndex_hT )   ! ice albedo 
    742 # endif 
    743 # if defined key_lim2 
    744       CALL histwrite( nid_T, "soicetem", it, tn_ice(:,:,1) , ndim_hT, ndex_hT )   ! surf. ice temperature 
    745       CALL histwrite( nid_T, "soicealb", it, alb_ice(:,:,1), ndim_hT, ndex_hT )   ! ice albedo 
    746 # endif 
    747 #endif 
    748          ! Write fields on U grid 
     832      IF( lk_cpl .AND. nn_ice == 2 ) THEN 
     833         CALL histwrite( nid_T, "soicetem", it, tn_ice(:,:,1) , ndim_hT, ndex_hT )   ! surf. ice temperature 
     834         CALL histwrite( nid_T, "soicealb", it, alb_ice(:,:,1), ndim_hT, ndex_hT )   ! ice albedo 
     835      ENDIF 
     836 
    749837      CALL histwrite( nid_U, "vozocrtx", it, un            , ndim_U , ndex_U )    ! i-current 
    750838      IF( ln_traldf_gdia ) THEN 
     
    768856      CALL histwrite( nid_U, "sozotaux", it, utau          , ndim_hU, ndex_hU )   ! i-wind stress 
    769857 
    770          ! Write fields on V grid 
    771858      CALL histwrite( nid_V, "vomecrty", it, vn            , ndim_V , ndex_V  )   ! j-current 
    772859      IF( ln_traldf_gdia ) THEN 
     
    783870      CALL histwrite( nid_V, "sometauy", it, vtau          , ndim_hV, ndex_hV )   ! j-wind stress 
    784871 
    785          ! Write fields on W grid 
    786872      CALL histwrite( nid_W, "vovecrtz", it, wn             , ndim_T, ndex_T )    ! vert. current 
    787873      IF( ln_traldf_gdia ) THEN 
Note: See TracChangeset for help on using the changeset viewer.