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 2528 for trunk/NEMOGCM/NEMO/OPA_SRC/DIA/diawri_dimg.h90 – NEMO

Ignore:
Timestamp:
2010-12-27T18:33:53+01:00 (13 years ago)
Author:
rblod
Message:

Update NEMOGCM from branch nemo_v3_3_beta

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/DIA/diawri_dimg.h90

    • Property svn:eol-style deleted
    r1685 r2528  
    22  !!                        ***  diawri_dimg.h90  *** 
    33  !!---------------------------------------------------------------------- 
    4   !!   OPA 9.0 , LOCEAN-IPSL (2005)  
    5   !! $Id$ 
    6   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     4  !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     5  !! $Id $ 
     6  !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    77  !!---------------------------------------------------------------------- 
    88 
    9   SUBROUTINE dia_wri (kt) 
     9  SUBROUTINE dia_wri( kt ) 
    1010    !!---------------------------------------------------------------------- 
    1111    !!           *** routine dia_wri *** 
     
    4242    !!  level 2:  vtau(:,:) * vmask(:,:,1) meridional stress in N. m-2 
    4343    !!  level 3:  qsr + qns                total heat flux (W/m2) 
    44     !!  level 4:  emp (:,:)               E-P flux (mm/day) 
     44    !!  level 4:  ( emp (:,:)-rnf(:,:) )   E-P flux (mm/day) 
    4545    !!  level 5:  tb  (:,:,1)-sst          model SST -forcing sst (degree C) ! deprecated 
    4646    !!  level 6:  bsfb(:,:)         streamfunction (m**3/s) 
     
    5454    !!  level 14: qct(:,:)                 equivalent flux due to treshold SST 
    5555    !!  level 15: fbt(:,:)                 feedback term . 
    56     !!  level 16: emps(:,:)                concentration/dilution water flux 
     56    !!  level 16: ( emps(:,:) - rnf(:,:) ) concentration/dilution water flux 
    5757    !!  level 17: fsalt(:,:)               Ice=>ocean net freshwater 
    5858    !!  level 18: gps(:,:)                 the surface pressure (m). 
     
    6060    !!  level 20: spgv(:,:)                the surface pressure gradient in Y direction. 
    6161    !!  
    62     !! History  
    63     !!      original  : 91-03 () 
    64     !!      additions : 91-11 (G. Madec) 
    65     !!      additions : 92-06 (M. Imbard) correction restart file 
    66     !!      additions : 92-07 (M. Imbard) split into diawri and rstwri 
    67     !!      additions : 93-03 (M. Imbard) suppress writibm 
    68     !!      additions : 94-12 (M. Imbard) acces direct files 
    69     !!      additions : 97-2002 ( Clipper Group ) dimg files 
    70     !!                  dec 2003 ( J.M. Molines) f90, mpp output for OPA9.0 
    71     !!   9.0  !  05-05  (S. Theetten) add emps fsalt move gps spgu spgv 2 lines below 
    72     !!   9.0  !  05-11  (V. Garnier) Surface pressure gradient organization 
     62    !! History:  OPA  ! 1997-02 ( Clipper Group ) dimg files 
     63    !!            -   ! 2003-12 ( J.M. Molines) f90, mpp output for OPA9.0 
     64    !!   NEMO    1.0  ! 2005-05  (S. Theetten) add emps fsalt move gps spgu spgv 2 lines below 
     65    !!            -   ! 2005-11  (V. Garnier) Surface pressure gradient organization 
    7366    !!---------------------------------------------------------------------- 
    74     !! * modules used 
    7567    USE lib_mpp 
    76  
    77     !! * Arguments 
     68    !! 
    7869    INTEGER ,INTENT(in) :: kt 
    79  
    80     !! * local declarations 
     70    !! 
    8171    INTEGER :: inbsel, jk 
    82 !!  INTEGER :: iwrite 
    8372    INTEGER :: iyear,imon,iday 
    8473    INTEGER, SAVE :: nmoyct  
     
    10190    CHARACTER(LEN=80) :: clmode 
    10291    CHARACTER(LEN= 4) :: clver 
     92    !!---------------------------------------------------------------------- 
    10393    ! 
    10494    !  Initialization 
    10595    !  --------------- 
    10696    ! 
    107 #ifdef key_diaspr 
    108     inbsel = 20 
    109 #else 
    11097    inbsel = 17 
    111 #endif 
    112 #if defined key_flx_core 
    113     inbsel = 23 
    114 #endif 
    115  
    116     IF( inbsel >  jpk) THEN 
    117        IF( lwp) WRITE(numout,*)  & 
    118             ' STOP inbsel =',inbsel,' is larger than jpk=',jpk 
     98 
     99    IF( inbsel >  jpk ) THEN 
     100       IF(lwp) WRITE(numout,*)  ' STOP inbsel =',inbsel,' is larger than jpk=',jpk 
    119101       STOP 
    120102    ENDIF 
    121  
    122103 
    123104    iyear = ndastp/10000 
     
    167148       fsel(:,:,2 ) = fsel(:,:,2 ) + vtau(:,:) * vmask(:,:,1) 
    168149       fsel(:,:,3 ) = fsel(:,:,3 ) + qsr (:,:) + qns  (:,:)  
    169        fsel(:,:,4 ) = fsel(:,:,4 ) + emp (:,:) 
     150       fsel(:,:,4 ) = fsel(:,:,4 ) + ( emp(:,:)-rnf(:,:) )  
    170151       !        fsel(:,:,5 ) = fsel(:,:,5 ) + tb  (:,:,1)  !RB not used 
    171152       fsel(:,:,6 ) = fsel(:,:,6 ) + sshn(:,:)  
     
    179160       !        fsel(:,:,14) = fsel(:,:,14) + qct(:,:) 
    180161       !        fsel(:,:,15) = fsel(:,:,15) + fbt(:,:) 
    181        fsel(:,:,16) = fsel(:,:,16) + emps(:,:) 
    182 #ifdef key_diaspr    
    183        fsel(:,:,18) = fsel(:,:,18) + gps(:,:)/g  
    184 #endif 
     162       fsel(:,:,16) = fsel(:,:,16) + ( emps(:,:)-rnf(:,:) )  
    185163       ! 
    186164       ! Output of dynamics and tracer fields and selected fields 
     
    210188          ! computed from the averaged gradients. 
    211189          ! 
    212 #ifdef key_diaspr 
    213           fsel(:,:,18)= gps(:,:)/g 
    214           fsel(:,:,19)= spgu(:,:) 
    215           fsel(:,:,20)= spgv(:,:) 
    216 #endif 
    217190          ! mask mean field with tmask except utau vtau (1,2) 
    218191          DO jk=3,inbsel 
     
    242215          fsel(:,:,2 ) = vtau(:,:) * vmask(:,:,1) 
    243216          fsel(:,:,3 ) = (qsr (:,:) + qns (:,:)) * tmask(:,:,1) 
    244           fsel(:,:,4 ) = emp (:,:) * tmask(:,:,1) 
     217          fsel(:,:,4 ) = ( emp(:,:)-rnf(:,:) ) * tmask(:,:,1)  
    245218          !         fsel(:,:,5 ) = (tb  (:,:,1) - sf_sst(1)%fnow(:,:) ) *tmask(:,:,1) !RB not used 
    246219 
     
    255228          !         fsel(:,:,14) =  qct(:,:) 
    256229          !         fsel(:,:,15) =  fbt(:,:) 
    257           fsel(:,:,16) =  emps(:,:) * tmask(:,:,1) 
    258 #ifdef key_diaspr            
    259           fsel(:,:,18) =      gps(:,:) /g 
    260           fsel(:,:,19) =      spgu(:,:) 
    261           fsel(:,:,20) =      spgv(:,:) 
    262 #endif 
     230          fsel(:,:,16) = ( emps(:,:)-rnf(:,:) ) * tmask(:,:,1)  
    263231          ! 
    264232          !         qct(:,:) = 0._wp 
     
    383351    ! 
    3843529000 FORMAT(a,"_",a,"_y",i4.4,"m",i2.2,"d",i2.2,".dimgproc") 
    385  
     353    ! 
    386354  END SUBROUTINE dia_wri 
Note: See TracChangeset for help on using the changeset viewer.