[cdftools] 101/228: JMM : add modification by Pierre MAthiot in cdfmkmask( use of i, j limits) and cdficediags ( add lim3 naming convention as option)

Alastair McKinstry mckinstry at moszumanska.debian.org
Fri Jun 12 08:21:35 UTC 2015


This is an automated email from the git hooks/post-receive script.

mckinstry pushed a commit to branch master
in repository cdftools.

commit 7c9bcda6ed654b689f5b2abd0629bbc23bf2580d
Author: molines <molines at 1055176f-818a-41d9-83e1-73fbe5b947c5>
Date:   Tue Aug 23 14:50:40 2011 +0000

    JMM : add modification by Pierre MAthiot in cdfmkmask( use of  i,j limits) and cdficediags ( add lim3 naming convention as option)
    
    
    git-svn-id: http://servforge.legi.grenoble-inp.fr/svn/CDFTOOLS/trunk@548 1055176f-818a-41d9-83e1-73fbe5b947c5
---
 cdficediags.f90 | 51 +++++++++++++++++++++++++++++++++++++++-----
 cdfio.f90       | 46 +++++++++++++++++++++++++++++++++++++++-
 cdfmkmask.f90   | 66 +++++++++++++++++++++++++++++++++++++++++++++++++++------
 modcdfnames.f90 |  3 +++
 4 files changed, 154 insertions(+), 12 deletions(-)

diff --git a/cdficediags.f90 b/cdficediags.f90
index a64bf18..c2651c3 100644
--- a/cdficediags.f90
+++ b/cdficediags.f90
@@ -11,6 +11,7 @@ PROGRAM cdficediag
   !! History : 2.1  : 01/2006  : J.M. Molines : Original code
   !!         : 2.1  : 07/2009  : R. Dussin    : Add Ncdf output
   !!           3.0  : 12/2010  : J.M. Molines : Doctor norm + Lic.
+  !! Modified: 3.0  : 08/2011  : P.   Mathiot : Add LIM3 option
   !!----------------------------------------------------------------------
   USE cdfio
   USE modcdfnames
@@ -48,12 +49,16 @@ PROGRAM cdficediag
   !
   CHARACTER(LEN=256)                         :: cf_ifil              ! input ice file
   CHARACTER(LEN=256)                         :: cf_out='icediags.nc' ! output file
+  CHARACTER(LEN=256)                         :: cldum                ! dummy string
+  !
+  LOGICAL                                    :: lchk  = .false.      ! missing file flag
+  LOGICAL                                    :: llim3 = .false.      ! LIM3 flag
   !!----------------------------------------------------------------------
   CALL ReadCdfNames()
 
   narg = iargc()
-  IF ( narg /= 1 ) THEN
-     PRINT *,' usage : cdficediag ICE-file'
+  IF ( narg == 0 ) THEN
+     PRINT *,' usage : cdficediag ICE-file [-lim3] '
      PRINT *,'      '
      PRINT *,'     PURPOSE :'
      PRINT *,'        Compute the ice volume, area and extent for each hemisphere.'
@@ -66,7 +71,10 @@ PROGRAM cdficediag
      PRINT *,'        ice concentration, but it will be deprecated soon.'
      PRINT *,'      '
      PRINT *,'     ARGUMENTS :'
-     PRINT *,'       ICE-file : netcdf icemod file' 
+     PRINT *,'       ICE-file : netcdf icemod file (LIM2 by default)' 
+     PRINT *,'      '
+     PRINT *,'     OPTION :'
+     PRINT *,'       [-lim3 ] : LIM3 variable name convention is used'
      PRINT *,'      '
      PRINT *,'     REQUIRED FILES :'
      PRINT *,'        ',TRIM(cn_fhgr),' and ',TRIM(cn_fmsk)
@@ -84,7 +92,22 @@ PROGRAM cdficediag
   ENDIF
 
   CALL getarg (1, cf_ifil)
-  IF ( chkfile(cf_ifil) ) STOP ! missing file
+
+  lchk = lchk .OR. chkfile(cn_fhgr) 
+  lchk = lchk .OR. chkfile(cn_fmsk) 
+  lchk = lchk .OR. chkfile(cf_ifil)
+
+  IF ( lchk ) STOP ! missing file
+
+  IF ( narg == 2 ) THEN
+     CALL getarg (2, cldum)
+     IF (TRIM(cldum) == '-lim3') THEN
+        llim3 = .true.
+     ELSE IF (TRIM(cldum) == '-lim2') THEN
+     ELSE
+        PRINT *,' For this sea-ice data format use a namelist '
+     END IF
+  END IF
 
   npiglo = getdim (cf_ifil,cn_x)
   npjglo = getdim (cf_ifil,cn_y)
@@ -173,8 +196,26 @@ PROGRAM cdficediag
      STOP
   END SELECT
 
+  ricethick(:,:)=0.
+  riceldfra(:,:)=0.
+
+  IF (llim3) THEN
+     cn_iicethic = cn_iicethic3
+     cn_ileadfra = cn_ileadfra3
+  END IF
+
+  ! Check variable
+  IF (chkvar(cf_ifil, cn_iicethic)) THEN
+     cn_iicethic='missing'
+     PRINT *,'' 
+     PRINT *,' WARNING, ICE THICKNESS IS SET TO 0. '
+     PRINT *,' '
+  END IF
+
+  IF (chkvar(cf_ifil, cn_ileadfra)) STOP
+  !
   DO jt = 1, npt
-     ricethick(:,:) = getvar(cf_ifil, cn_iicethic, 1, npiglo, npjglo, ktime=jt)
+     IF (TRIM(cn_iicethic) .NE. 'missing') ricethick(:,:) = getvar(cf_ifil, cn_iicethic, 1, npiglo, npjglo, ktime=jt)
      riceldfra(:,:) = getvar(cf_ifil, cn_ileadfra, 1, npiglo, npjglo, ktime=jt)
 
      ! North : ff > 0 
diff --git a/cdfio.f90 b/cdfio.f90
index 7be8095..0e5f6b1 100644
--- a/cdfio.f90
+++ b/cdfio.f90
@@ -6,6 +6,7 @@
   !! History : 2.1 : 2005  : J.M. Molines   : Original code
   !!               : 2009  : R. Dussin      : add putvar_0d function
   !!           3.0 : 12/2010 : J.M. Molines : Doctor + Licence     
+  !! Modified: 3.0 : 08/2011 : P.   Mathiot : Add chkvar function           
   !!----------------------------------------------------------------------
 
   !!----------------------------------------------------------------------
@@ -18,6 +19,7 @@
   !!   functions     : description
   !! .............................
   !!   chkfile       : check the existence of a file
+  !!   chkvar        : check the existence of a variable in a file
   !!   closeout      : close output file
   !!   copyatt       : copy attributes from a file taken as model
   !!   create        : create a netcdf data set
@@ -98,7 +100,7 @@
      MODULE PROCEDURE atted_char, atted_r4
   END INTERFACE
 
-  PUBLIC :: chkfile
+  PUBLIC :: chkfile, chkvar
   PUBLIC :: copyatt, create, createvar, getvaratt, cvaratt
   PUBLIC :: putatt, putheadervar, putvar, putvar1d, putvar0d, atted
   PUBLIC :: getatt, getdim, getvdim, getipk, getnvar, getvarname, getvarid, getspval
@@ -2142,5 +2144,47 @@ CONTAINS
 
   END FUNCTION chkfile
 
+  LOGICAL FUNCTION chkvar (cd_file, cd_var)
+    !!---------------------------------------------------------------------
+    !!                  ***  FUNCTION chkvar  ***
+    !!
+    !! ** Purpose :  Check if cd_var exists in file cd_file.
+    !!               Return false if it exists, true if it does not
+    !!               Do nothing is varname is 'none'
+    !!
+    !! ** Method  : Doing it this way allow statements such as
+    !!              IF ( chkvar( cf_toto, cv_toto) ) STOP  ! missing var
+    !!
+    !!----------------------------------------------------------------------
+    CHARACTER(LEN=*), INTENT(in) :: cd_file
+    CHARACTER(LEN=*), INTENT(in) :: cd_var
+
+    INTEGER(KIND=4)              :: istatus
+    INTEGER(KIND=4)              :: incid, id_t, id_var
+
+    !!----------------------------------------------------------------------
+    IF ( TRIM(cd_var) /= 'none')  THEN
+    
+       ! Open cdf dataset
+       istatus = NF90_OPEN(cd_file, NF90_NOWRITE,incid)
+       ! Read variable
+       istatus = NF90_INQ_VARID(incid, cd_var, id_var)
+
+       IF ( istatus == NF90_NOERR ) THEN
+          chkvar = .false.
+       ELSE
+          PRINT *, ' '
+          PRINT *, ' Var ',TRIM(cd_var),' is missing in file ',TRIM(cd_file)
+          chkvar = .true.
+       ENDIF
+       
+       ! Close file
+       istatus = NF90_CLOSE(incid) 
+    ELSE
+       chkvar = .false.  ! 'none' file is not checked
+    ENDIF
+
+  END FUNCTION chkvar
+
 END MODULE cdfio
 
diff --git a/cdfmkmask.f90 b/cdfmkmask.f90
index 4e7584f..f5db2b1 100644
--- a/cdfmkmask.f90
+++ b/cdfmkmask.f90
@@ -14,6 +14,7 @@ PROGRAM cdfmkmask
   !!
   !! History : 2.1  : 11/2005  : J.M. Molines : Original code
   !!           3.0  : 01/2011  : J.M. Molines : Doctor norm + Lic.
+  !! Modified : 3.0 : 08/2011  : P.   Mathiot : Add zoomij and zoombat option
   !!----------------------------------------------------------------------
   USE cdfio
   USE modcdfnames
@@ -29,29 +30,37 @@ PROGRAM cdfmkmask
   INTEGER(KIND=4)                           :: ierr                     ! working integer
   INTEGER(KIND=4)                           :: narg, iargc, ijarg       ! 
   INTEGER(KIND=4)                           :: npiglo, npjglo, npk      ! size of the domain
+  INTEGER(KIND=4)                           :: iimin, iimax             ! limit in i
+  INTEGER(KIND=4)                           :: ijmin, ijmax             ! limit in j
   INTEGER(KIND=4)                           :: ncout                    ! ncid of output file
   INTEGER(KIND=4), DIMENSION(4)             :: ipk, id_varout           ! outptut variables : number of levels,
 
-  
   REAL(KIND=4)                              :: rlonmin, rlonmax         ! limit in longitude
   REAL(KIND=4)                              :: rlatmin, rlatmax         ! limit in latitude
+  REAL(KIND=4)                              :: rbatmin, rbatmax         ! limit in latitude
   REAL(KIND=4), DIMENSION(1)                :: tim                      ! time counter
   REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: tmask, zmask             ! 2D mask at current level
   REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: rlon, rlat               ! latitude and longitude
+  REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: rbat                     ! bathymetry 
 
   CHARACTER(LEN=256)                        :: cf_tfil                  ! file name
   CHARACTER(LEN=256)                        :: cf_out = 'mask_sal.nc'   ! output file
+  CHARACTER(LEN=256)                        :: cv_mask                  ! variable name
   CHARACTER(LEN=256)                        :: cldum                    ! dummy string
 
   TYPE (variable), DIMENSION(4)             :: stypvar                  ! output attribute
  
-  LOGICAL                                   :: lzoom = .false.          ! zoom flag
+  LOGICAL                                   :: lzoom    = .false.       ! zoom flag lat/lon
+  LOGICAL                                   :: lzoomij  = .false.       ! zoom flag i/j
+  LOGICAL                                   :: lzoombat = .false.       ! zoom flag bat
   !!----------------------------------------------------------------------
   CALL ReadCdfNames()
 
   narg = iargc()
   IF ( narg == 0 ) THEN
      PRINT *,' usage : cdfmkmask T-file [-zoom lonmin lonmax latmin latmax] ...'
+     PRINT *,'                   ... [-zoomij iimin iimax ijmin ijmax] ...'
+     PRINT *,'                   ... [-zoombat bathymin bathymax]  ...'
      PRINT *,'                   ... [-o OUT-file ]'
      PRINT *,'      '
      PRINT *,'     PURPOSE :'
@@ -60,16 +69,26 @@ PROGRAM cdfmkmask
      PRINT *,'      '
      PRINT *,'     ARGUMENTS :'
      PRINT *,'       T-file : netcdf file with salinity.' 
+     PRINT *,'                if T-file = -maskfile, we assume a reference file named ',TRIM(cn_fmsk)
+     PRINT *,'                with tmask variable.' 
      PRINT *,'      '
      PRINT *,'     OPTIONS :'
      PRINT *,'       [-zoom lonmin lonmax latmin latmax] : geographical windows used to'
      PRINT *,'                        limit the area where the mask is builded. Outside'
      PRINT *,'                        this area, the mask is set to 0.'
+     PRINT *,'       [-zoomij iimin iimax ijmin ijmax] : model grid windows used to'
+     PRINT *,'                        limit the area where the mask is builded. Outside'
+     PRINT *,'                        this area, the mask is set to 0.'
+     PRINT *,'       [-zoombat bathymin bathymax] : depth windows used to'
+     PRINT *,'                        limit the area where the mask is builded. Outside'
+     PRINT *,'                        this area, the mask is set to 0.' 
+     PRINT *,'                        Need mesh_zgr.nc'
      PRINT *,'       [-o OUT-file ] : output file name to be used in place of standard'
      PRINT *,'                        name [ ',TRIM(cf_out),' ]'
      PRINT *,'      '
      PRINT *,'     REQUIRED FILES :'
-     PRINT *,'       none' 
+     PRINT *,'       If option -zoombat is used, file ', TRIM(cn_fzgr),' is required.'
+     PRINT *,'       If option T-file is -maskfile then ', TRIM(cn_fmsk), ' is required.'
      PRINT *,'      '
      PRINT *,'     OUTPUT : '
      PRINT *,'       netcdf file : ', TRIM(cf_out), ' or OUT-file.'
@@ -86,13 +105,25 @@ PROGRAM cdfmkmask
     CALL getarg (ijarg, cldum) ; ijarg = ijarg + 1
     SELECT CASE ( cldum )
     !
-    CASE ( '-zoom' )  ! read a zoom area
+    CASE ( '-zoom' )  ! read a zoom lat/lon area
        lzoom = .true.
        CALL getarg (ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) rlonmin
        CALL getarg (ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) rlonmax
        CALL getarg (ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) rlatmin
        CALL getarg (ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) rlatmax
     !
+    CASE ( '-zoomij' )  ! read a zoom i/j area
+       lzoomij = .true.
+       CALL getarg (ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) iimin
+       CALL getarg (ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) iimax
+       CALL getarg (ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) ijmin
+       CALL getarg (ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) ijmax
+    !
+    CASE ( '-zoombat' )  ! read a zoom bathy area 
+       lzoombat = .true.
+       CALL getarg (ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) rbatmin
+       CALL getarg (ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) rbatmax
+    !
     CASE ( '-o'    )  ! change output file name
        CALL getarg (ijarg, cf_out) ; ijarg = ijarg + 1
     !
@@ -102,6 +133,15 @@ PROGRAM cdfmkmask
     END SELECT
   ENDDO
 
+  IF ( lzoom .AND. lzoomij ) PRINT *, 'WARNING 2 spatial condition for mask'
+  
+  cv_mask = cn_vosaline
+  IF (TRIM(cf_tfil)=='-maskfile') THEN
+     cv_mask = 'tmask'
+     cf_tfil = cn_fmsk
+     cn_z    = 'z'
+  END IF    
+
   IF ( chkfile(cf_tfil) ) STOP ! missing file
 
   npiglo = getdim (cf_tfil,cn_x)
@@ -142,7 +182,8 @@ PROGRAM cdfmkmask
   ierr  = createvar   (ncout,    stypvar, 4,      ipk,    id_varout )
   ierr  = putheadervar(ncout,    cf_tfil,  npiglo, npjglo, npk)
 
-  ALLOCATE (tmask(npiglo,npjglo), zmask(npiglo,npjglo))
+  ALLOCATE (tmask(npiglo,npjglo), zmask(npiglo,npjglo) )
+  IF ( lzoombat ) ALLOCATE ( rbat(npiglo,npjglo) )
 
   IF ( lzoom ) THEN
     ALLOCATE (rlon(npiglo,npjglo), rlat(npiglo,npjglo))
@@ -152,7 +193,7 @@ PROGRAM cdfmkmask
 
   DO jk=1, npk
      ! tmask
-     tmask(:,:) = getvar(cf_tfil, 'vosaline',  jk, npiglo, npjglo)
+     tmask(:,:) = getvar(cf_tfil, cv_mask,  jk, npiglo, npjglo)
      WHERE (tmask > 0 ) tmask = 1
      WHERE (tmask <=0 ) tmask = 0
 
@@ -167,6 +208,19 @@ PROGRAM cdfmkmask
         WHERE (rlat > rlatmax ) tmask = 0
         WHERE (rlat < rlatmin ) tmask = 0
      ENDIF
+
+     IF ( lzoomij ) THEN
+        tmask(1:iimin-1,:)      = 0
+        tmask(iimax+1:npiglo,:) = 0
+        tmask(:,ijmax+1:npjglo) = 0
+        tmask(:,ijmax+1:npjglo) = 0   
+     ENDIF
+
+     IF ( lzoombat ) THEN
+        rbat(:,:)= getvar(cn_fzgr, cn_hdepw,  1 ,npiglo, npjglo)
+        WHERE (rbat < rbatmin .OR. rbat > rbatmax) tmask = 0
+     ENDIF
+
      ierr       = putvar(ncout, id_varout(1), tmask, jk ,npiglo, npjglo)
      ! umask
      zmask = 0.
diff --git a/modcdfnames.f90 b/modcdfnames.f90
index 0755443..f147421 100644
--- a/modcdfnames.f90
+++ b/modcdfnames.f90
@@ -5,6 +5,7 @@ MODULE modCdfNames
   !! This will ease the generalization of CDFTOOLS
   !!=====================================================================
   !! History : 3.0  !  12/2010 ! J.M. Molines : Original code
+  !! Modified: 3.0  !  08/2010 ! P.   Mathiot : Add LIM3 variables
   !!----------------------------------------------------------------------
   IMPLICIT NONE
 
@@ -107,6 +108,8 @@ MODULE modCdfNames
   ! ice variable names
   CHARACTER(LEN=20) :: cn_iicethic='iicethic' !: ice thickness
   CHARACTER(LEN=20) :: cn_ileadfra='ileadfra' !: ice concentration
+  CHARACTER(LEN=20) :: cn_iicethic3='iicethic'!: ice thickness (LIM3)
+  CHARACTER(LEN=20) :: cn_ileadfra3='iiceconc'!: ice concentration (LIM3)
   
   ! Bathymetry
   CHARACTER(LEN=20) :: cn_fbathymet='bathy_meter.nc' !: file Bathymetry in meters

-- 
Alioth's /usr/local/bin/git-commit-notice on /srv/git.debian.org/git/debian-science/packages/cdftools.git



More information about the debian-science-commits mailing list