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

Ignore:
Timestamp:
2015-01-20T15:26:13+01:00 (9 years ago)
Author:
jamesharle
Message:

Merging branch with HEAD of the trunk

File:
1 edited

Legend:

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

    r4792 r5038  
    4444   USE in_out_manager  ! I/O manager 
    4545   USE diadimg         ! dimg direct access file format output 
     46<<<<<<< .working 
    4647   USE diaar5, ONLY :   lk_diaar5 
     48======= 
     49>>>>>>> .merge-right.r5035 
    4750   USE iom 
    4851   USE ioipsl 
     
    8891      INTEGER, DIMENSION(2) :: ierr 
    8992      !!---------------------------------------------------------------------- 
    90       ! 
    9193      ierr = 0 
    92       ! 
    9394      ALLOCATE( ndex_hT(jpi*jpj) , ndex_T(jpi*jpj*jpk) ,     & 
    9495         &      ndex_hU(jpi*jpj) , ndex_U(jpi*jpj*jpk) ,     & 
     
    130131      REAL(wp)                     ::   zztmp, zztmpx, zztmpy   !  
    131132      !! 
     133<<<<<<< .working 
    132134      REAL(wp), POINTER, DIMENSION(:,:)   :: z2d      ! 2D workspace 
    133135      REAL(wp), POINTER, DIMENSION(:,:)   :: z2ds     ! 2D workspace 
     136======= 
     137      REAL(wp), POINTER, DIMENSION(:,:)   :: z2d      ! 2D workspace 
     138>>>>>>> .merge-right.r5035 
    134139      REAL(wp), POINTER, DIMENSION(:,:,:) :: z3d      ! 3D workspace 
    135140      !!---------------------------------------------------------------------- 
     
    149154         z3d(:,:,:) = tsn(:,:,:,jp_tem) * fse3t_n(:,:,:) 
    150155         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 
     156         DO jj = 1, jpj 
     157            DO ji = 1, jpi 
     158               z2d(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_tem) * fse3t_n(ji,jj,mikt(ji,jj)) 
     159            END DO 
     160         END DO   
     161         CALL iom_put( "sst"  , z2d(:,:)                 )   ! sea surface heat content       
     162         DO jj = 1, jpj 
     163            DO ji = 1, jpi 
     164               z2d(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_tem)**2 * fse3t_n(ji,jj,mikt(ji,jj)) 
     165            END DO 
     166         END DO   
     167         CALL iom_put( "sst2" , z2d(:,:)      )   ! sea surface content of squared temperature 
    154168         z3d(:,:,:) = tsn(:,:,:,jp_sal) * fse3t_n(:,:,:)             
    155169         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 
     170         DO jj = 1, jpj 
     171            DO ji = 1, jpi 
     172               z2d(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_sal) * fse3t_n(ji,jj,mikt(ji,jj)) 
     173            END DO 
     174         END DO   
     175         CALL iom_put( "sss"  , z2d(:,:)                 )   ! sea surface salinity content 
     176         DO jj = 1, jpj 
     177            DO ji = 1, jpi 
     178               z2d(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_sal)**2 * fse3t_n(ji,jj,mikt(ji,jj)) 
     179            END DO 
     180         END DO   
     181         CALL iom_put( "sss2" , z2d(:,:)                 )   ! sea surface content of squared salinity 
    159182      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 
     183         CALL iom_put( "toce" , tsn(:,:,:,jp_tem)        )   ! temperature 
     184         IF ( iom_use("sst") ) THEN 
     185            DO jj = 1, jpj 
     186               DO ji = 1, jpi 
     187                  z2d(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_tem) 
     188               END DO 
     189            END DO 
     190            CALL iom_put( "sst"  , z2d(:,:)            ) ! sea surface temperature 
     191         ENDIF 
     192         IF ( iom_use("sst2") )   CALL iom_put( "sst2" , z2d(:,:) * z2d(:,:) ) ! square of sea surface temperature 
    163193         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 
     194         IF ( iom_use("sss") ) THEN 
     195            DO jj = 1, jpj 
     196               DO ji = 1, jpi 
     197                  z2d(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_sal) 
     198               END DO 
     199            END DO 
     200            CALL iom_put( "sss"  , z2d(:,:)            ) ! sea surface salinity 
     201         ENDIF 
     202         CALL iom_put( "sss2" , z2d(:,:) * z2d(:,:) ) ! square of sea surface salinity 
    166203      END IF 
    167204      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 
     205         CALL iom_put( "uoce" , umask(:,:,:) * un(:,:,:) * fse3u_n(:,:,:) )    ! i-transport 
     206         CALL iom_put( "voce" , vmask(:,:,:) * vn(:,:,:) * fse3v_n(:,:,:) )    ! j-transport 
    170207      ELSE 
    171          CALL iom_put( "uoce" , un                         )    ! i-current 
    172          CALL iom_put( "voce" , vn                         )    ! j-current 
    173       END IF 
     208         CALL iom_put( "uoce" , umask(:,:,:) * un(:,:,:)                  )    ! i-current 
     209         CALL iom_put( "voce" , vmask(:,:,:) * vn(:,:,:)                  )    ! j-current 
     210         IF ( iom_use("ssu") ) THEN 
     211            DO jj = 1, jpj 
     212               DO ji = 1, jpi 
     213                  z2d(ji,jj) = un(ji,jj,miku(ji,jj)) 
     214               END DO 
     215            END DO 
     216            CALL iom_put( "ssu"   , z2d                                    )    ! i-current 
     217         ENDIF 
     218         IF ( iom_use("ssv") ) THEN 
     219            DO jj = 1, jpj 
     220               DO ji = 1, jpi 
     221                  z2d(ji,jj) = vn(ji,jj,mikv(ji,jj)) 
     222               END DO 
     223            END DO 
     224            CALL iom_put( "ssv"   , z2d                                    )    ! j-current 
     225         ENDIF 
     226      ENDIF 
    174227      CALL iom_put(    "avt"  , avt                        )    ! T vert. eddy diff. coef. 
    175228      CALL iom_put(    "avm"  , avmu                       )    ! T vert. eddy visc. coef. 
     
    178231      ENDIF 
    179232 
    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  
     233      IF ( iom_use("sstgrad2") .OR. iom_use("sstgrad2") ) THEN 
     234         DO jj = 2, jpjm1                                    ! sst gradient 
     235            DO ji = fs_2, fs_jpim1   ! vector opt. 
     236               zztmp      = tsn(ji,jj,1,jp_tem) 
     237               zztmpx     = ( tsn(ji+1,jj  ,1,jp_tem) - zztmp ) / e1u(ji,jj) + ( zztmp - tsn(ji-1,jj  ,1,jp_tem) ) / e1u(ji-1,jj  ) 
     238               zztmpy     = ( tsn(ji  ,jj+1,1,jp_tem) - zztmp ) / e2v(ji,jj) + ( zztmp - tsn(ji  ,jj-1,1,jp_tem) ) / e2v(ji  ,jj-1) 
     239               z2d(ji,jj) = 0.25 * ( zztmpx * zztmpx + zztmpy * zztmpy )   & 
     240                  &              * umask(ji,jj,1) * umask(ji-1,jj,1) * vmask(ji,jj,1) * umask(ji,jj-1,1) 
     241            END DO 
     242         END DO 
     243         CALL lbc_lnk( z2d, 'T', 1. ) 
     244         CALL iom_put( "sstgrad2",  z2d               )    ! square of module of sst gradient 
     245         !CDIR NOVERRCHK< 
     246         z2d(:,:) = SQRT( z2d(:,:) ) 
     247         CALL iom_put( "sstgrad" ,  z2d               )    ! module of sst gradient 
     248      ENDIF 
     249          
     250      ! clem: heat and salt content 
     251      IF( iom_use("heatc") ) THEN 
     252         z2d(:,:)  = 0._wp  
     253         DO jk = 1, jpkm1 
     254            DO jj = 2, jpjm1 
     255               DO ji = fs_2, fs_jpim1   ! vector opt. 
     256                  z2d(ji,jj) = z2d(ji,jj) + fse3t(ji,jj,jk) * tsn(ji,jj,jk,jp_tem) * tmask(ji,jj,jk) 
     257               END DO 
     258            END DO 
     259         END DO 
     260         CALL lbc_lnk( z2d, 'T', 1. ) 
     261         CALL iom_put( "heatc", (rau0 * rcp) * z2d )    ! vertically integrated heat content (J/m2) 
     262      ENDIF 
     263 
     264<<<<<<< .working 
    195265      ! clem: heat and salt content 
    196266      z2d(:,:)  = 0._wp  
     
    211281 
    212282      IF( lk_diaar5 ) THEN 
     283======= 
     284      IF( iom_use("saltc") ) THEN 
     285         z2d(:,:)  = 0._wp  
     286         DO jk = 1, jpkm1 
     287            DO jj = 2, jpjm1 
     288               DO ji = fs_2, fs_jpim1   ! vector opt. 
     289                  z2d(ji,jj) = z2d(ji,jj) + fse3t(ji,jj,jk) * tsn(ji,jj,jk,jp_sal) * tmask(ji,jj,jk) 
     290               END DO 
     291            END DO 
     292         END DO 
     293         CALL lbc_lnk( z2d, 'T', 1. ) 
     294         CALL iom_put( "saltc", rau0 * z2d )   ! vertically integrated salt content (PSU*kg/m2) 
     295      ENDIF 
     296      ! 
     297      IF ( iom_use("eken") ) THEN 
     298         rke(:,:,jk) = 0._wp                               !      kinetic energy  
     299         DO jk = 1, jpkm1 
     300            DO jj = 2, jpjm1 
     301               DO ji = fs_2, fs_jpim1   ! vector opt. 
     302                  zztmp   = 1._wp / ( e1e2t(ji,jj) * fse3t(ji,jj,jk) ) 
     303                  zztmpx  = 0.5 * (  un(ji-1,jj,jk) * un(ji-1,jj,jk) * e2u(ji-1,jj) * fse3u(ji-1,jj,jk)    & 
     304                     &             + un(ji  ,jj,jk) * un(ji  ,jj,jk) * e2u(ji  ,jj) * fse3u(ji  ,jj,jk) )  & 
     305                     &          *  zztmp  
     306                  ! 
     307                  zztmpy  = 0.5 * (  vn(ji,jj-1,jk) * vn(ji,jj-1,jk) * e1v(ji,jj-1) * fse3v(ji,jj-1,jk)    & 
     308                     &             + vn(ji,jj  ,jk) * vn(ji,jj  ,jk) * e1v(ji,jj  ) * fse3v(ji,jj  ,jk) )  & 
     309                     &          *  zztmp  
     310                  ! 
     311                  rke(ji,jj,jk) = 0.5_wp * ( zztmpx + zztmpy ) 
     312                  ! 
     313               ENDDO 
     314            ENDDO 
     315         ENDDO 
     316         CALL lbc_lnk( rke, 'T', 1. ) 
     317         CALL iom_put( "eken", rke )            
     318      ENDIF 
     319          
     320      IF( iom_use("u_masstr") .OR. iom_use("u_heattr") .OR. iom_use("u_salttr") ) THEN 
     321>>>>>>> .merge-right.r5035 
    213322         z3d(:,:,jpk) = 0.e0 
    214323         DO jk = 1, jpkm1 
     
    216325         END DO 
    217326         CALL iom_put( "u_masstr", z3d )                  ! mass transport in i-direction 
     327<<<<<<< .working 
    218328 
    219329         zztmp = 0.5 * rcp 
     330======= 
     331      ENDIF 
     332       
     333      IF( iom_use("u_heattr") ) THEN 
     334>>>>>>> .merge-right.r5035 
    220335         z2d(:,:) = 0.e0  
    221336         z2ds(:,:) = 0.e0  
     
    223338            DO jj = 2, jpjm1 
    224339               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) ) 
     340                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_tem) + tsn(ji+1,jj,jk,jp_tem) ) 
    226341                  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) ) 
    227342               END DO 
     
    229344         END DO 
    230345         CALL lbc_lnk( z2d, 'U', -1. ) 
     346<<<<<<< .working 
    231347         CALL lbc_lnk( z2ds, 'U', -1. ) 
    232348         CALL iom_put( "u_heattr", z2d )                  ! heat transport in i-direction 
     349======= 
     350         CALL iom_put( "u_heattr", (0.5 * rcp) * z2d )    ! heat transport in i-direction 
     351      ENDIF 
     352 
     353      IF( iom_use("u_salttr") ) THEN 
     354         z2d(:,:) = 0.e0  
     355>>>>>>> .merge-right.r5035 
    233356         CALL iom_put( "u_salttr", z2ds )                 ! salt transport in i-direction 
    234357 
     358         z3d(:,:,jpk) = 0.e0 
     359         DO jk = 1, jpkm1 
     360<<<<<<< .working 
     361            z3d(:,:,jk) = rau0 * vn(:,:,jk) * e1v(:,:) * fse3v(:,:,jk) * vmask(:,:,jk) 
     362======= 
     363            DO jj = 2, jpjm1 
     364               DO ji = fs_2, fs_jpim1   ! vector opt. 
     365                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_sal) + tsn(ji+1,jj,jk,jp_sal) ) 
     366               END DO 
     367            END DO 
     368>>>>>>> .merge-right.r5035 
     369         END DO 
     370         CALL lbc_lnk( z2d, 'U', -1. ) 
     371         CALL iom_put( "u_salttr", 0.5 * z2d )            ! heat transport in i-direction 
     372      ENDIF 
     373 
     374       
     375      IF( iom_use("v_masstr") .OR. iom_use("v_heattr") .OR. iom_use("v_salttr") ) THEN 
    235376         z3d(:,:,jpk) = 0.e0 
    236377         DO jk = 1, jpkm1 
     
    238379         END DO 
    239380         CALL iom_put( "v_masstr", z3d )                  ! mass transport in j-direction 
    240  
     381<<<<<<< .working 
     382 
     383======= 
     384      ENDIF 
     385       
     386      IF( iom_use("v_heattr") ) THEN 
     387>>>>>>> .merge-right.r5035 
    241388         z2d(:,:) = 0.e0  
    242389         z2ds(:,:) = 0.e0  
     
    244391            DO jj = 2, jpjm1 
    245392               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) ) 
     393                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_tem) + tsn(ji,jj+1,jk,jp_tem) ) 
    247394                  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) ) 
    248395               END DO 
     
    250397         END DO 
    251398         CALL lbc_lnk( z2d, 'V', -1. ) 
     399<<<<<<< .working 
    252400         CALL lbc_lnk( z2ds, 'V', -1. ) 
    253401         CALL iom_put( "v_heattr", z2d )                  !  heat transport in j-direction 
    254402         CALL iom_put( "v_salttr", z2ds )                 !  salt transport in j-direction 
     403======= 
     404         CALL iom_put( "v_heattr", (0.5 * rcp) * z2d )    !  heat transport in j-direction 
     405>>>>>>> .merge-right.r5035 
     406      ENDIF 
     407 
     408      IF( iom_use("v_salttr") ) THEN 
     409         z2d(:,:) = 0.e0  
     410         DO jk = 1, jpkm1 
     411            DO jj = 2, jpjm1 
     412               DO ji = fs_2, fs_jpim1   ! vector opt. 
     413                  z2d(ji,jj) = z2d(ji,jj) + z3d(ji,jj,jk) * ( tsn(ji,jj,jk,jp_sal) + tsn(ji,jj+1,jk,jp_sal) ) 
     414               END DO 
     415            END DO 
     416         END DO 
     417         CALL lbc_lnk( z2d, 'V', -1. ) 
     418         CALL iom_put( "v_salttr", 0.5 * z2d )            !  heat transport in j-direction 
    255419      ENDIF 
    256420      ! 
     
    518682         ENDIF 
    519683 
    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 
     684         IF( .NOT. lk_cpl ) THEN 
     685            CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
     686               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     687            CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp 
     688               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     689            CALL histdef( nid_T, "sosafldp", "Surface salt flux: damping"         , "Kg/m2/s",   &  ! erp * sn 
     690               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     691         ENDIF 
     692 
     693         IF( lk_cpl .AND. nn_ice <= 1 ) THEN 
     694            CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
     695               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     696            CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp 
     697               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     698            CALL histdef( nid_T, "sosafldp", "Surface salt flux: Damping"         , "Kg/m2/s",   &  ! erp * sn 
     699               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     700         ENDIF 
     701          
    539702         clmx ="l_max(only(x))"    ! max index on a period 
    540703         CALL histdef( nid_T, "sobowlin", "Bowl Index"                         , "W-point",   &  ! bowl INDEX  
     
    551714#endif 
    552715 
    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  
     716         IF( lk_cpl .AND. nn_ice == 2 ) THEN 
     717            CALL histdef( nid_T,"soicetem" , "Ice Surface Temperature"            , "K"      ,   &  ! tn_ice 
     718               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     719            CALL histdef( nid_T,"soicealb" , "Ice Albedo"                         , "[0,1]"  ,   &  ! alb_ice 
     720               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     721         ENDIF 
    564722 
    565723         CALL histend( nid_T, snc4chunks=snc4set ) 
     
    652810      ENDIF 
    653811 
    654       ! Write fields on T grid 
    655812      IF( lk_vvl ) THEN 
    656813         CALL histwrite( nid_T, "votemper", it, tsn(:,:,:,jp_tem) * fse3t_n(:,:,:) , ndim_T , ndex_T  )   ! heat content 
     
    663820         CALL histwrite( nid_T, "sosstsst", it, tsn(:,:,1,jp_tem) , ndim_hT, ndex_hT )   ! sea surface temperature 
    664821         CALL histwrite( nid_T, "sosaline", it, tsn(:,:,1,jp_sal) , ndim_hT, ndex_hT )   ! sea surface salinity 
    665  
    666822      ENDIF 
    667823      IF( lk_vvl ) THEN 
     
    713869      ENDIF 
    714870 
    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 
     871      IF( .NOT. lk_cpl ) THEN 
     872         CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
     873         CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
    724874         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 )   ! ??? 
     875         CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
     876      ENDIF 
     877      IF( lk_cpl .AND. nn_ice <= 1 ) THEN 
     878         CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
     879         CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
     880         IF( ln_ssr ) zw2d(:,:) = erp(:,:) * tsn(:,:,1,jp_sal) * tmask(:,:,1) 
     881         CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
     882      ENDIF 
     883!      zw2d(:,:) = FLOAT( nmln(:,:) ) * tmask(:,:,1) 
     884!      CALL histwrite( nid_T, "sobowlin", it, zw2d          , ndim_hT, ndex_hT )   ! ??? 
    729885 
    730886#if defined key_diahth 
     
    735891#endif 
    736892 
    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 
     893      IF( lk_cpl .AND. nn_ice == 2 ) THEN 
     894         CALL histwrite( nid_T, "soicetem", it, tn_ice(:,:,1) , ndim_hT, ndex_hT )   ! surf. ice temperature 
     895         CALL histwrite( nid_T, "soicealb", it, alb_ice(:,:,1), ndim_hT, ndex_hT )   ! ice albedo 
     896      ENDIF 
     897 
    749898      CALL histwrite( nid_U, "vozocrtx", it, un            , ndim_U , ndex_U )    ! i-current 
    750899      IF( ln_traldf_gdia ) THEN 
     
    768917      CALL histwrite( nid_U, "sozotaux", it, utau          , ndim_hU, ndex_hU )   ! i-wind stress 
    769918 
    770          ! Write fields on V grid 
    771919      CALL histwrite( nid_V, "vomecrty", it, vn            , ndim_V , ndex_V  )   ! j-current 
    772920      IF( ln_traldf_gdia ) THEN 
     
    783931      CALL histwrite( nid_V, "sometauy", it, vtau          , ndim_hV, ndex_hV )   ! j-wind stress 
    784932 
    785          ! Write fields on W grid 
    786933      CALL histwrite( nid_W, "vovecrtz", it, wn             , ndim_T, ndex_T )    ! vert. current 
    787934      IF( ln_traldf_gdia ) THEN 
Note: See TracChangeset for help on using the changeset viewer.