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 5609 for trunk/NEMOGCM/TOOLS/SIREN/src/iom_rstdimg.f90 – NEMO

Ignore:
Timestamp:
2015-07-17T17:42:15+02:00 (9 years ago)
Author:
jpaul
Message:

commit changes/bugfix/... for SIREN; see ticket #1580

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/TOOLS/SIREN/src/iom_rstdimg.f90

    r5037 r5609  
    10581058      INTEGER(i4), DIMENSION(ip_maxdim)            :: il_start 
    10591059      INTEGER(i4), DIMENSION(ip_maxdim)            :: il_count 
     1060 
    10601061      REAL(dp),    DIMENSION(:,:,:,:), ALLOCATABLE :: dl_value 
    10611062 
     
    12041205      ENDIF 
    12051206 
     1207      ! force to change _FillValue to avoid mistake  
     1208      ! with dummy zero _FillValue 
     1209      IF( td_var%d_fill == 0._dp )THEN 
     1210         CALL var_chg_FillValue(td_var) 
     1211      ENDIF 
     1212 
     1213      ! use scale factor and offset 
     1214      WHERE( td_var%d_value(:,:,:,:) /= td_var%d_fill ) 
     1215         td_var%d_value(:,:,:,:) = & 
     1216         &  td_var%d_value(:,:,:,:)*td_var%d_scf + td_var%d_ofs 
     1217      END WHERE 
     1218 
    12061219   END SUBROUTINE iom_rstdimg__read_var_value 
    12071220   !------------------------------------------------------------------- 
     
    16601673         ! change FillValue to 0. 
    16611674         CALL var_chg_FillValue(td_file%t_var(ji),0._dp) 
     1675 
     1676         ! use scale factor and offset 
     1677         WHERE( td_file%t_var(ji)%d_value(:,:,:,:) /= & 
     1678         &      td_file%t_var(ji)%d_fill ) 
     1679            td_file%t_var(ji)%d_value(:,:,:,:) = & 
     1680            &  (td_file%t_var(ji)%d_value(:,:,:,:)-td_file%t_var(ji)%d_ofs) /& 
     1681            &    td_file%t_var(ji)%d_scf 
     1682         END WHERE 
    16621683 
    16631684         cl_name(ji)  = TRIM(td_file%t_var(ji)%c_name) 
Note: See TracChangeset for help on using the changeset viewer.