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 1857 for branches/DEV_r1837_mass_heat_salt_fluxes/NEMO/LIM_SRC_2/limwri_2.F90 – NEMO

Ignore:
Timestamp:
2010-05-03T13:59:46+02:00 (14 years ago)
Author:
gm
Message:

ticket:#665 Reverting previous commit and going back to revision 1850

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/DEV_r1837_mass_heat_salt_fluxes/NEMO/LIM_SRC_2/limwri_2.F90

    r1855 r1857  
    1212   !!   'key_lim2'                                    LIM 2.0 sea-ice model 
    1313   !!---------------------------------------------------------------------- 
    14    !!   lim_wri_2       : write of the diagnostics variables in ouput file  
    15    !!   lim_wri_init_2  : initialization and namelist read 
    16    !!   lim_wri_state_2 : write for initial state (output.init.nc if ninist=1) or/and in the abort file 
     14   !!---------------------------------------------------------------------- 
     15   !!   lim_wri_2      : write of the diagnostics variables in ouput file  
     16   !!   lim_wri_init_2 : initialization and namelist read 
     17   !!   lim_wri_state_2 : write for initial state or/and abandon: 
     18   !!                     > output.init.nc (if ninist = 1 in namelist) 
     19   !!                     > output.abort.nc 
    1720   !!---------------------------------------------------------------------- 
    1821   USE phycst 
     
    3942   INTEGER, PARAMETER                       ::   jpnoumax = 40   ! maximum number of variable for ice output 
    4043   INTEGER                                  ::   noumef          ! number of fields 
    41    REAL(wp)           , DIMENSION(jpnoumax) ::   cmulti         ! multiplicative constant 
    42    REAL(wp)           , DIMENSION(jpnoumax) ::   cadd            ! additive constant 
     44   REAL(wp)           , DIMENSION(jpnoumax) ::   cmulti ,     &  ! multiplicative constant 
     45      &                                          cadd            ! additive constant 
    4346   CHARACTER(len = 35), DIMENSION(jpnoumax) ::   titn            ! title of the field 
    4447   CHARACTER(len = 8 ), DIMENSION(jpnoumax) ::   nam             ! name of the field 
     
    4952   INTEGER , DIMENSION( jpij ) ::   ndex51              ! ???? 
    5053 
    51    REAL(wp) ::   epsi16 = 1.e-16   ! constant values 
    52    REAL(wp) ::   rzero  = 0.e0     ! 
    53    REAL(wp) ::   rone   = 1.e0     ! 
     54   REAL(wp)  ::            &  ! constant values 
     55      epsi16 = 1.e-16   ,  & 
     56      zzero  = 0.e0     ,  & 
     57      zone   = 1.e0 
    5458 
    5559   !! * Substitutions 
    5660#   include "vectopt_loop_substitute.h90" 
    5761   !!---------------------------------------------------------------------- 
    58    !! NEMO/LIM 3.3,  UCL-LOCEAN-IPSL (2010)  
     62   !!  LIM 2.0, UCL-LOCEAN-IPSL (2006) 
    5963   !! $Id$ 
    6064   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     
    7781      !! 
    7882      !! ** Method  :   computes the average of some variables and write 
    79       !!              it in the NetCDF ouput files 
    80       !! CAUTION: the sea-ice time-step must be an integer fraction of a day 
     83      !!      it in the NetCDF ouput files 
     84      !!      CAUTION: the sea-ice time-step must be an integer fraction 
     85      !!      of a day 
    8186      !!------------------------------------------------------------------- 
    8287      INTEGER, INTENT(in) ::   kt     ! number of iteration 
    8388      !! 
    84       INTEGER  ::   ji, jj, jf   ! dummy loop indices 
     89      INTEGER  ::   ji, jj, jf                      ! dummy loop indices 
    8590      CHARACTER(len = 40)  ::   clhstnam, clop 
    86       REAL(wp) ::   zsto, zjulian, zout          ! temporary scalars 
    87       REAL(wp) ::   zindh, zinda, zindb, ztmu 
     91      REAL(wp) ::   zsto, zjulian, zout,   &  ! temporary scalars 
     92         &          zindh, zinda, zindb, ztmu 
    8893      REAL(wp), DIMENSION(1)                ::   zdept 
    8994      REAL(wp), DIMENSION(jpi,jpj)          ::   zfield 
     
    127132      DO jj = 2 , jpjm1 
    128133         DO ji = 1 , jpim1   ! NO vector opt. 
    129             zindh  = MAX( rzero , SIGN( rone , hicif(ji,jj) * (1.0 - frld(ji,jj) ) - 0.10 ) ) 
    130             zinda  = MAX( rzero , SIGN( rone , ( 1.0 - frld(ji,jj) ) - 0.10 ) ) 
     134            zindh  = MAX( zzero , SIGN( zone , hicif(ji,jj) * (1.0 - frld(ji,jj) ) - 0.10 ) ) 
     135            zinda  = MAX( zzero , SIGN( zone , ( 1.0 - frld(ji,jj) ) - 0.10 ) ) 
    131136            zindb  = zindh * zinda 
    132             ztmu   = MAX( 0.5 * rone , ( tmu(ji,jj) + tmu(ji+1,jj) + tmu(ji,jj+1) + tmu(ji+1,jj+1) ) )  
     137            ztmu   = MAX( 0.5 * zone , ( tmu(ji,jj) + tmu(ji+1,jj) + tmu(ji,jj+1) + tmu(ji+1,jj+1) ) )  
    133138            zcmo(ji,jj,1)  = hsnif (ji,jj) 
    134139            zcmo(ji,jj,2)  = hicif (ji,jj) 
     
    138143            zcmo(ji,jj,6)  = fbif  (ji,jj) 
    139144            zcmo(ji,jj,7)  = zindb * (  u_ice(ji,jj  ) * tmu(ji,jj  ) + u_ice(ji+1,jj  ) * tmu(ji+1,jj  )   & 
    140                &                      + u_ice(ji,jj+1) * tmu(ji,jj+1) + u_ice(ji+1,jj+1) * tmu(ji+1,jj+1) ) & 
    141                &                  / ztmu  
     145                                      + u_ice(ji,jj+1) * tmu(ji,jj+1) + u_ice(ji+1,jj+1) * tmu(ji+1,jj+1) ) & 
     146                                  / ztmu  
    142147 
    143148            zcmo(ji,jj,8)  = zindb * (  v_ice(ji,jj  ) * tmu(ji,jj  ) + v_ice(ji+1,jj  ) * tmu(ji+1,jj  )   & 
    144                &                      + v_ice(ji,jj+1) * tmu(ji,jj+1) + v_ice(ji+1,jj+1) * tmu(ji+1,jj+1) ) & 
    145                &                  / ztmu 
     149                                      + v_ice(ji,jj+1) * tmu(ji,jj+1) + v_ice(ji+1,jj+1) * tmu(ji+1,jj+1) ) & 
     150                                  / ztmu 
    146151            zcmo(ji,jj,9)  = sst_m(ji,jj) 
    147152            zcmo(ji,jj,10) = sss_m(ji,jj) 
     
    195200      !! ** input   :   Namelist namicewri 
    196201      !!------------------------------------------------------------------- 
    197       INTEGER ::   jf      ! dummy loop indices 
     202      INTEGER ::   nf      ! ??? 
    198203      TYPE FIELD  
    199204         CHARACTER(len = 35) :: ztitle  
     
    204209         REAL                :: zcadd         
    205210      END TYPE FIELD 
    206       TYPE(FIELD) ::   field_1 , field_2 , field_3 , field_4 , field_5 , field_6   
    207       TYPE(FIELD) ::   field_7 , field_8 , field_9 , field_10, field_11, field_12 
    208       TYPE(FIELD) ::   field_13, field_14, field_15, field_16, field_17, field_18, field_19 
     211      TYPE(FIELD) ::  & 
     212         field_1 , field_2 , field_3 , field_4 , field_5 , field_6 ,   & 
     213         field_7 , field_8 , field_9 , field_10, field_11, field_12,   & 
     214         field_13, field_14, field_15, field_16, field_17, field_18,   & 
     215         field_19 
    209216      TYPE(FIELD) , DIMENSION(jpnoumax) :: zfield 
    210       !! 
    211       NAMELIST/namiceout/ noumef,                                          & 
    212          field_1 , field_2 , field_3 , field_4 , field_5 , field_6 ,       & 
    213          field_7 , field_8 , field_9 , field_10, field_11, field_12,       & 
    214          field_13, field_14, field_15, field_16, field_17, field_18, field_19 
     217 
     218      NAMELIST/namiceout/ noumef, & 
     219         field_1 , field_2 , field_3 , field_4 , field_5 , field_6 ,   & 
     220         field_7 , field_8 , field_9 , field_10, field_11, field_12,   & 
     221         field_13, field_14, field_15, field_16, field_17, field_18,   & 
     222         field_19 
    215223      !!------------------------------------------------------------------- 
    216224 
     
    238246      zfield(19) = field_19 
    239247       
    240       DO jf = 1, noumef 
    241          titn  (jf) = zfield(jf)%ztitle 
    242          nam   (jf) = zfield(jf)%zname 
    243          uni   (jf) = zfield(jf)%zunit 
    244          nc    (jf) = zfield(jf)%znc 
    245          cmulti(jf) = zfield(jf)%zcmulti 
    246          cadd  (jf) = zfield(jf)%zcadd 
     248      DO nf = 1, noumef 
     249         titn  (nf) = zfield(nf)%ztitle 
     250         nam   (nf) = zfield(nf)%zname 
     251         uni   (nf) = zfield(nf)%zunit 
     252         nc    (nf) = zfield(nf)%znc 
     253         cmulti(nf) = zfield(nf)%zcmulti 
     254         cadd  (nf) = zfield(nf)%zcadd 
    247255      END DO 
    248256 
     
    254262         WRITE(numout,*) '           title                            name     unit      Saving (1/0) ',   & 
    255263            &            '    multiplicative constant       additive constant ' 
    256          DO jf = 1 , noumef          
    257             WRITE(numout,*) '   ', titn(jf), '   ', nam(jf),'      ', uni(jf),'  ', nc(jf),'        ', cmulti(jf),   & 
    258                &       '        ', cadd(jf) 
     264         DO nf = 1 , noumef          
     265            WRITE(numout,*) '   ', titn(nf), '   ', nam(nf),'      ', uni(nf),'  ', nc(nf),'        ', cmulti(nf),   & 
     266               &       '        ', cadd(nf) 
    259267         END DO 
    260268      ENDIF 
     
    273281      !!        Used to find errors in the initial state or save the last 
    274282      !!      ocean state in case of abnormal end of a simulation 
     283      !! 
     284      !! History : 
     285      !!   2.0  !  2009-06  (B. Lemaire) 
    275286      !!---------------------------------------------------------------------- 
    276287      INTEGER, INTENT( in ) ::   kt               ! ocean time-step index) 
Note: See TracChangeset for help on using the changeset viewer.