From 8de6e05aade00745f09259d974b435799e85eee5 Mon Sep 17 00:00:00 2001 From: neichin Date: Mon, 9 Jan 2017 17:43:56 +0100 Subject: [PATCH 01/33] adding diags for icb files (#9) * icb diags * icb diags * cleaning * icb diags * Update cdficbclimato.f90 * Update cdficbdiags.f90 --- src/cdficbclimato.f90 | 174 +++++++++++++++++++++++++++++++++++ src/cdficbdiags.f90 | 204 ++++++++++++++++++++++++++++++++++++++++++ 2 files changed, 378 insertions(+) create mode 100644 src/cdficbclimato.f90 create mode 100644 src/cdficbdiags.f90 diff --git a/src/cdficbclimato.f90 b/src/cdficbclimato.f90 new file mode 100644 index 0000000..fecb546 --- /dev/null +++ b/src/cdficbclimato.f90 @@ -0,0 +1,174 @@ +PROGRAM cdficbclimato + !!====================================================================== + !! *** PROGRAM cdficbclimato *** + !!===================================================================== + !! ** Purpose : Compute the iceberg mass and melt + !! + !! ** Method : Use the icb files for input and determine the + !! + !!---------------------------------------------------------------------- + USE cdfio + USE modcdfnames + !!---------------------------------------------------------------------- + !!---------------------------------------------------------------------- + IMPLICIT NONE + + INTEGER(KIND=4) :: jk, jj, jt, ji ! dummy loop index + INTEGER(KIND=4) :: ierr ! working integer + INTEGER(KIND=4) :: narg, iargc ! command line + INTEGER(KIND=4) :: npiglo, npjglo, npt, numFiles ! size of the domain + INTEGER(KIND=4) :: nvpk ! vertical levels in working variable + INTEGER(KIND=4) :: nperio = 4 ! boundary condition ( periodic, north fold) + INTEGER(KIND=4) :: ikx, iky, ikz=0 ! dims of netcdf output file + INTEGER(KIND=4) :: nboutput=2 ! number of values to write in cdf output + INTEGER(KIND=4) :: ncout ! for netcdf output + INTEGER(KIND=4), DIMENSION(:), ALLOCATABLE :: ipk, id_varout, itimeVar + + REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: e1, e2 ! metrics + REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: tmask, ff ! npiglo x npjglo + REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: ricbmass, ricbmelt ! icbmass icbmelt + REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: rdumlon, rdumlat ! dummy lon lat for output + REAL(KIND=4), DIMENSION(:), ALLOCATABLE :: tim ! time counter + + TYPE(variable), DIMENSION(:), ALLOCATABLE :: stypvar ! structure of output + ! + CHARACTER(LEN=256), DIMENSION(:), ALLOCATABLE :: cf_icb ! input icb file + CHARACTER(LEN=256) :: cf_out='icbdiags.nc' ! output file + CHARACTER(LEN=256) :: cldum ! dummy string + ! + LOGICAL :: lchk = .false. ! missing file flag + !!---------------------------------------------------------------------- + CALL ReadCdfNames() + + narg = iargc() + IF ( narg == 0 ) THEN + PRINT *,' usage : cdficbclimato 12-ICB-monthly-means-files' + PRINT *,' ' + PRINT *,' PURPOSE :' + PRINT *,' Compute the 2D field of icb mass and icb melt.' + PRINT *,' ' + PRINT *,' ARGUMENTS :' + PRINT *,' ICE-file : netcdf icb file' + PRINT *,' ' + PRINT *,' REQUIRED FILES :' + PRINT *,' ',TRIM(cn_fhgr),' and ',TRIM(cn_fmsk) + PRINT *,' ' + PRINT *,' OUTPUT : ' + PRINT *,' netcdf file : ', TRIM(cf_out) + PRINT *,' variables : Mass (Kg/m2 )' + PRINT *,' Melt (Kg/m2/s )' + STOP + ENDIF + + CALL getarg(1,cldum) + READ(cldum,*) numFiles + + IF (numFiles < 12) STOP + + ALLOCATE(cf_icb(numFiles)) + + DO ji= 1, numFiles + CALL getarg(i+1,cf_icb(i)) + lchk = lchk .OR. chkfile(cf_icb(i)) + END DO + + + lchk = lchk .OR. chkfile(cn_fhgr) + lchk = lchk .OR. chkfile(cn_fmsk) + + IF ( lchk ) STOP ! missing file + + npiglo = getdim (cf_icb(1),cn_x) + npjglo = getdim (cf_icb(1),cn_y) + npt = 12 + ikx = npiglo + iky = npjglo + + ALLOCATE ( tmask(npiglo,npjglo) ,ff(npiglo,npjglo) ) + ALLOCATE ( ricbmass(npiglo,npjglo) ) + ALLOCATE ( ricbmelt(npiglo,npjglo) ) + ALLOCATE ( e1(npiglo,npjglo),e2(npiglo,npjglo) ) + ALLOCATE ( tim(npt),itimeVar(npt) ) + + itimeVar = (/(i,i=1,12)/) + + ALLOCATE ( stypvar(nboutput), ipk(nboutput), id_varout(nboutput) ) + ALLOCATE ( rdumlon(1,1), rdumlat(1,1) ) + + rdumlon(:,:) = 0. + rdumlat(:,:) = 0. + + ipk(:) = 1 + + ! define new variables for output + stypvar%scale_factor = 1. + stypvar%add_offset = 0. + stypvar%savelog10 = 0. + stypvar%conline_operation = 'N/A' + stypvar%caxis = 'T' + + stypvar(1)%cname = 'Mass' + stypvar(1)%cunits = 'Kg/m2' + stypvar(1)%clong_name = 'Icb mass per unit of area' + stypvar(1)%cshort_name = 'Mass' + + stypvar(2)%cname = 'Melt' + stypvar(2)%cunits = 'Kg/m2/s' + stypvar(2)%clong_name = 'Icb melt flux' + stypvar(2)%cshort_name = 'Melt' + + + e1(:,:) = getvar(cn_fhgr, cn_ve1t, 1, npiglo, npjglo) + e2(:,:) = getvar(cn_fhgr, cn_ve2t, 1, npiglo, npjglo) + ff(:,:) = getvar(cn_fhgr, cn_gphit, 1, npiglo, npjglo) ! only the sign of ff is important + + tmask(:,:)=getvar(cn_fmsk,'tmask',1,npiglo,npjglo) + SELECT CASE (nperio) + CASE (0) ! closed boundaries + ! nothing to do + CASE (4) ! ORCA025 type boundary + tmask(1:2,:)=0. + tmask(:,npjglo)=0. + tmask(npiglo/2+1:npiglo,npjglo-1)= 0. + CASE (6) + tmask(1:2,:)=0. + tmask(:,npjglo)=0. + CASE DEFAULT + PRINT *,' Nperio=', nperio,' not yet coded' + STOP + END SELECT + + itimeVar = (/(i,i=1,12)/) + ! Check variable + IF (chkvar(cf_icb(1), cn_iicbmass)) THEN + cn_iicbmass='missing' + PRINT *,'' + PRINT *,' WARNING, ICEBERG MASS IS SET TO 0. ' + PRINT *,' ' + END IF + + ! + DO jt = 1, npt + IF (TRIM(cn_iicbmass) /= 'missing') ricbmass(:,:) = getvar(cf_icb(jt), cn_iicbmass, 1, npiglo, npjglo, ktime=1) + ricbmelt(:,:) = getvar(cf_icb(jt), cn_iicbmelt, 1, npiglo, npjglo, ktime=1) + + IF ( jt == 1 ) THEN + ! create output fileset + ncout = create (cf_out, 'none', ikx, iky, ikz, cdep='depthw' ) + ierr = createvar (ncout, stypvar, nboutput, ipk, id_varout ) + ierr = putheadervar(ncout, cf_icb(1), ikx, iky, ikz) + + tim = getvar1d(cf_icb(1), cn_vtimec, npt ) + tim = (/(i,i=1,12)/) + ierr = putvar1d(ncout, tim, npt, 'T') + ENDIF + + ! netcdf output + !ierr = putvar0d(ncout,cn_vtimec,jt,ktime=jt) + ierr = putvar(ncout,id_varout(1),REAL(ricbmass(:,:)),1,npiglo,npjglo, ktime=jt) + ierr = putvar(ncout,id_varout(2),REAL(ricbmelt(:,:)),1,npiglo,npjglo, ktime=jt) + + END DO ! time loop + ierr = closeout(ncout) + +END PROGRAM cdficbclimato diff --git a/src/cdficbdiags.f90 b/src/cdficbdiags.f90 new file mode 100644 index 0000000..e358cf5 --- /dev/null +++ b/src/cdficbdiags.f90 @@ -0,0 +1,204 @@ +PROGRAM cdficbdiag + !!====================================================================== + !! *** PROGRAM cdficbdiag *** + !!===================================================================== + !! ** Purpose : Compute the Ice volume, area and extend for each + !! hemisphere + !! + !! ** Method : Use the icemod files for input and determine the + !! hemisphere with sign of the coriolis parameter. + !! + !! History : 3.0 : 01/2016 : N. Merino : Original code + + !!---------------------------------------------------------------------- + USE cdfio + USE modcdfnames + !!---------------------------------------------------------------------- + !! CDFTOOLS_3.0 , MEOM 2011 + !! $Id: cdficbdiags.f90 759 2014-07-21 22:01:28Z molines $ + !! Copyright (c) 2010, J.-M. Molines + !! Software governed by the CeCILL licence (Licence/CDFTOOLSCeCILL.txt) + !!---------------------------------------------------------------------- + IMPLICIT NONE + + INTEGER(KIND=4) :: jk, jj, jt ! dummy loop index + INTEGER(KIND=4) :: ierr ! working integer + INTEGER(KIND=4) :: narg, iargc ! command line + INTEGER(KIND=4) :: npiglo, npjglo, npt ! size of the domain + INTEGER(KIND=4) :: nvpk ! vertical levels in working variable + INTEGER(KIND=4) :: nperio = 4 ! boundary condition ( periodic, north fold) + INTEGER(KIND=4) :: ikx=1, iky=1, ikz=0 ! dims of netcdf output file + INTEGER(KIND=4) :: nboutput=4 ! number of values to write in cdf output + INTEGER(KIND=4) :: ncout ! for netcdf output + INTEGER(KIND=4), DIMENSION(:), ALLOCATABLE :: ipk, id_varout + + REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: e1, e2 ! metrics + REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: tmask, ff ! npiglo x npjglo + REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: ricbmass, ricbmelt ! thickness, leadfrac (concentration) + REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: rdumlon, rdumlat ! dummy lon lat for output + REAL(KIND=4), DIMENSION(:), ALLOCATABLE :: tim ! time counter + + REAL(KIND=8) :: dmasss, dmelts ! volume, area extend South hemisphere + REAL(KIND=8) :: dextends, dextends2 ! volume, area extend South hemisphere + REAL(KIND=8) :: dmassn, dmeltn ! volume, area extend North hemisphere + REAL(KIND=8) :: dextendn, dextendn2 ! volume, area extend North hemisphere + + TYPE(variable), DIMENSION(:), ALLOCATABLE :: stypvar ! structure of output + ! + CHARACTER(LEN=256) :: cf_ifil ! input ice file + CHARACTER(LEN=256) :: cf_out='icbdiags.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 == 0 ) THEN + PRINT *,' usage : cdficbdiag ICB-file ' + PRINT *,' ' + PRINT *,' PURPOSE :' + PRINT *,' Compute the spatially integrated icb mass and melt flux.' + PRINT *,' ' + PRINT *,' ARGUMENTS :' + PRINT *,' ICB-file : a single netcdf icb file' + PRINT *,' ' + PRINT *,' REQUIRED FILES :' + PRINT *,' ',TRIM(cn_fhgr),' and ',TRIM(cn_fmsk) + PRINT *,' ' + PRINT *,' OUTPUT : ' + PRINT *,' netcdf file : ', TRIM(cf_out) + PRINT *,' variables : [NS]Mass (Kg )' + PRINT *,' [NS]Melt (Kg/s )' + PRINT *,' N = northern hemisphere' + PRINT *,' S = southern hemisphere' + PRINT *,' standard output' + STOP + ENDIF + + CALL getarg (1, cf_ifil) + + lchk = lchk .OR. chkfile(cn_fhgr) + lchk = lchk .OR. chkfile(cn_fmsk) + lchk = lchk .OR. chkfile(cf_ifil) + + IF ( lchk ) STOP ! missing file + + npiglo = getdim (cf_ifil,cn_x) + npjglo = getdim (cf_ifil,cn_y) + npt = getdim (cf_ifil,cn_t) + + ALLOCATE ( tmask(npiglo,npjglo) ,ff(npiglo,npjglo) ) + ALLOCATE ( ricbmass(npiglo,npjglo) ) + ALLOCATE ( ricbmelt(npiglo,npjglo) ) + ALLOCATE ( e1(npiglo,npjglo),e2(npiglo,npjglo) ) + ALLOCATE ( tim(npt) ) + + ALLOCATE ( stypvar(nboutput), ipk(nboutput), id_varout(nboutput) ) + ALLOCATE ( rdumlon(1,1), rdumlat(1,1) ) + + rdumlon(:,:) = 0. + rdumlat(:,:) = 0. + + ipk(:) = 1 + + ! define new variables for output + stypvar%scale_factor = 1. + stypvar%add_offset = 0. + stypvar%savelog10 = 0. + stypvar%conline_operation = 'N/A' + stypvar%caxis = 'T' + + stypvar(1)%cname = 'NMass' + stypvar(1)%cunits = 'Kg' + stypvar(1)%clong_name = 'Icb_Mass_in_Northern_Hemisphere' + stypvar(1)%cshort_name = 'NMass' + + stypvar(2)%cname = 'NMelt' + stypvar(2)%cunits = 'Kg/s' + stypvar(2)%clong_name = 'Icb_melt_in_Northern_Hemisphere' + stypvar(2)%cshort_name = 'NMelt' + + stypvar(3)%cname = 'SVMass' + stypvar(3)%cunits = 'Kg' + stypvar(3)%clong_name = 'Icb_Mass_in_Southern_Hemisphere' + stypvar(3)%cshort_name = 'SMass' + + stypvar(4)%cname = 'SMelt' + stypvar(4)%cunits = 'Kg/s' + stypvar(4)%clong_name = 'Icb_Melt_in_Southern_Hemisphere' + stypvar(4)%cshort_name = 'SMelt' + + + e1(:,:) = getvar(cn_fhgr, cn_ve1t, 1, npiglo, npjglo) + e2(:,:) = getvar(cn_fhgr, cn_ve2t, 1, npiglo, npjglo) + ff(:,:) = getvar(cn_fhgr, cn_gphit, 1, npiglo, npjglo) ! only the sign of ff is important + + ! modify the mask for periodic and north fold condition (T pivot, F Pivot ...) + ! in fact should be nice to use jperio as in the code ... + tmask(:,:)=getvar(cn_fmsk,'tmask',1,npiglo,npjglo) + SELECT CASE (nperio) + CASE (0) ! closed boundaries + ! nothing to do + CASE (4) ! ORCA025 type boundary + tmask(1:2,:)=0. + tmask(:,npjglo)=0. + tmask(npiglo/2+1:npiglo,npjglo-1)= 0. + CASE (6) + tmask(1:2,:)=0. + tmask(:,npjglo)=0. + CASE DEFAULT + PRINT *,' Nperio=', nperio,' not yet coded' + STOP + END SELECT + + ricbmass(:,:)=0. + ricbmelt(:,:)=0. + + + IF (chkvar(cf_ifil, cn_iicbmass)) STOP + + IF (chkvar(cf_ifil, cn_iicbmelt)) STOP + ! + DO jt = 1, npt + IF (TRIM(cn_iicbmass) /= 'missing') ricbmass(:,:) = getvar(cf_ifil, cn_iicbmass, 1, npiglo, npjglo, ktime=jt) + ricbmelt(:,:) = getvar(cf_ifil, cn_iicbmelt, 1, npiglo, npjglo, ktime=jt) + + ! North : ff > 0 + dmassn = SUM( ricbmass (:,:)* e1(:,:) * e2(:,:) * tmask (:,:), (ff > 0 ) ) + dmeltn = SUM( ricbmelt (:,:)* e1(:,:) * e2(:,:) * tmask (:,:), (ff > 0 ) ) + + ! South : ff < 0 + dmasss = SUM( ricbmass (:,:)* e1(:,:) * e2(:,:) * tmask (:,:), (ff < 0) ) + dmelts = SUM( ricbmelt (:,:)* e1(:,:) * e2(:,:) * tmask (:,:), (ff < 0 )) + + PRINT *,' TIME = ', jt,' ( ',tim(jt),' )' + PRINT *,' Northern Hemisphere ' + PRINT *,' NMass (Kg) ', dmassn + PRINT *,' NMelt (Kg/s) ', dmeltn + PRINT * + PRINT *,' Southern Hemisphere ' + PRINT *,' Mass (Kg) ', dmasss + PRINT *,' Melt (Kg/s) ', dmelts + + IF ( jt == 1 ) THEN + ! create output fileset + ncout = create (cf_out, 'none', ikx, iky, ikz, cdep='depthw' ) + ierr = createvar (ncout, stypvar, nboutput, ipk, id_varout ) + ierr = putheadervar(ncout, cf_ifil, ikx, iky, ikz, pnavlon=rdumlon, pnavlat=rdumlat) + + tim = getvar1d(cf_ifil, cn_vtimec, npt ) + ierr = putvar1d(ncout, tim, npt, 'T') + ENDIF + + ! netcdf output + ierr = putvar0d(ncout,id_varout(1), REAL(dmassn), ktime=jt) + ierr = putvar0d(ncout,id_varout(2), REAL(dmeltn), ktime=jt) + ierr = putvar0d(ncout,id_varout(3), REAL(dmasss), ktime=jt) + ierr = putvar0d(ncout,id_varout(4), REAL(dmelts), ktime=jt) + + END DO ! time loop + ierr = closeout(ncout) + +END PROGRAM cdficbdiag From c7fb91f9541b9d5c89cbd9f9e0258bcbeaf88521 Mon Sep 17 00:00:00 2001 From: Jean-Marc Molines Date: Mon, 9 Jan 2017 17:45:21 +0100 Subject: [PATCH 02/33] Update CDFTOOLSCeCILL.txt --- License/CDFTOOLSCeCILL.txt | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/License/CDFTOOLSCeCILL.txt b/License/CDFTOOLSCeCILL.txt index 9b568c5..a9db2eb 100644 --- a/License/CDFTOOLSCeCILL.txt +++ b/License/CDFTOOLSCeCILL.txt @@ -6,8 +6,8 @@ Contributors (alphabetic order ) : C.Q. Akuetevi, M. Balmaseda, E. Behrens, F. Castruccio, M. Chekki, P. Colombo, J. Deshayes, N. Djath, N. Ducousso, C. Dufour, R. Dussin, N. Ferry, F. Hernandez, M. Juza, A. Lecointre, S. Leroux, G. Mainsant, -P. Mathiot, A. Melet, X. Meunier, G. Moreau, W. Rath, J. Regidor, -M. Scheinert, A.M. Treguier +P. Mathiot, A. Melet, X. Meunier, G. Moreau, N. Merino, W. Rath, +J. Regidor, M. Scheinert, A.M. Treguier This software is a computer program for analysis of NEMO model output produced in the frame of the DRAKKAR project. It is designed for the From 5171c6d34047124e368cc0d4bf6e889472f484f1 Mon Sep 17 00:00:00 2001 From: jmm Date: Mon, 9 Jan 2017 17:52:38 +0100 Subject: [PATCH 03/33] modify Makefile for cdficb and correction in cdficbclimato --- src/Makefile | 6 ++++++ src/cdficbclimato.f90 | 10 +++++----- 2 files changed, 11 insertions(+), 5 deletions(-) diff --git a/src/Makefile b/src/Makefile index 007fa49..98b775e 100644 --- a/src/Makefile +++ b/src/Makefile @@ -324,6 +324,12 @@ cdfmxlhcsc: cdfio.o eos.o cdfmxlhcsc.f90 cdficediags: cdfio.o cdficediags.f90 $(F90) cdficediags.f90 -o $(BINDIR)/cdficediags cdfio.o modcdfnames.o $(FFLAGS) +cdficbclimato: cdfio.o cdficbclimato.f90 + $(F90) cdficbclimato.f90 -o $(BINDIR)/cdficbclimato cdfio.o modcdfnames.o $(FFLAGS) + +cdficbdiags: cdfio.o cdficbdiags.f90 + $(F90) cdficbdiags.f90 -o $(BINDIR)/cdficbdiags cdfio.o modcdfnames.o $(FFLAGS) + cdfzonalmean: cdfio.o cdfzonalmean.f90 $(F90) $(OMP) cdfzonalmean.f90 -o $(BINDIR)/cdfzonalmean cdfio.o modcdfnames.o $(FFLAGS) diff --git a/src/cdficbclimato.f90 b/src/cdficbclimato.f90 index fecb546..1744cf5 100644 --- a/src/cdficbclimato.f90 +++ b/src/cdficbclimato.f90 @@ -68,8 +68,8 @@ PROGRAM cdficbclimato ALLOCATE(cf_icb(numFiles)) DO ji= 1, numFiles - CALL getarg(i+1,cf_icb(i)) - lchk = lchk .OR. chkfile(cf_icb(i)) + CALL getarg(ji+1,cf_icb(ji)) + lchk = lchk .OR. chkfile(cf_icb(ji)) END DO @@ -90,7 +90,7 @@ PROGRAM cdficbclimato ALLOCATE ( e1(npiglo,npjglo),e2(npiglo,npjglo) ) ALLOCATE ( tim(npt),itimeVar(npt) ) - itimeVar = (/(i,i=1,12)/) + itimeVar = (/(ji,ji=1,12)/) ALLOCATE ( stypvar(nboutput), ipk(nboutput), id_varout(nboutput) ) ALLOCATE ( rdumlon(1,1), rdumlat(1,1) ) @@ -138,7 +138,7 @@ PROGRAM cdficbclimato STOP END SELECT - itimeVar = (/(i,i=1,12)/) + itimeVar = (/(ji,ji=1,12)/) ! Check variable IF (chkvar(cf_icb(1), cn_iicbmass)) THEN cn_iicbmass='missing' @@ -159,7 +159,7 @@ PROGRAM cdficbclimato ierr = putheadervar(ncout, cf_icb(1), ikx, iky, ikz) tim = getvar1d(cf_icb(1), cn_vtimec, npt ) - tim = (/(i,i=1,12)/) + tim = (/(ji,ji=1,12)/) ierr = putvar1d(ncout, tim, npt, 'T') ENDIF From edfaffb441336354b6a05bbadfc214a9b93a7399 Mon Sep 17 00:00:00 2001 From: jmm Date: Tue, 10 Jan 2017 20:28:16 +0100 Subject: [PATCH 04/33] add new extension to skip in .gitignore (.opod, .html, .tmp, cdftools.1 ) --- .gitignore | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/.gitignore b/.gitignore index 7e1ba17..4407cbc 100644 --- a/.gitignore +++ b/.gitignore @@ -9,3 +9,7 @@ make.macro *.aux *.idx *.toc +cdftools.1 +*.html +*.opod +*.tmp From db2283051b5b8cda7432e5c93f91e0edc0a6a6fa Mon Sep 17 00:00:00 2001 From: jmm Date: Tue, 10 Jan 2017 22:23:07 +0100 Subject: [PATCH 05/33] corrections on comments in cdfsection ( the degree symbol caused a crash in the html doc) --- src/cdfsections.f90 | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/cdfsections.f90 b/src/cdfsections.f90 index a87b1aa..ea5a16c 100644 --- a/src/cdfsections.f90 +++ b/src/cdfsections.f90 @@ -5,7 +5,7 @@ program cdfsections ! ! ** Purpose : extract oceanic fields along a track made of several sections. ! -! ** Method : computes N sections by taking the nearest point north of 60°N +! ** Method : computes N sections by taking the nearest point north of 60N ! and near undefined values (bottom or coasts), and interpolates ! between the four nearest points elsewhere. ! @@ -19,7 +19,7 @@ program cdfsections ! WARNING : ! - require large memory : reduce domain size with ncks if insufficient memory error. ! - does not work if the section crosses the Greenwich line (easy to modify if needed). -! - not yet tested north of 60°N (but should work) ... +! - not yet tested north of 60N (but should work) ... ! ! history : ! N. JOURDAIN (LEGI-MEOM), April 2009 @@ -112,7 +112,7 @@ program cdfsections PRINT *,' It is recommended to put a lot of points on each section if the aim' PRINT *,' is to compute X-integrations along the section (10 x the model resolution).' PRINT *,'NB : sections cannot cross the Greenwich line !!' - PRINT *,'NB : Not yet tested north of 60°N.' + PRINT *,'NB : Not yet tested north of 60N.' PRINT *,'NB : require a large amount of memory !' PRINT *,' -> reduce domain size with ncks -d if insufficient memory error.' PRINT *,' ' From ca6b6eaa7ca7a594b6f3d52e79c69ed153ac4df4 Mon Sep 17 00:00:00 2001 From: jmm Date: Tue, 10 Jan 2017 22:23:58 +0100 Subject: [PATCH 06/33] Use pod to produce html documentation. * add style sheet (minimum) * modify text in cdftools-begin.pod * modify text in cdftools-end.pod * adapt Makefile to build the opod file --- src/Makefile | 14 ++++++++++++-- src/cdftools-begin.pod | 24 +++++++++++++----------- src/cdftools-end.pod | 11 +---------- src/cdftools.css | 19 +++++++++++++++++++ 4 files changed, 45 insertions(+), 23 deletions(-) create mode 100644 src/cdftools.css diff --git a/src/Makefile b/src/Makefile index 98b775e..c26ef39 100644 --- a/src/Makefile +++ b/src/Makefile @@ -551,16 +551,26 @@ clean: cleanexe: clean ( cd $(BINDIR) ; \rm -f $(EXEC) ) -man: cdftools.1 +man: cdftools.1 cdftools.html cdftools.1: cdftools.opod pod2man --center "CDFTOOLS / NEMO Documentation" \ --release "SVN Revision $$(LANG=C svn update | grep '^At rev' | awk '{print $$3}' | cut -f 1 -d '.')" \ cdftools.opod > cdftools.1 +cdftools.html: cdftools.opod + pod2html --infile=cdftools.opod --outfile=cdftools.html --title="CDFTOOLS Man pages" --css="./cdftools.css" + cdftools.opod: $(EXEC) cdftools-begin.pod cdftools-end.pod cat cdftools-begin.pod > cdftools.opod - for s in $$( cd $(BINDIR); ls -1 ); do echo ''; echo "=head2 $$s"; echo ''; $$s; done >> cdftools.opod + for s in $$( cd $(BINDIR); ls -1 ); do echo ''; echo "=head2 $$s"; echo ''; $(BINDIR)/$$s; done >> cdftools.opod + echo ' ' >> cdftools.opod + echo "=head1 AUTHORS" >> cdftools.opod + echo ' ' >> cdftools.opod + echo "Project headed by Jean-Marc Molines, (IGE, Grenoble - France)" >> cdftools.opod + echo ' ' >> cdftools.opod + grep -A1000 -i contribu ../License/CDFTOOLSCeCILL.txt | grep -m1 -B1000 ^$$ >> cdftools.opod + echo ' ' >> cdftools.opod cat cdftools-end.pod >> cdftools.opod install: diff --git a/src/cdftools-begin.pod b/src/cdftools-begin.pod index b33daff..24fa2b8 100644 --- a/src/cdftools-begin.pod +++ b/src/cdftools-begin.pod @@ -1,21 +1,23 @@ =head1 NAME -cdftools - diagnostics in Fortran 90 for NEMO model outputs +CDFTOOLS - diagnostics in Fortran 90 for NEMO model outputs -=head1 SYNOPSIS +=head1 PACKAGE DESCRIPTION + +C is a diagnostic package written in fortran 90 for the analysis of NEMO model output, initialized in the frame of the DRAKKAR project (https://www.drakkar-ocean.eu/). It is now available on GitHub under the CeCILL license (http://www.cecill.info/licences/Licence_CeCILL_V2-en.html). + +C web site : http://www.nemo-ocean.eu/ - cdf* option... +=head1 SYNOPSIS -=head1 DESCRIPTION +C is a collection of fortran program. Each program belonging to this collection is +designed to perform some specific actions on NEMO output files, and generally provides another netcdf file as output. Output files follow the same CDF format as NEMO file, thus allowing for the building of a secondary data base (assuming that the primary data base is just the raw model output). -C is a diagnostic package written in fortran 90 -for the analysis of NEMO model output in the frame of the DRAKKAR project. +This documentation is automatically produced by the concatenation of the C messages produced by each particular program when invoked without any argument. (Standard behaviour of all cdftools). In the documentation, we use a rather classical formalism, where mandatory arguments are just indicated on the command line and options are indicated between squared brackets [..]. -This software is a computer program for analysis of NEMO model output -produced in the frame of the DRAKKAR project. It is designed for the -treatment of the NetCdf files produced by NEMO-DRAKKAR. +Each program name starts with the 3 letters 'cdf' followed by a word related to the action performed by the tools. Example: C is used to compute the vertical velocity using the horizontal velocity field represented by its two components Ufile.nc and Vfile.nc. -C web site : http://www.nemo-ocean.eu/ +Better than a long speech, the following paragraphs describes each of the existing cdftools. -=head1 COMMAND +=head1 COMMANDS DESCRIPTION diff --git a/src/cdftools-end.pod b/src/cdftools-end.pod index cb54d98..5968d57 100644 --- a/src/cdftools-end.pod +++ b/src/cdftools-end.pod @@ -1,16 +1,7 @@ -=head1 AUTHORS - -Written by Jean-Marc Molines, Grenoble - France - -Contributors : M. Balmaseda, E. Behrens, F. Castruccio, J. Deshayes, -N. Djath, N. Ducousso, C. Dufour, R. Dussin, N. Ferry, F. Hernandez, -M. Juza, A. Lecointre, P. Mathiot, A. Melet, G. Moreau, A.M. Treguier - =head1 LICENSE AND COPYRIGHT -Copyright (C) 1998-2012 LEGI / Team MEOM / CNRS UMR 5519 - Grenoble - France, -Jean-Marc.Molines@legi.grenoble-inp.fr +Copyright (C) 1998-2016 IGE-MEOM (Jean-Marc.Molines@univ-grenoble-alpes.fr ) This software is governed by the CeCILL license under French law and abiding by the rules of distribution of free software. You can use, diff --git a/src/cdftools.css b/src/cdftools.css new file mode 100644 index 0000000..90cec1c --- /dev/null +++ b/src/cdftools.css @@ -0,0 +1,19 @@ +h1 { + color: red; + text-align: left; + } + +h2 { + color: blue; + } + +ul { + list-style-type: disc; + color: red; + } + +ul ul li { + list-style-type: circle; + color: blue; + } + From 277e1528315515a7f292284de5a65ecb9a8a2e6a Mon Sep 17 00:00:00 2001 From: jmm Date: Wed, 11 Jan 2017 09:31:14 +0100 Subject: [PATCH 07/33] move html documentation into DOC sub directory. * add the action in installman target of the Makefile * adjust .gitignore to deal with html files in DOC but not in src * move style sheet to DOC as well --- .gitignore | 1 - {src => DOC}/cdftools.css | 0 DOC/cdftools.html | 4463 +++++++++++++++++++++++++++++++++++++ src/.gitignore | 1 + src/Makefile | 1 + 5 files changed, 4465 insertions(+), 1 deletion(-) rename {src => DOC}/cdftools.css (100%) create mode 100644 DOC/cdftools.html create mode 100644 src/.gitignore diff --git a/.gitignore b/.gitignore index 4407cbc..3a2d190 100644 --- a/.gitignore +++ b/.gitignore @@ -10,6 +10,5 @@ make.macro *.idx *.toc cdftools.1 -*.html *.opod *.tmp diff --git a/src/cdftools.css b/DOC/cdftools.css similarity index 100% rename from src/cdftools.css rename to DOC/cdftools.css diff --git a/DOC/cdftools.html b/DOC/cdftools.html new file mode 100644 index 0000000..dec036f --- /dev/null +++ b/DOC/cdftools.html @@ -0,0 +1,4463 @@ + + + + +CDFTOOLS Man pages + + + + + + + + + + + +

NAME

+ +

CDFTOOLS - diagnostics in Fortran 90 for NEMO model outputs

+ +

PACKAGE DESCRIPTION

+ +

CDFTOOLS is a diagnostic package written in fortran 90 for the analysis of NEMO model output, initialized in the frame of the DRAKKAR project (https://www.drakkar-ocean.eu/). It is now available on GitHub under the CeCILL license (http://www.cecill.info/licences/Licence_CeCILL_V2-en.html).

+ +

NEMO web site : http://www.nemo-ocean.eu/

+ +

SYNOPSIS

+ +

CDFTOOLS is a collection of fortran program. Each program belonging to this collection is designed to perform some specific actions on NEMO output files, and generally provides another netcdf file as output. Output files follow the same CDF format as NEMO file, thus allowing for the building of a secondary data base (assuming that the primary data base is just the raw model output).

+ +

This documentation is automatically produced by the concatenation of the USAGE messages produced by each particular program when invoked without any argument. (Standard behaviour of all cdftools). In the documentation, we use a rather classical formalism, where mandatory arguments are just indicated on the command line and options are indicated between squared brackets [..].

+ +

Each program name starts with the 3 letters 'cdf' followed by a word related to the action performed by the tools. Example: cdfw Ufile.nc Vfile.nc is used to compute the vertical velocity using the horizontal velocity field represented by its two components Ufile.nc and Vfile.nc.

+ +

Better than a long speech, the following paragraphs describes each of the existing cdftools.

+ +

COMMANDS DESCRIPTION

+ +

cdf16bit

+ +
  usage : cdf16bit 32BIT-file [ -check ] [ -verbose]
+       
+      PURPOSE :
+        Convert input 32 bit precision file into 16 bit
+        precision file using add_offset and scale_factor
+       
+      ARGUMENTS :
+        32BIT-file : input 32 bit file to be converted
+       
+      OPTIONS :
+        [ -check ]   : control than the scale factors are adequate
+        [ -verbose ] : give information level by level.
+       
+      REQUIRED FILES :
+        none 
+       
+      OUTPUT : 
+        netcdf file : cdf16bit.nc
+          variables : same names than in input file
+ +

cdf2levitusgrid2d

+ +
  usage : cdf2levitusgrid2d IN-file OUT-file  VAR-name2D
+       
+      PURPOSE :
+        remaps (bin) 2D high resolution (finer than 1x1 deg) 
+        fields on Levitus 2D 1x1 deg grid                    
+        (does not work for vector fields)  
+        It assumes that Levitus grid SW grid cell center 
+        is (0.5W,89.5S) 
+       
+      ARGUMENTS :
+        IN-file  : netcdf input file 
+        OUT-file : netcdf output file 
+        VAR-name2D : input variable name for interpolation 
+       
+      OPTIONS :
+       
+      REQUIRED FILES :
+        mesh_hgr.nc
+        mask.nc
+        levitus_mask.nc
+       
+      OUTPUT : 
+        netcdf file : name given as second argument
+          variables : 2d_var_name
+ +

cdf2levitusgrid3d

+ +
  usage : cdf2levitusgrid3d -f IN-file -o OUT-file  -v VAR-name3D [-360]
+         [-r resolution] 
+       
+      PURPOSE :
+        remaps (bin) 3D high resolution (finer than 1x1 deg) 
+        fields on a regular grid. (vertical grid as input grid)  
+        (does not work for vector fields)  
+        Resolution can be given as argument, default is   0.3333333      deg.
+       
+      ARGUMENTS :
+        -f IN-file  : netcdf input file 
+        -o OUT-file : netcdf output file 
+        -v VAR-name2D : input variable name for interpolation 
+       
+      OPTIONS :
+        -360 : outfile is defined from 0 to 360 deg
+               Default is from -180 to 180 
+        -r  : resolution.
+      
+      REQUIRED FILES :
+        mesh_hgr.nc
+        mask.nc
+       
+      OUTPUT : 
+        netcdf file : name given as second argument
+          variables : 3d_var_name
+ +

cdf2matlab

+ +
  usage : cdf2matlab IN-file IN-var level 
+       
+      PURPOSE :
+        Convert global nemo input file (ORCA configurations) into
+        a file with monotonically increasing longitudes.
+       
+      ARGUMENTS :
+        IN-file : input model file.
+        IN-var  : netcdf variable name to process.
+        level   : level to process.
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : output.nc
+          variables : same name than in input file.
+ +

cdf_xtrac_brokenline

+ +
  usage :  cdf_xtrac_brokenline T-file U-file V-file [ice-file] ....
+     [-f section_filei,sec_file2, ... ] [-verbose] [-ssh ] [-mld] [-ice]
+       
+      PURPOSE :
+         This tool extracts model variables from model files for a geographical
+       broken line, similar to an oceanographic campaign where an oceanic 
+       section is formed by one or more legs.
+         The broken line is specified by the position of ending points of each
+       leg, given in an ASCII file. OVIDE section is taken as default, when no
+       section file is provided.
+         This tool provides a netcdf file similar to a model file, but with a 
+       degenerated y dimension (1). In order to be able to use standard CDFTOOLS
+       relevant metric variables are saved into the output file, such as pseudo
+       e1v and e3v_ps and vmask. Therefore the output file can be considered as
+       a mesh_hgr, mesh_zgr and mask file for any 'meridional' computation.
+         This tools works with temperatures, salinities and normal velocities.
+       The broken line is approximated in the model, by a succession of segments
+       joining F-points. The velocity is taken as either U or V depending on the
+       orientation of the segment, temperatures and salinities are interpolated
+       on the velocity points. When progressing along the broken line, velocity
+       is positive when heading to the right of the progression.
+         The barotropic transport across the broken line is computed, using the
+       same sign convention. On a closed broken line, the barotropic transport
+       should be very small.
+       
+      ARGUMENTS :
+       T-file   :  model gridT file 
+       U-file   :  model gridU file 
+       V-file   :  model gridV file 
+       ice-file :  model ice file 
+       
+      OPTIONS :
+       -f section_file1,section_file2,... : provide a comma separated list of
+               files for section definition. Section_file is an ascii file as 
+               follows:
+              * line #1 : name of the section (e.g. ovide). 
+                   Will be used for naming the output file.
+              * line #2 : number of points defining the broken line.
+              * line #3-end : a pair of Longitude latitude values defining
+                    the points. If not supplied, use hard-coded information
+                    for OVIDE section. A comment can be added at the end of
+                    of the lines, using a # as separator
+       -verbose : increase verbosity  
+       -ssh     : also save ssh along the broken line.
+       -mld     : also save mld along the broken line.
+       -ice     : also save ice properties along the broken line.
+      
+      REQUIRED FILES :
+       mesh_hgr.nc and mesh_zgr.nc must be in the current directory 
+       
+      OUTPUT : 
+        netcdf file : section_name.nc
+          variables : temperature, salinity, normal velocity, pseudo V metrics,
+                      mask, barotropic transport, bathymetry of velocity points.
+        ASCII file : section_name_section.dat usefull for cdftransport 
+       
+      SEE ALSO :
+         cdftransport, cdfmoc, cdfmocsig. This tool replaces cdfovide.
+       
+ +

cdfbathy

+ +
  usage : cdfbathy/cdfvar -f IN-file [options]
+       
+      PURPOSE :
+        Allow manual modification of the input file. Very convenient
+        for bathymetric files, can also be used with any model file
+        Keep a log.f90 file of the modifications for automatic reprocessing
+       
+      ARGUMENTS :
+        IN-file : original input file. The program works on a copy of the
+                 original file (default)
+       
+      OPTIONS :
+        -file (or -f )       : name of input file 
+        -var  (or -v )       : name of cdf variable [default: Bathymetry]
+        -lev  (or -l )       : level to work with 
+        -time (or -t )       : time to work with 
+        -scale  s            : use s as a scale factor (divide when read the file)
+        -zoom (or -z )       : sub area of the bathy file to work with (imin imax jmin jmax)
+        -fillzone (or -fz )  : sub area will be filled with 0 up to the first coast line 
+        -fillpool (or -fp ) [ icrit ] : the whole file is check and fill all the pool smaller than (icrit) cell by 0
+        -raz_zone (or -raz ) : sub area will be filled with 0 up 
+        -raz_below depmin    : any depth less than depmin in subarea will be replaced by 0 
+           (or -rb depmin )  
+        -set_below depmin    : any depth less than depmin in subarea will be replaced by depmin 
+           (or -sb depmin ) 
+        -fullstep depmin     : sub area will be reshaped as full-step, below depmin
+           (or -fs depmin )    requires the presence of the file zgr_bat.txt (from ocean.output, eg )
+        -dumpzone (or -d )   : sub area will be output to an ascii file, which can be used by -replace
+                               after manual editing 
+        -nicedumpzone        : sub area will be output to an ascii file (nice output)
+                 (or -nd )
+        -replace (or -r )    : sub area defined by the file will replace the original bathy
+        -append (or -a )     : fortran log file (log.f90) will be append with actual modif
+                               Standard behaviour is to overwrite/create log file
+        -overwrite (or -o )  : input bathy file will be used as output.
+                               Standard behaviour is to use a work copy of the original file
+                               (indexed from 01 to 99 if necessary ) 
+        -log logfile         : log file for change (default is log.f90) 
+       
+      OUTPUT : 
+           netcdf file : according to used options, if the original file is to be modified
+                  a sequence number is added at the end of the input file name, to keep
+                  modifications.
+             variables : same as input file
+ +

cdfbci

+ +
  usage : cdfbci UVWT-file
+       
+      PURPOSE :
+        Compute elements for analysing the baroclinic instability
+       
+      ARGUMENTS :
+        UVWT-file : input file is produced by cdfmoyuvwt, and the mean
+               must be computed on a long-enough period for the 
+               statistics to be meaningful. Points are on T grid.
+       
+      REQUIRED FILES :
+        Need mesh_hgr.nc file
+       
+      OUTPUT : 
+        netcdf file : bci.nc
+          variables : 5 output variables
+              dTdx : zonal derivative of Tbar on T point (*1000)
+              dTdy : meridional derivative of Tbar on T point (*1000)
+              uT   : anomaly of u times anomaly of T on T point
+              vT   : anomaly of v times anomaly of T on T point
+              bci  : transfert of energy for the baroclinic instability (*1000)
+       
+      SEE ALSO :
+        cdfmoyuvwt 
+ +

cdfbn2

+ +
  usage : cdfbn2  T-file [W] [-full]
+      PURPOSE :
+        Compute the Brunt-Vaissala frequency (N2) according to
+        temperature and salinity given in the input file.
+       
+      ARGUMENTS :
+        T-file : netcdf input gridT file for temperature and salinity.
+       
+      OPTIONS :
+        [ W ] : keep N2 at W points. Default is to interpolate N2
+              at T point on the vertical.
+        [ -full ] : indicate a full step configuration instead of
+                 the default partial steps.
+       
+      REQUIRED FILES :
+        mesh_zgr.nc is needed for this program.
+       
+      OUTPUT : 
+        netcdf file : bn2.nc
+          variables : vobn2
+ +

cdfbotpressure

+ +
  usage : cdfbotpressure T-file [-full] [-ssh] [-ssh2 ] [-xtra ] 
+       
+      PURPOSE :
+           Compute the vertical bottom pressure (pa) from in situ density
+       
+      ARGUMENTS :
+          T-file : gridT file holding either Temperature and  salinity 
+       
+      OPTIONS :
+         -full : for full step computation 
+         -ssh  : Also take SSH into account in the computation
+                 In this case, use rau0=   1035.000      kg/m3 for 
+                 surface density (as in NEMO)
+                 If you want to use 2d surface density from 
+                 the model, use option -ssh2
+         -ssh2 : as option -ssh but surface density is taken from 
+                 the model instead of a constant
+         -xtra :  Using this option, the output file also contains the ssh,
+                 and the pressure contribution of ssh to bottom pressure. 
+                 Require either -ssh or -ssh2 option. Botpressure is still
+                 the total pressure, including ssh effect.
+       
+      REQUIRED FILES :
+        mask.nc and mesh_zgr.nc
+       
+      OUTPUT : 
+        netcdf file :  botpressure.nc
+          variables :  sobotpres
+       
+      SEE ALSO :
+         cdfvint
+       
+ +

cdfbottom

+ +
  usage : cdfbottom  IN-file [ T | U | V | F]
+       
+      PURPOSE :
+        Create a 2D file with bottom most values for all the variables
+        which are in the input 3D file.
+       
+      ARGUMENTS :
+        IN-file : input netcdf 3D file.
+       
+      OPTIONS :
+        [ T | U | V | F] : specify the type of grid point on the C-grid
+             if not given, assume that land points are values with 0.
+       
+      REQUIRED FILES :
+        mask.nc file is required if the grid point is specified
+                   or if the land value is not 0.
+       
+      OUTPUT : 
+        netcdf file : bottom.nc
+          variables :  same names than input file, long_name attribute is
+                prefixed by Bottom 
+ +

cdfbottomsig

+ +
  usage : cdfbottomsig  T-file [zref]
+       
+      PURPOSE :
+        Create a 2D file with bottom density. In case a depth reference
+        is given, the density is refered to this depth. By default sigma-0
+        is used. Bottom most point is determined from the last non zero 
+        salinity point in the water column.
+       
+      ARGUMENTS :
+        T-file : input file with temperature and salinity 
+       
+      OPTIONS :
+        [zref] : depth reference for potential density
+               keyword 'ntr' can also be specified, which indicates that we
+               will use neutral density
+              If not given assume sigma-0
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        netcdf file : botsig.nc
+          variables : sobotsig0 or sobotsigi ( kg/m3 - 1000 )
+                      or sobotsigntr (kg/m3)
+ +

cdfbti

+ +
  usage : cdfbti UVWT-file
+       
+      PURPOSE :
+        Compute  the terms in the barotropic energy tranfert equation.
+        The transfert of energy for the barotropic instability is 
+        bti= -[(u'bar)^2*dubar/dx ...
+              +(v'bar)^2*dvbar/dy ...
+              +(u'v'*(dubar/dy +dvbar/dx))]
+       
+      ARGUMENTS :
+        UVWT-file : netcdf file produced by cdfmoyuvwt
+       
+      REQUIRED FILES :
+        mesh_hgr.nc
+       
+      OUTPUT : 
+        netcdf file : bti.nc
+          variables : 
+                dudx : zonal derivate of ubar on T point
+                dvdx : zonal derivate of vbar on T point
+                dudy : meridional derivate of ubar on T point
+                dvdy : meridional derivate of vbar on T point
+                anousqrt : mean of (u-ubar)^2 on T point
+                anovsqrt : mean of (v-vbar)^2 on T point
+                anouv : mean of (u-ubar)*(v-vbar) on T point
+                bti  : transfert of energy for the barotropic instability.
+       
+      SEE ALSO :
+       cdfmoyuvwt, cdfbci, cdfnrjcomp, cdfkempemekeepe
+       
+ +

cdfbuoyflx

+ +
  usage : cdfbuoyflx  -t T-file [-r RNF-file] [-f FLX-file ] [-sss SSS-name]
+      ... [-sst SST-name] [-nc4] [-o output_file]  [-short ]
+       
+      PURPOSE :
+        Compute (or read) the heat and water fluxes components.
+        Compute (or read) the net heat and water fluxes.
+        Compute the buoyancy heat and water fluxes components.
+        Compute the net buoyancy fluxes.
+        Save sss and sst. 
+       
+      ARGUMENTS :
+        -t T-file   : netcdf file with temperature and salinity 
+       
+       
+      OPTIONS :
+        [ -r RNF-file ] : Specify a run-off file if runoff not in T-file 
+                          nor in FLX-file
+        [ -f FLX-file ] : Use this option if fluxes are not saved in gridT files
+        [ -sss SSS-name ] : Use this option if SSS variable name in T-file 
+                           differ from vosaline
+        [ -sst SST-name ] : Use this option if SST variable name in T-file 
+                           differ from votemper
+        [ -nc4 ] Use netcdf4 output with chunking and deflation level 1
+                This option is effective only if cdftools are compiled with
+                a netcdf library supporting chunking and deflation.
+        [ -o output_file ] Default is buoyflx.nc
+        [ -short ] With this option only save the buoyancy flux without 
+                   all the components of the flux.
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : buoyflx.nc
+          variables : 25 variables (2D) or 1 variable in case of -short option
+       
+      SEE ALSO :
+       
+       
+ +

cdfcensus

+ +
  usage :  cdfcensus T-file nlog [-zoom imin imax jmin jmax] ...
+                 ... [-klim kmin kmax]  [-full] [-bimg] ... 
+                 ... [-srange smin smax ds ] ...
+                 ... [-trange tmin tmax dt ] 
+       
+      PURPOSE :
+         Compute the volumetric water mass census: the ocean is divided in
+         T,S bins; the program gives the volume of water for each bin.
+         A sub-area can be specified, both horizontaly and vertically.
+         Temperature and salinity ranges can be also adapted, as well as the
+         width of the bins. Default values are provided. In order to attenuate
+         the huge maximum values, a log10 operator can be applied many times,
+         the number of filter passes being set on the command line.
+       
+      ARGUMENTS :
+        T-file  : netcdf file name for temperature and salinity
+        nlog    : number of log10 filter to perform. Can be 0.
+       
+      OPTIONS :
+        [-zoom imin imax jmin jmax] : define a model sub-area, in model 
+                                      coordinates
+        [-klim ik1 ik2            ] : set limits on the vertical.
+        [-srange smin smax ds     ] : define the size of the salinity bin
+                         defaut is : 25.0 40.0  0.020
+        [-trange tmin tmax dt     ] : define the size of the temperatude bin
+                         defaut is : -2.0 38.0  0.050
+        [-full                    ] : use for full step computation
+        [-bimg                    ] : output on bimg files (to be deprecated).
+       
+      REQUIRED FILES :
+        mesh_hgr.nc  and mesh_zgr.nc
+       
+      OUTPUT : 
+        - netcdf file : census.nc
+            variables : volcensus  (10^15 m3 )
+                        sigma0  (kg/m3 -1000 )
+                        sigma2  (kg/m3 -1000 )
+                        sigma3  (kg/m3 -1000 )
+        - bimg file   : According to options.
+ +

cdfchgrid

+ +
  usage : cdfchgrid -f IN-file -r REF-file -var IN-var [-nc4] [-o OUT-file] [-d]
+       
+      PURPOSE :
+        Build a new file on a refined grid, from a coarser grid, assuming that
+        the two grids are embedded, with common points (hence an odd scaling 
+        factor). Grid characteristics are hard wired in the code. Support for
+        ORCA025 --> ORCA12, eORCA025 --> eORCA12 is actually provided. Hooks 
+        are ready in the code for adding new conversion.
+        No interpolation, only copying value of a coarse grid cell, onto 
+        scale x scale cells of the output grid (scale is the refinement factor)
+       
+      RESTRICTION :
+        Caution for mask coherence !
+        This tool is only adapted for drowned field
+       
+      ARGUMENTS :
+        -f IN-file  : input Coarser-grid file
+        -r REF-file : Reference file used for identification of the output grid
+                should be of same geometry than the output file.
+        -var IN-var : input coarser-grid variable to be converted
+       
+      OPTIONS :
+        -nc4        : use netcdf4 chunking and deflation for the output file
+        -o OUT-file : specify output file name instead of cdfchgrid.nc
+        -d          : Display some debugging information 
+       
+      REQUIRED FILES :
+        none 
+       
+      OUTPUT : 
+        netcdf file : cdfchgrid.nc
+          variable : same name as in input file
+ +

cdfclip

+ +
  usage : cdfclip -f IN-file [-o OUT-file] -zoom imin imax jmin jmax [kmin kmax]
+       
+      PURPOSE :
+        Clip the input file according to the indices given in the
+        zoom statement. If no vertical zoomed area is indicated, 
+        the whole water column is considered.  This program is able
+        to extract data for a region crossing the E-W periodic boundary
+        of a global configuration. It does so if imax < imin.
+       
+      ARGUMENTS :
+        -f IN-file : specify the input file to be clipped
+        -zoom imin imax jmin jmax : specify the domain to be extracted.
+            If imin=imax, or jmin = jmax assume a vertical section either 
+            meridional or zonal.
+       
+      OPTIONS :
+        [-o OUT-file ] : use OUT-file instead of cdfclip.nc for output file
+                If used, -o option must be used before -zoom argument 
+        [kmin kmax ] : specify vertical limits for the zoom, in order to reduce
+                the extracted area to some levels. Default is to take the whole
+                water column.
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        netcdf file : cdfclip.nc This can be changed using -o option
+          variables : same as input variables.
+ +

cdfcmp

+ +
  usage : cmp_var -f1 IN-file1 -f2 IN-file2 -var IN-var ...
+      ... [-lev kmin kmax ] [-zoom imin imax jmin jmax] ...
+       
+      PURPOSE :
+         Find where IN-var is different between IN-file1 and IN-file2 
+         Options allow to restrict the finding to a sub area in space
+       
+      ARGUMENTS :
+        -f1 IN-file1 : input file1
+        -f2 IN-file2 : input file2
+        -var IN-var  : input variable
+       
+      OPTIONS :
+        [-lev kmin kmax ] : restrict to level between kmin and kmax. 
+        [-zoom imin imax jmin jmax] : restrict to sub area specified
+                                      by the given limits. 
+       
+      REQUIRED FILES :
+        none 
+       
+      OUTPUT : 
+        output is done on standard output.
+ +

cdfcofdis

+ +
  usage :  cdfcofdis mesh_hgr.nc mask.nc gridT.nc [-jperio jperio ] [-surf]
+       
+      PURPOSE :
+         Compute the distance to the coast and create a file with the Tcoast
+         variable, indicating the distance to the coast. This computation is don
+ e
+         for every model level, unless -surf option is used.
+       
+      ARGUMENTS :
+        HGR-file : name of the mesh_hgr file 
+        MSK-file : name of the mask file 
+        T-file   : netcdf file at T point.
+       
+      OPTIONS :
+        [ -jperio jperio ] : define the NEMO jperio variable for north fold 
+            condition. Default is  4.
+        [ -surf ] : only compute  distance at the surface.
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        netcdf file : dist.coast
+          variables : Tcoast (m)
+       
+       
+ +

cdfcoloc

+ +
  usage : cdfcoloc  -w root_weight -t gridT -trc TRC_file ...
+           ...  -u gridU -v gridV [-l field list ] [-h]
+        -w root_weight  : specify the root name of the weight files
+                          _T.bin, _U.bin, or _V.bin will be appended 
+                          to name if necessary.
+        -t gridT file   : name of gridT model file
+        -trc TRC file   : name of gridT model file
+        -d  diag file   : name of specific diagnostic file 
+        -u gridU file   : name of gridU model file
+        -v gridV file   : name of gridV model file
+        -b bathy file   : name of etopo like bathymetric file
+        -l field list   : list of fields to be colocated, separated by ','
+                          Default list is :U,V,Sx,Sy,H
+        -h              : Give the details of available field to colocate.
+      Return a column ascii file id dep fields()
+ mask.nc is required in local directory
+ coordinates.nc,mesh_zgr.nc are also required for slope computation
+ +

cdfconvert

+ +
  usage : cdfconvert CLIPPER_tag CLIPPER_Confcase
+       
+      PURPOSE :
+        Convert dimg files (CLIPPER like) to netcdf (DRAKKAR like).
+       
+      ARGUMENTS :
+        CLIPPER_tag      : a string such as y2000m01d15 for time identification.
+        CLIPPER_confcase : CONFIG-CASE of the files to be converted (eg ATL6-V6)
+       
+      REQUIRED FILES :
+         mesh_hgr.nc and mesh_zgr.nc
+       
+      OUTPUT : 
+        netcdf file : gridT, gridU, gridV files
+          variables : same as in standard NEMO output
+       
+      SEE ALSO :
+        cdfflxconv, cdfsstconv, cdfstrconv
+       
+ +

cdfcsp

+ +
  usage : cdfcsp list_of_files 
+       
+      PURPOSE :
+        Replace missing_values by 0 and update attribute
+       
+      ARGUMENTS :
+        The list of cdf file to process, all variables will be processed
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : same as input file (modified)
+          variables : same as input file
+ +

cdfcurl

+ +
  usage : cdfcurl -u U-file U-var -v V-file V-var -l levlist [-T] [-8]...
+            ... [-surf] [-overf] [-nc4] [-o OUT-file ]
+       
+      PURPOSE :
+        Compute the curl of a vector field, at a specified level.
+        If level is specified as 0, assume that the input files are
+        forcing files, presumably on A-grid. In this latter case, the
+        vector field is interpolated on the C-grid. In any case, the
+        curl is computed on the F-point (unless -T option is used).
+       
+      ARGUMENTS :
+        -u U-file U-var : file and variable name for zonal component
+        -v V-file V-var : file and variable name for meridional component
+        -l levlist    : levels to be processed. If set to 0, assume forcing file
+                 in input. Example of recognized syntax :
+                   -l "1,10,30"  or -l "1-20" or even -l "1-3,10-20,30-"
+                   -l  1 . Note that -l "3-" set a levlist from 3 to the bottom
+ 
+      OPTIONS :
+        -T : compute curl at T point instead of default F-point
+        -8 : save in double precision instead of standard simple precision.
+        -surf : work with single level C-grid (not forcing)
+        -overf : store the ratio curl/f where f is the coriolis parameter
+        -nc4 : use netcdf4 output with chunking and deflation 1
+        -o OUT-file : specify output file name instead of curl.nc
+       
+      REQUIRED FILES :
+         mesh_hgr.nc
+       
+      OUTPUT : 
+        netcdf file : curl.nc
+          variables : socurl or socurlt (if -T option), units : s^-1
+             or socurloverf, no units (if -overf option)
+ +

cdfdegradt

+ +
  usage : cdfdegradt IN-Tfile IN-var ri rj [i0 j0]
+        ... [-full]
+        
+      PURPOSE :
+        Degrad the horizontal resolution of NEMO T-grid ouput,       
+        for each z-level and time step, with a ratio of ri along     
+        x direction and rj along y direction. If specified, the input
+        grid is considered starting from the indices i0 and j0.      
+       
+      ARGUMENTS :
+        IN-Tfile  : netcdf T-file.
+        IN-var    : name of netcdf variable to work with
+        ri        : degradation ratio for x-direction   
+        rj        : degradation ratio for y-direction   
+       
+      OPTIONS : 
+        [i0 j0] : spatial indices from where starting the procedure   
+                  of degradation.                                    
+        [-full] : flag for full steps grid, instead of default partial
+                  steps.
+       
+      REQUIRED FILES :
+        Files mesh_hgr.nc, mesh_zgr.nc, mask.nc
+       
+      OUTPUT : 
+        netcdf file : degraded_cdfvar.nc 
+        netcdf file : flsdc.nc
+       
+ +

cdfdegradu

+ +
  usage : cdfdegradu IN-Ufile IN-var ri rj [i0 j0]
+        ... [-full]
+        
+      PURPOSE :
+        Degrad the horizontal resolution of NEMO U-grid ouput,       
+        for each z-level and time step, with a ratio of ri along     
+        x direction and rj along y direction. If specified, the input
+        grid is considered starting from the indices i0 and j0.      
+       
+      ARGUMENTS :
+        IN-Ufile  : netcdf U-file.
+        IN-var    : name of netcdf variable to work with
+        ri        : degradation ratio for x-direction   
+        rj        : degradation ratio for y-direction   
+       
+      OPTIONS : 
+        [i0 j0] : spatial indices from where starting the procedure   
+                  of degradation.                                    
+        [-full] : flag for full steps grid, instead of default partial
+                  steps.
+       
+      REQUIRED FILES :
+        Files mesh_hgr.nc, mesh_zgr.nc, mask.nc
+       
+      OUTPUT : 
+        netcdf file : degraded_cdfvar.nc 
+        netcdf file : flsdc.nc
+       
+ +

cdfdegradv

+ +
  usage : cdfdegradv IN-Vfile IN-var ri rj [i0 j0]
+        ... [-full]
+        
+      PURPOSE :
+        Degrad the horizontal resolution of NEMO V-grid ouput,       
+        for each z-level and time step, with a ratio of ri along     
+        x direction and rj along y direction. If specified, the input
+        grid is considered starting from the indices i0 and j0.      
+       
+      ARGUMENTS :
+        IN-Vfile  : netcdf V-file.
+        IN-var    : name of netcdf variable to work with
+        ri        : degradation ratio for x-direction   
+        rj        : degradation ratio for y-direction   
+       
+      OPTIONS : 
+        [i0 j0] : spatial indices from where starting the procedure   
+                  of degradation.                                    
+        [-full] : flag for full steps grid, instead of default partial
+                  steps.
+       
+      REQUIRED FILES :
+        Files mesh_hgr.nc, mesh_zgr.nc, mask.nc
+       
+      OUTPUT : 
+        netcdf file : degraded_cdfvar.nc 
+        netcdf file : flsdc.nc
+       
+ +

cdfdegradw

+ +
  usage : cdfdegradw IN-Wfile IN-var ri rj [i0 j0]
+        ... [-full]
+        
+      PURPOSE :
+        Degrad the horizontal resolution of NEMO W-grid ouput,       
+        for each z-level and time step, with a ratio of ri along     
+        x direction and rj along y direction. If specified, the input
+        grid is considered starting from the indices i0 and j0.      
+       
+      ARGUMENTS :
+        IN-Wfile  : netcdf W-file.
+        IN-var    : name of netcdf variable to work with
+        ri        : degradation ratio for x-direction   
+        rj        : degradation ratio for y-direction   
+       
+      OPTIONS : 
+        [i0 j0] : spatial indices from where starting the procedure   
+                  of degradation.                                    
+        [-full] : flag for full steps grid, instead of default partial
+                  steps.
+       
+      REQUIRED FILES :
+        Files mesh_hgr.nc, mesh_zgr.nc, mask.nc
+       
+      OUTPUT : 
+        netcdf file : degraded_cdfvar.nc 
+        netcdf file : flsdc.nc
+       
+ +

cdfdifmask

+ +
  usage : cdfdifmask  mask1 mask2
+      PURPOSE :
+        Compute the difference between 2 mask files.
+       
+      ARGUMENTS :
+        mask1, mask2 : model files to be compared.
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : mask_diff.nc
+        variables : tmask, umask, vmask, fmask
+ +

cdfdiv

+ +
  usage : cdfdiv -u U-file U-var -v V-file V-var -l levlist  [-8]...
+            ... [-surf] [-overf] [-full] [-o OUT-file ]
+       
+      PURPOSE :
+        Compute the divergence of the flow from the U and V velocity components
+       
+      ARGUMENTS :
+        -u U-file U-var : file and variable name for zonal component
+        -v V-file V-var : file and variable name for meridional component
+        -l levlist    : levels to be processed. If set to 0, assume forcing file
+                 in input. Example of recognized syntax :
+                   -l "1,10,30"  or -l "1-20" or even -l "1-3,10-20,30-"
+                   -l  1 . Note that -l "3-" set a levlist from 3 to the bottom
+ 
+      OPTIONS :
+        -8 : save in double precision instead of standard simple precision.
+        -surf : work with single level C-grid (not forcing)
+        -overf : store the ratio curl/f where f is the coriolis parameter
+        [ -full ] : in case of full step configuration. Default is partial step.
+        -o OUT-file : specify output file name instead of curl.nc
+       
+      REQUIRED FILES :
+         mesh_hgr.nc mesh_zgr.nc
+       
+      OUTPUT : 
+        netcdf file : curl.nc
+          variables : div units : s^-1
+                or divoverf, no units (if -overf option)
+ +

cdfeddyscale

+ +
  usage : cdfeddyscale mean-cdfeddyscale_pass1-file
+       
+      PURPOSE :
+      Compute: -the Taylor scale or large scale eddy (lambda1)
+               -the small scale eddy (lambda2)
+               -and the inertial range (scar) on F-points
+       
+      lambda1 = sqrt(mean Kinetic Energie / Enstrophy)
+      lambda2 = sqrt(Enstrophy / Palinstrophy)
+      Inertial Range    = lambda1 / lambda2
+       
+      Enstrophy = 1/2 * ( mean((RV)^2) )
+      Palinstrophy = 1/2 * ( mean((dx(RV))^2 + (dy(RV))^2) )
+       
+      ARGUMENTS :
+      mean-cdfeddyscale_pass1-file : mean of the terms compute by
+      the program cdfeddyscale_pass1
+       
+      OUTPUT : 
+        netcdf file : lambda.nc
+          variables : solambda1 (m), solambda2 (m), soscar
+       
+      SEE ALSO :
+        cdfeddyscale_pass1 
+ +

cdfeddyscale_pass1

+ +
  usage : cdfeddyscale_pass1 U-file V-file U-var V-var lev
+       
+      PURPOSE :
+      Compute: - the curl and the square of curl on F-points,
+               - the gradient components of the curl and the
+                 square of the gradient components on UV-points,
+               - the square of velocity components on UV-points,
+      for given gridU gridV files and variables. These variables are required
+      for computing eddy scales with cdfeddyscale. Therefore this program is
+      the first step in computing the eddy scales.
+      
+         These terms will used to compute the Taylor scale or large
+      scale eddy (lambda1) and the small scale eddy (lambda2) in
+      the program cdfeddyscale.
+       
+      ARGUMENTS :
+        U-file : zonal component of the vector field.
+        V-file : meridional component of the vector field.
+        U-var  : zonal component variable name
+        V-var  : meridional component variable name.
+        lev    : level to be processed. If set to 0, assume forcing file 
+                 in input.
+       
+      REQUIRED FILES :
+         mesh_hgr.nc
+       
+      OUTPUT : 
+        netcdf file : lambda_int.nc
+          variables : socurl (s^-1), socurl2 (s^-2)
+          variables : sodxcurl, sodycurl (s^-1.m^-1)
+          variables : sodxcurl2, sodycurl2 (s^-2.m^-2)
+          variables : vozocrtx2, vomecrty2 (m^2.s^-2)
+          WARNING : variables in the output file are not located at the same
+                  C-grid point.
+       
+      SEE ALSO : 
+         cdfeddyscale
+ +

cdfeke

+ +
  usage : cdfeke U-file [U2-file]  V-file [V2-file] T-file [-mke ] [-nc4] ...
+             ... [-o output_file]
+       
+      PURPOSE :
+         Compute the Eddy Kinetic Energy from previously computed
+         mean values and mean squared values of velocity components.
+       
+      ARGUMENTS : both 'General Use' or 'Reduced Use' are acceptable
+       * General Use: 5 files are given in argument, and EKE is computed
+        U-file  : gridU type file with mean U component.
+        U2-file : gridU2 type file with mean U2 component.
+        V-file  : gridV type file with mean V component.
+        V2-file : gridV2 type file with mean V2 component.
+        T-file  : any gridT or gridT2 (smaller) file, used for EKE header.
+        
+       * Reduced Use: no U2/V2 file, only MKE is computed from U and V file.
+        U-file  : gridU type file with mean U component.
+        V-file  : gridV type file with mean V component.
+        T-file  : any gridT or gridT2 (smaller) file, used for MKE header.
+              
+      OPTION :
+        -mke  : output MKE field together with EKE. 
+        -nc4  : allow netcdf4 output with compression and chunking.
+        -o output file : specify output file name instead of eke.nc
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : eke.nc unless -o option in use.
+          variables : voeke (m2/s)
+          variables : vomke (m2/s) if required
+ +

cdfenstat

+ +
  usage : cdfenstat list_of_model_files [-spval0] [-nc4] [-v4d] -o OUT-file]
+      PURPOSE :
+        Compute the time average of a list of files given as arguments.
+        This program handle multi time-frame files is such a way that
+        the output files are also multi time-frame, each frame being
+        the average across the files given in the list.
+        
+        The program assume that all files in the list are of same
+        type (shape, variables , and number of time frames ). 
+        For some variables, the program also compute the time average 
+        of the squared variables, which is used in other cdftools 
+        (cdfeke, cdfrmsssh, cdfstdevw, cdfstddevts ... The actual variables
+        selected for squared average are :
+          - vozocrtx
+          - vomecrty
+          - vovecrtz
+          - sossheig
+        This selection can be adapted with the nam_cdf_namelist process.
+        (See cdfnamelist -i for details).
+        If you want to compute the average of already averaged files,
+        consider using cdfmoy_weighted instead, in order to take into
+        account a particular weight for each file in the list.
+       
+      ARGUMENTS :
+        A list of similar model output files. 
+       
+      OPTIONS :
+        [ -spval0 ] :  set missing_value attribute to 0 for all output
+                variables and take care of the input missing_value.
+                This option is usefull if missing_values differ from files 
+                to files; it was formely done by cdfmoy_chsp).
+        [ -nc4 ] : output file will be in netcdf4, with chunking and deflation
+        [ -v4d ] : uses 4D arrays for improved performance (use more memory !)
+        [ -o OUT-file ] : specify a name for output file instead of cdfmoy.nc
+       
+      REQUIRED FILES :
+        none 
+       
+      OUTPUT : 
+        netcdf file : cdfmoy.ncunless -o option in use
+        variables : are the same than in the input files. Standard Dev are 
+         named  stdev_<variable>
+ +

cdfets

+ +
  usage : cdfets  T-file 
+       
+      PURPOSE :
+        Compute the eddy time scale, and a proxy for rossby radius.
+        The Rossby radius is computed as the vertical integral of N2
+        (Brunt Vaissala frequency), scaled by |f|*pi
+        The Eddy Time Scale is the ratio N/|grad B| where N is the square
+        root of N2 and |grad B| is the module of the horizontal buoyancy
+        gradient. B is the buoyancy computed as B=-g rho/rho0.
+       
+      ARGUMENTS :
+        T-file : netcdf input file for temperature and salinity (gridT).
+       
+      REQUIRED FILES :
+         mesh_hgr.nc, mesh_zgr.nc
+       
+      OUTPUT : 
+        netcdf file : ets.nc
+          variables : voets (days)  and sorosrad (m)
+ +

cdffindij

+ +
  usage :   cdffindij  xmin xmax ymin ymax  [-c COOR-file] [-p point_type]...
+                     [-f list_file ] [-d decriptor] [-o output_file] [-a] [-l]
+       
+      PURPOSE :
+        Return the model limit (i,j space) of the geographical window 
+        given on the input line. If using -f list_file option, then the output
+        is just a single point, not a window, and xmin, xmax, ymin ymax are not
+        used at all.
+       
+      ARGUMENTS :
+        xmin xmax ymin ymax : geographical limits of the window, in lon/lat
+        (relevant only if -f option not used.)
+       
+      OPTIONS :
+        [-c COOR-file ] : specify a particular coordinate file
+                      default is coordinates.nc
+        [-p point type] : specify the point on the C-grid (T U V F)
+                      default is F
+        [-f list_file ] : list_file is an ascii file describing the location
+                 (one per line) of geographical points to be translated to 
+                 model (i,j) point. Unless specified with -d option, this list
+                 file contains Longitude (X) Latitudes (Y) information.
+        [-d descriptor] : descriptor is a string indicating the position of
+                 X and Y coordinates for the lines of list_file. Default value
+                 of the descriptor is 'XY'. Any other field on the line is 
+                 indicated with any characterm except X or Y. Example of valid
+                 descriptor : 'oXYooo' or 'ooYabcdfXooo' 
+        [-a  ] : With this option, output is similar to input with I,J appended
+                 to the corresponding line.
+        [-l  ] : With this option, also output the exact model longitude and 
+                 latitude of the I,J point.
+        [-o output_file] : write output in ascii output_file instead of standard
+                 output.
+       
+      REQUIRED FILES :
+        coordinates.nc or the specified coordinates file.
+       
+      OUTPUT : 
+        Output is done on standard output.
+ +

cdffixtime

+ +
  usage : cdffixtime  -f IN-file -i initial date [-t tag] [-dt freq] ... 
+                ...  [-keep ] [-leap] [ -noleap]
+       
+      PURPOSE :
+         Change time_counter in file to set it according to drakkar rule,
+         time_counter attibutes 'units' and 'time_origin' are ajusted.
+          * units are 'seconds since yyyy-mm-dd hh:mm:ss' 
+          * time_origin is set to 'yyyy-MMM-dd hh:mm:ss', MMM represents a
+         litteral abbreviation for the month (eg: JAN FEB MAR ...)
+         Once fixed, the time_counter indicates the middle of the output 
+         interval (in case of averaged output, of course).
+       
+      ARGUMENTS :
+        -f IN-file     : specify the file whose time_counter need adjustment
+        -i inital date : indicate the time origin in a fixed 2 words format
+                    yyyy-mm-dd hh:mm:ss ( eg: 1956-05-16 04:30:00 )
+       
+      OPTIONS :
+        [ -t tag ]  : supply a time tag corresponding to the file. If not
+                      supplied, tag is taken from the name of the input file
+                      assuming DRAKKAR convention ( CONFIG-CASE_tag_xxxx.nc )
+        [ -dt freq] : number of days between model output [ 5d ]
+        [-leap ]    : assume a calendar with leap years
+        [-noleap ]  : assume a calendar without leap years (default)
+        [-keep ]    : keep the actual value of time_counter, adjust time_counter
+                     attributes only;
+       
+      REQUIRED FILES :
+        none 
+       
+      OUTPUT : 
+        netcdf file : Input file is modified (only attributes)
+       
+ +

cdfflxconv

+ +
  Usage : cdfflxconv YEAR config 
+     Output 6 cdf files : for emp, qnet, qsr, sst, taux, tauy with standard var 
+ name :
+         sowaflup, sohefldo, soshfldo, sst, sozotaux, sometauy 
+     coordinates.diags ( clipper like) is required in current dir 
+ +

cdffracinv

+ +
  usage : cdffracinv TRC-file [-inv INV-name]
+       
+      PURPOSE :
+        Compute the fraction of inventory for passive tracers, which is 
+        the ratio between inventory at a grid point and the total inventory.
+       
+      ARGUMENTS :
+        TRC-file : netcdf file with tracer inventory.
+       
+      OPTIONS :
+        -inv INV-name  : name of the netcdf name for inventory [ invcfc ]
+       
+      REQUIRED FILES :
+        none ... but : horizontal weight to be coded ?
+       
+      OUTPUT : 
+        netcdf file : fracinv.nc
+          variables : fracinv
+ +

cdffwc

+ +
  usage : cdffwc IN-file BASIN-var1,var2,.. [-o OUT-file] [-sref REFSAL]
+                 [-full] [-accum] [-ssh]
+       
+      PURPOSE :
+        Computes the freshwater content in a given basin from top
+        to bottom for each layer. Can handle full step configuration
+        using the -full option.
+       
+      ARGUMENTS :
+         IN-file            : netcdf input file.
+         BASIN-var1,var2,.. : Comma separated list of sub-basin variables
+                              to process.
+         OUT-file           : use specified output file instead of <IN-var>.nc
+       
+      OPTIONS :
+         -full  : for full step computation 
+         -accum : compute accumulated content from top to bottom
+         -ssh   : take ssh into account for surface layer
+         -sref  : reference salinity (= 34.7 by deafult)
+       
+      REQUIRED FILES :
+        mesh_zgr.nc, mesh_hgr.nc and subbasins.nc and mask.nc
+       
+      OUTPUT : 
+        netcdf file :  fwc.nc (or specified with -o option)
+          variables :  fwc_BASIN, where BASIN was set by argument BASIN-var*
+                       (cAsE sensitive !)
+       
+ +

cdfgeo-uv

+ +
  usage : cdfgeo-uv -f T-file [-o UOUT-file VOUT-file ] [ -C option ]
+       
+      PURPOSE :
+          Compute the geostrophic velocity component from the gradient 
+        of the SSH read in the input file. 
+          Without any -C option, the zonal component is located on a 
+        C-grid V point, the meridional one is located on C-Grid U point.
+          See the use of the -C option in order to have (Ugeo, Vgeo) 
+        at (U,V) points on the C-grid.
+       
+      ARGUMENTS :
+       -f  T-file : netcdf file with SSH (input).
+       
+      OPTIONS :
+       -o UOUT-file VOUT-file: specify the names of the output files.
+                 Default are: ugeo.nc vgeo.nc.
+       -C option : Using this option, the output velocity component are
+                at the correct (U,V) points on the C-grid
+                2 options are available :
+               option = 1 : SSH is interpolated on the F point prior derivation
+               option = 2 : Ugeo and Vgeo are interpolated on the C-grid after
+                      derivation
+                  Both option should give very similar results...
+   
+      REQUIRED FILES :
+         mesh_hgr.nc and mesh_zgr.nc
+       
+      OUTPUT : 
+        - netcdf file : ugeo.nc (default)
+            variables : vozocrtx
+            Unless -C option is used : 
+              *** CAUTION:  this variable is located on V-point ***
+        - netcdf file : vgeo.nc (default)
+            variables : vomecrty
+            Unless -C option is used : 
+              *** CAUTION:  this variable is located on U-point ***
+ +

cdfgeostrophy

+ +
  usage : cdfgeostrophy T-file
+       
+      PURPOSE :
+        Compute the geostrophic velocity component from the pressure gradient 
+        computed from SSH and in-situ density (T,S of input file) 
+       
+      WARNING : USE AT YOUR OWN RISKS
+       
+      ARGUMENTS :
+        T-file : netcdf file with SSH, T and S.
+       
+      REQUIRED FILES :
+         mask.nc mesh_hgr.nc and mesh_zgr.nc
+       
+      OUTPUT : 
+        - netcdf file : ugeo.nc
+            variables : vozocrtx
+        - netcdf file : vgeo.nc
+            variables : vomecrty
+ +

cdfgradT

+ +
  usage : cdfgradT T-file [S-file] 
+       
+      PURPOSE :
+         Compute horizontal and vertical gradient of temperature and salinity.
+       Results are saved at U point for zonal gradient, V point for meridional
+       gradient and W for vertical gradient.
+       
+      ARGUMENTS :
+        T-file : File with votemper and vosaline variables
+            If vosaline not in T-file give a second name for S-file.
+       
+      OPTIONS :
+        S-file : File with vosaline variable if not in T file
+       
+      REQUIRED FILES :
+        mesh_hgr.nc mask.nc and mesh_zgr.nc
+       
+      OUTPUT : 
+        netcdf file : gradT.nc
+                     6  variables : 
+               vozogradt, vomegradt, vovegradt : 3 component of the temperature
+                           located respectively at U, V and W points
+               vozograds, vomegrads, vovegrads : 3 component of the salinity
+                           located respectively at U, V and W points
+       
+      SEE ALSO :
+       
+       
+ +

cdfhdy

+ +
  usage : cdfhdy T-file level1 level2
+       
+      PURPOSE :
+         Compute dynamical height anomaly field from gridT file.
+         It is computed as the integral of (1/g) *10e4 * sum [ delta * dz ]
+             where delta = (1/rho - 1/rho0)
+             10e4 factor is for the conversion decibar to pascal.
+       
+      ARGUMENTS :
+         T-file  : netcdf file with temperature and salinity
+         level1  : upper limit for vertical integration (usually 1 = surface)
+         level2  : lower limit for vertical integration.
+       
+      REQUIRED FILES :
+        mask.nc and mesh_zgr.nc
+       
+      OUTPUT : 
+        netcdf file : cdfhdy.nc
+          variables : sohdy (m)
+ +

cdfhdy3d

+ +
  usage : cdfhdy3d T-file
+       
+      PURPOSE :
+         Compute dynamic height anomaly from T-file given as argument.
+       
+      ARGUMENTS :
+        T-file : netcdf file with temperature and salinity.
+       
+       
+      REQUIRED FILES :
+         mask.nc and mesh_zgr.nc
+       
+      OUTPUT : 
+        netcdf file : cdfhdy3d.nc
+          variables : vohdy ( m )
+       
+      SEE ALSO :
+       cdfhdy
+       
+ +

cdfheatc

+ +
  usage :  cdfheatc  T-file ...
+     ... [imin imax jmin jmax kmin kmax] [-full] 
+       
+      PURPOSE :
+         Computes the heat content in the specified area (Joules)
+         A sub-domain can be specified in option.
+       
+      ARGUMENTS :
+        T-file : a file with temperature and salinity
+       
+      OPTIONS :
+        [imin imax jmin jmax kmin kmax] : limit of a sub domain where
+                       the heat content will be calculated.
+                    - if imin = 0 then ALL i are taken
+                    - if jmin = 0 then ALL j are taken
+                    - if kmin = 0 then ALL k are taken
+        [-full ] : assume full step model output instead of default
+                   partial steps.
+        [-mxloption ] : pass 1 to compute only in the mixed layer, -1 to exclude
+                        it from the calculations 
+       
+      REQUIRED FILES :
+        Files mesh_hgr.nc, mesh_zgr.nc and mask.nc
+       
+      OUTPUT : 
+        netcdf file : to be done ....
+        Standard output
+ +

cdfhflx

+ +
  usage : cdfhflx  T-file 
+       
+      PURPOSE :
+        Computes the Meridional Heat Transport (MHT) from surface heat fluxes,
+        in function of the latitude.
+        If a sub-basin file is available, MHT is computed for each sub-basin.
+        Note that the latitude is in fact a line of constant J coordinate, not
+        a true parallel, if the model grid is distorted as in the northern most
+        part of ORCA configurations.
+       
+      ARGUMENTS :
+        T-file : a file with heat fluxes (gridT). 
+       
+      REQUIRED FILES :
+        Files mesh_hgr.nc, new_maskglo.nc and mask.nc.
+        If new_maskglo.nc is not available, only global MHT is computed.
+       
+      OUTPUT : 
+        ASCII file  : hflx.out
+        netcdf file : cdfhflx.nc
+          variables : hflx_glo, [hflx_atl, hflx_inp, hflx_pac, hflx_ind]
+ +

cdfhgradb

+ +
  usage : cdfhgradb -t T-file [-s S-file] [-nc4 ] [-o OUT-file] ...
+                    ...  [-sal SAL-name]  [-tem TEMP-name] 
+       
+      PURPOSE :
+         Compute the norm of the horizontal buoyancy gradient.
+       Results are saved at T points.
+       
+      ARGUMENTS :
+        -t T-file : File with votemper and vosaline variables
+            If vosaline not in T-file use -s option.
+           Note that salinity and/or temperature variables name can be changed
+           with -sal and/or -tem options, respectively.
+       
+      OPTIONS :
+       [-s S-file ] : File with vosaline variable if not in T file
+       [-nc4      ] : use netcdf4 chunking and deflation on output 
+       [-o output file] : specify the name of output file instead of 
+                 default name hgradb_gridT.nc
+       [-sal SAL-name] : specify the name of salinity variable
+       [-tem TEM-name] : specify the name of temperature variable
+       
+      REQUIRED FILES :
+        mesh_hgr.nc mask.nc and mesh_zgr.nc
+       
+      OUTPUT : 
+        netcdf file : hgradb_gridT.nc ( unless specified with -o option)
+                     1  variables : 
+               vohgradb: norm of the horizontal buoyancy gradient at t-point
+       
+      SEE ALSO :
+         cdfbuoyflx  
+       
+ +

cdficediags

+ +
  usage : cdficediag ICE-file [-lim3] 
+       
+      PURPOSE :
+         Compute the ice volume, area and extent for each hemisphere.
+         The extent is computed in a similar way to NSIDC for easy 
+         comparison : the extent is the surface of the grid cells covered
+         by ice when the ice concentration is above 0.15
+       
+         For compatibility with previous version, another estimate of 
+         the extend is computed using grid cell surfaces weighted by the
+         ice concentration, but it will be deprecated soon.
+       
+      ARGUMENTS :
+        ICE-file : netcdf icemod file (LIM2 by default)
+       
+      OPTION :
+        [-lim3 ] : LIM3 variable name convention is used
+        [-o OUT-file ] : specify output file instead of icediags.nc
+       
+      REQUIRED FILES :
+         mesh_hgr.nc and mask.nc
+       
+      OUTPUT : 
+        netcdf file : icediags.nc
+          variables : [NS]Volume  (10^9 m3 )
+                      [NS]Area    (10^9 m2 )
+                      [NS]Extent  (10^9 m2 ) -- obsolete --
+                      [NS]Exnsidc (10^9 m2 )
+                N = northern hemisphere
+                S = southern hemisphere
+        standard output
+ +

cdfimprovechk

+ +
  usage : cdfimprovechk IN-var OBS-file REF-file TST-file
+       
+      PURPOSE :
+         Estimate the improvement/deterioration of a test run,
+         compared with a reference run relative to some observations
+         This program computes the quantity zchk= ( REF - TEST )/(REF - OBS)
+         Where 0 < zchk <= 1, the TST is better than the reference
+         Where 1 < zchk, the TST  was corrected in the right sense but too much
+         Where  zchk < 0, the TST  was corrected was corrected in the wrong way.
+       
+      ARGUMENTS :
+         IN-var    : netcdf input variable
+         OBS-file  : netcdf observation file
+         REF-file  : netcdf reference file
+         TST-file  : netcdf test file
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        netcdf file : chk.nc
+          variables : same as input variable.
+ +

cdfinfo

+ +
  usage : cdfinfo 'model cdf file' [-dep dep] 
+       
+      PURPOSE :
+         Gives very basic information about the file given in arguments.
+       
+      ARGUMENTS :
+         model output file in netcdf.
+       
+      OPTIONS :
+         [-dep depth ] : return the nearest k index corresponding to depth 
+       
+      OUTPUT : 
+         On standard ouput, gives the size of the domain, the depth 
+         dimension name, the number of variables.
+       
+ +

cdfisf_fill

+ +
  usage : cdfisf_fill  -f ISF-file -v ISF-var -l ISF-list [-nc4 ] [-o OUT-file]
+       
+      PURPOSE : Build a nc file with a single value for each pool around a list
+                of given point. A warning is given when neighbouring ice-shelves
+                cannot be discriminated (no gap in between). In this case, hand
+                edit on the ISF-file is required.
+       
+      ARGUMENTS : 
+          -f ISF-file : netcdf file  which contains the ice shelf draft variable
+                      (mesh_zgr is OK). It is used as a mask, only.
+          -v ISF-var  : variable name corresponding to the ice shelf draft or 
+                       ice shelf level
+          -l ISF-list : text file containing at least the following information:
+  
+                  1  NAME    LON  LAT I  J 
+                  ...             
+                  i  NAMEi   LON  LAT I  J 
+                  ...             
+                  EOF             
+                  No NAME  X    Y   I  J 
+       
+      OPTIONS : 
+           -nc4 : use NetCDF4 chunking and deflation for the output
+           -o OUT-file : specify the name of the output file instead of fill.nc
+                  This file will be one of the input file for cdfmkforcingisf 
+                  as the ISF-fill_file 
+       
+      OUTPUT : 
+               netcdf file : fill.nc 
+               variable : sofillvar contains for all points in ice shelf NAME 
+                          the value -i (negative value)
+               text file : <ISF-list>_zmin_zmax.txt 
+                         this output file is similar to <ISF-list> but updated
+                         with the minimum and maximul value of ice-draft for 
+                         each shelf.
+       
+      SEE ALSO : 
+            cdfisf_forcing,  cdfisf_rnf 
+       
+ +

cdfisf_forcing

+ +
  usage : cdfisf_forcing -f ISF-fill_file  -v ISF-fill_var -l ISF-listfile 
+              -m ISF-poolmask [-vm ISF-poolmask_variable] [-p PATTERN-file] 
+             [-vp PATTERN-variable] [-nc4] [-o OUT-file ]
+       
+      PURPOSE : 
+          Build basal melting rate file used in NEMO ISF when nn_isf=4 
+       
+      ARGUMENTS : 
+           -f ISF-fill_file : file built by cdfisf_fill (all the ice shelves 
+                              are tagged with an id)
+           -v ISF-fill_var  : name of fill variable to use in ISF-fill_file
+           -l ISF-listfile : text file used to build the ISF-fill_file. 
+                             Only the last variable on each line is used (GT/y)
+       
+      OPTIONS :
+           -p PATTERN-file : specify the file use for patterns. 
+                             [ default : isfpattern.nc ]
+           -vp PATTERN-variable : specify the name of the pattern variable. 
+                             [ default : sowflisf ]
+           -vm ISF-poolmask_variable : specify the name of the variable used 
+                  for masking the pools. [ default : isfpoolmask ]
+           -nc4 : use netcdf4 chunking and deflation
+           -o OUT-file : specify output filename. [ default : isfforcing.nc ]
+               
+      REQUIRED FILES : 
+            mesh_zgr.nc mesh_hgr.nc,
+            isfpattern.nc (ie reference file used to define the isf melting 
+                  pattern), unless -p option is used to give different name.
+       
+      OUTPUT :
+          netcdf file : isfforcing.nc unless specified with -o option
+          variable : sofwfisf 
+       
+      SEE ALSO : cdfisf_fill, cdfisf_rnf, cdfisf_poolchk
+       
+ +

cdfisf_poolchk

+ +
  usage : cdfisf_poolchk -m MASK-file -d ISFDRAFT-file [-v ISFDRAFT-variable]
+             [-nc4] [-o OUT-file]
+       
+      PURPOSE :
+        Produce a netcdf mask file with 1 everywhere, except for points 
+        not connected to the open ocean (Frequent for cavities below 
+        ice-shelves), which have 0 value. Both 3D and 2D variables are
+        created, the 2D variables beiing used for cdfisf_forcing.
+       
+      ARGUMENTS :
+        -m MASK-file : name of the input NEMO mask file, with tmask variable.
+        -d ISFDRAFT-file : name of the file with ice shelf draft.
+       
+      OPTIONS :
+        -v ISFDRAFT-variable: name of the variable for ice shelf draft.
+        -nc4 : use netcdf4 with chunking and deflation for the output.
+        -o OUT-file : name of the output file. [Default : poolmask.nc ]
+       
+      REQUIRED FILES :
+        Only the mask file given as argument
+       
+      OUTPUT : 
+        netcdf file : poolmask.nc unless -o option is used.
+          variables : tmask_pool3d, tmask_pool2d
+       
+      SEE ALSO :
+       cdfisf_fill, cdfisf_forcing, cdfisf_rnf
+       
+ +

cdfisf_rnf

+ +
  usage : cdfisf_rnf -f ISF-fill-file -v ISF-fill_var -l ISF-listfile -w width 
+      [-b BATHY-file] [-vb BATHY-var] [-i ISFDRAFT-file] [-vi ISFDRAFT-variable]
+      [-nc4] [-o OUT-file ]
+       
+      PURPOSE :
+         Build a netcdf file runoff file using the basal melting of the 
+         ice-shelves. This netcdf file is intented to be used with NEMO when
+         nn_isf namelist parameter is set to 3.
+       
+      ARGUMENTS :
+           -f ISF-fill_file : file built by cdffill (all the ice shelves are
+                              tagged with an id)
+           -v ISF-fill_var  : name of fill variable to use in ISF-fill_file
+           -l ISF-list : Text file with the melting rate (GT/y) given for
+                each ice shelf.
+           -w width : specify the width (in grid points) on which the run-off
+                will be applied.
+       
+      OPTIONS :
+           -b BATHY-file : give name of bathy file.
+                       [ default : bathy.nc ]
+           -vp BATHY-var : give name of bathy variable.
+                       [ default : Bathymetry ]
+           -i ISFDRAFT-file : give name of isf_draft file.
+                       [ default : isf_draft.nc ]
+           -vi ISFDRAFT-var : give name of isf_draft variable.
+                       [ default : isf_draft ]
+           -nc4 : Use this option to have netcdf4 output file, with chunking
+                and deflation.
+           -o OUT-file : Specify the name of the output file instead of 
+                the default name rnfisf.nc
+       
+      REQUIRED FILES :
+        mesh_hgr.nc and all files specified on the command line
+       
+      OUTPUT : 
+        netcdf file : rnfisf.nc unless -o option used
+          variables : sozisfmax (m), sozisfmin(m), sofwfisf (kg/m2/s)
+       
+      SEE ALSO :
+        cdfisf_fill, cdfisf_forcing, cdfisf_poolchk
+       
+ +

cdfisopsi

+ +
  usage : cdfisopsi ref_level sigma_ref gridT 
+       Compute  a geostrophic streamfunction
+       projected  on an isopycn.
+          ref_level = reference level for pot. density
+          sigma_ref = density level to project on
+          gridT     = input file for temperature and salinity
+   
+          Output on isopsi.nc variable soisopsi
+          Depths are taken from input file 
+          requires mesh_hgr.nc and mesh_zgr.nc
+ +

cdfkempemekeepe

+ +
 usage : cdfkempemekeepe file
+      Produce a cdf file transfertst1t3.nc with wT and anowT variables
+      file is from cdfmoyuvwt
+      the mean must have been computed on a period long enough
+      for the statistics to be meaningful
+                          
+ +

cdflap

+ +
  usage : cdflap IN-file IN-var  IN-type [-overf2] [-nometric]
+       
+      PURPOSE :
+        Compute the Laplacian of the variable IN-var in file IN-file
+        Assumes that the data are on a C-grid model (as NEMO) 
+       
+      ARGUMENTS :
+        IN-file : netcdf file in input
+        IN-var  : name of the variable to process 
+        IN-TYPE : Position of the variable on the C-grid [ T U V F ]
+       
+      OPTIONS :
+        -overf2 : save laplacien/f/f*g (where f is the local coriolis 
+             parameter, and g is the accelaration due to gravity --9.81 m/s2-- )
+             For the SSH field, this is a proxy for geostrophic vorticity
+        -nometric : compute laplacian without considering metrics 
+       
+      REQUIRED FILES :
+        mesh_hgr.nc mesh_zgr.nc and mask.nc
+       
+      OUTPUT : 
+        netcdf file : lap.nc
+          variables : lap<var> (unit/m2)
+        if option -overf2 is used, netcdf file is lapoverf2.nc and 
+        variable is lap<var>overf2
+ +

cdflinreg

+ +
  usage : cdflinreg 'list of model files' 
+       
+      PURPOSE :
+         Compute the linear regression coefficients for a bunch of
+         input files. 
+       
+      ARGUMENTS :
+        A list of netcdf model file of same kind
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        netcdf file : linreg.nc
+          variables : for each input variables, there are 3 computed field
+                 - slope coefficient
+                 - barycenter 
+                 - Pearson Coefficient
+ +

cdfmaskdmp

+ +
  usage : cdfmaskdmp T-file S-file  ... 
+                ... [ref_dep snmin swidth hmin hwidth latmax latwidth]
+       
+      PURPOSE :
+        Compute a damping mask with smooth transition according to density,
+        depth and latitude criteria.
+       
+      ARGUMENTS :
+        T-file : temperature file
+        S-file : salinity file
+         They can be the same file, but as many climatologied are provided
+         in separate files, we decided to put both in the command line.
+       
+      OPTIONS :
+         ** If used, they must all be provided in the correct order (!) **
+        ref_dep  : reference depth for potential density.
+        snmin    : density minimum for the mask.
+        swidth   : density width for tapering
+        hmin     : minimum depth
+        hwidth   : depth width  for tapering
+        latmax   : maximum latitude
+        latwidth : latitude width  for tapering
+       
+        Actual default values are :
+         ref_dep  =    2000.000    
+         snmin    =    37.16000    
+         swidth   =   2.5000000E-02
+         hmin     =    1000.000    
+         hwidth   =    100.0000    
+         latmax   =   -20.00000    
+         latwidth =    2.000000    
+       
+      REQUIRED FILES :
+        mask.nc
+       
+      OUTPUT : 
+        netcdf file : mask_dmp.nc
+          variables : wdmp
+ +

cdfmax

+ +
  usage : cdfmax -f file -var cdfvar ...
+       ... [-lev kmin kmax ] [-zoom imin imax jmin jmax] ...
+       ... [-time tmin tmax ] [-fact multfact]  [-xy ]
+       
+      PURPOSE :
+         Find minimum and maximum of a file as well as their 
+         respective location. Options allow to restrict the 
+         finding to a sub area in time and space. This program
+         also deal with vertical slabs in a domain.
+       
+      ARGUMENTS :
+        -f file  : input file 
+        -var cdfvar : input variable
+       
+      OPTIONS :
+        [-lev kmin kmax ] : restrict to level between kmin and kmax. 
+        [-zoom imin imax jmin jmax] : restrict to sub area specified
+                        by the given limits. If the zoomed area is 
+                        degenerated to a single line, then the vertical
+                        slab is considered as domain.
+        [-time tmin tmax ] : restrict to the indicated time windows.
+        [-fact multfact] : use a multiplicative factor for the output
+        [-xy ] : force horizontal slab even in the case of a degenerated
+                        zoomed area.
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        output is done on standard output.
+ +

cdfmaxmoc

+ +
  usage : cdfmaxmoc OVT-file basin_name latmin latmax depmin depmax
+       
+      PURPOSE :
+         Compute the maximum and minimum of the overturning, from file OVT-file,
+         for oceanic basin specified by cbasin, and in the geographical frame 
+         defined by latmin latmax, depmin, depmax.
+       
+      ARGUMENTS :
+        OVT-file   : overturning file from cdfmoc, with or w/o sub basins.
+        basin_name : name of oceanic subbasin as defined in new_maskglo.nc
+                 usually it can be one of atl, glo, inp, ind or pac
+                 glo means no subbasins.
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : maxmoc.nc
+          6 variables : 
+             maxmoc, minmoc ( sv )      : max and min of overturning
+             latmaxmoc latminmoc ( deg) : latitudes of max and min.
+             depmaxmoc depminmoc ( m)   : depth of max amd min .
+       
+      SEE ALSO :
+        cdfmoc 
+       
+ +

cdfmean

+ +
  usage : cdfmean  IN-file IN-var T|U|V|F|W [imin imax jmin jmax kmin kmax]
+        ... [-full] [-var] [-zeromean] 
+       
+      PURPOSE :
+         Computes the mean value of the field (3D, weighted). For 3D fields,
+         a horizontal mean for each level is also given. If a spatial window
+         is specified, the mean value is computed only in this window.
+       
+      ARGUMENTS :
+        IN-file : input netcdf file.
+        IN-var  : name of netcdf variable to work with.
+        T|U|V|F|W : position of cdfvar on the C-grid
+       
+      OPTIONS :
+        [imin imax jmin jmax kmin kmax] : spatial windows where mean value 
+                   is computed:
+                   if imin = 0 then ALL i are taken
+                   if jmin = 0 then ALL j are taken
+                   if kmin = 0 then ALL k are taken
+        [ -full ] : compute the mean for full steps, instead of default 
+                    partial steps.
+        [ -var ]  : also compute the spatial variance of cdfvar 
+        [ -zeromean ] : create a file with cdfvar having a zero spatial mean.
+       
+      REQUIRED FILES :
+        Files mesh_hgr.nc, mesh_zgr.nc, mask.nc
+       
+      OUTPUT : 
+        - netcdf file : cdfmean.nc
+            variables : mean_cdfvar, mean_3D_cdfvar 
+                     [var_cdfvar, var_3D_cdfvar, in case of -var]
+        - netcdf file : zeromean.nc [ in case of -zeromean option]
+            variables : cdfvar
+        - ASCII files : cdfmean.txt
+                        [ cdfvar.txt, in case of -var ]
+        - all output on ASCII files are also sent to standard output.
+ +

cdfmhst

+ +
  usage : cdfmhst  VT-file | (V-file T-file [S-file])  [MST] [-full] ...
+               ...  [-Zdim] 
+       
+      PURPOSE :
+        Compute the meridional heat/salt transport as a function of 
+        latitude. If the file new_maskglo.nc is provided, the meridional 
+        heat/salt transport for each sub-basin is also computed.
+       
+      ARGUMENTS :
+        VT-file  : netcdf file containing the mean value of the products
+                   U.S, U.T, V.S and V.T (obtained with cdfvT).
+          or   
+        V-file T-file [S-file] : specify V, T S file as separate files. If
+                  S-file is not specified, assume that salinity is in T-file.
+       
+      OPTIONS :
+        [MST ]   : output flag for meridional salt transport on netcdf files.
+                   If not specified, only the MHT is output.
+        [-full ] : to be set for full step case.
+        [-Zdim ] : to be set to output vertical structure of Heat/salt transport
+       
+      REQUIRED FILES :
+         mesh_hgr.nc, mesh_zgr.nc and mask.nc
+         If new_maskglo.nc is also available, sub-basin meridional transports
+         are also computed.
+       
+      OUTPUT : 
+        ASCII files : zonal_heat_trp.dat : Meridional Heat Transport
+                      zonal_salt_trp.dat : Meridional Salt Transport
+        netcdf file : mhst.nc
+            variables : ( [... ] : MST option ) 
+                        zomht_glo  : Meridional Heat Transport (global)
+                      [ zomst_glo  : Meridional Salt Transport (global) ] 
+        If new_maskglo.nc is available, per basin meridional transport 
+        are also available:
+                        zomht_atl  : Meridional Heat Transport
+                      [ zomst_atl  : Meridional Salt Transport ]
+                        zomht_inp  : Meridional Heat Transport
+                      [ zomst_inp  : Meridional Salt Transport ]
+                        zomht_ind  : Meridional Heat Transport
+                      [ zomst_ind  : Meridional Salt Transport ]
+                        zomht_pac  : Meridional Heat Transport
+                      [ zomst_pac  : Meridional Salt Transport ]
+                        zomht_inp0 : Meridional Heat Transport
+                      [ zomst_inp0 : Meridional Salt Transport ]
+ +

cdfmkmask

+ +
  usage : cdfmkmask T-file [-zoom lonmin lonmax latmin latmax] ...
+                    ... [-zoomij iimin iimax ijmin ijmax] ...
+                    ... [-zoombat bathymin bathymax]  ...
+                    ... [-zoomvar varname varmin varmax]  ...
+                    ... [-time ] [-o OUT-file ]
+       
+      PURPOSE :
+        Build a mask file from vosaline array read from the input file.
+        It assumes that land salinity values are set to 0.
+       
+      ARGUMENTS :
+        T-file : netcdf file with salinity.
+                 if T-file = -maskfile, we assume a reference file named mask.nc
+                 with tmask variable.
+                 if T-file = -mbathy, we assume a reference file named 
+                 bathylevel.nc with mbathy variable, giving the number of 
+                 levels in the ocean.
+       
+      OPTIONS :
+        [-zoom lonmin lonmax latmin latmax] : geographical windows used to
+                         limit the area where the mask is builded. Outside
+                         this area, the mask is set to 0.
+        [-zoomij iimin iimax ijmin ijmax] : model grid windows used to
+                         limit the area where the mask is builded. Outside
+                         this area, the mask is set to 0.
+        [-zoombat bathymin bathymax] : depth windows used to
+                         limit the area where the mask is builded. Outside
+                         this area, the mask is set to 0.
+                         Need mesh_zgr.nc
+        [-zoomvar varname varmin varmax] : range of varname used to
+                         limit the area where the mask is builded. Outside
+                         this area, the mask is set to 0.
+        [-time ] : If further time step is available
+                         a mask for each time step is done
+        [-o OUT-file ] : output file name to be used in place of standard
+                         name [ mask_sal.nc ]
+       
+      REQUIRED FILES :
+        If option -zoombat is used, file mesh_zgr.nc is required.
+        If option T-file is -maskfile then mask.nc is required.
+        If option T-file is -mbathy then bathylevel.nc and mesh_zgr.nc
+         are required.
+       
+      OUTPUT : 
+        netcdf file : mask_sal.nc or OUT-file.
+          variables : tmask, umask, vmask, fmask
+                 fmask can differ from standard fmask because it does not
+                 reflect the slip/noslip lateral condition.
+ +

cdfmltmask

+ +
  usage : cdfmltmask -f IN-file -m MSK-file -v IN-var1,var2,...  
+               -p  T| U | V | F | W | P  [-s _Fillvalue] [-nc4] [-o OUT-file]
+               [ -M MSK-var ]
+       
+      PURPOSE :
+        Multiply IN-var(s) of IN-file by the mask corresponding to the
+        C-grid point position given by the -p argument.
+       
+      ARGUMENTS :
+        -f IN-file  : input netcdf file.
+        -m MSK-file : input netcdf mask file.
+        -v IN-var1,var2,...   : Comma separated list of variable names to mask.
+        -p T| U | V | F | W | P : C-grid position of IN-var
+                 P indicate a polygon mask created by cdfpoly.
+       OPTIONS : 
+         -s _FillValue : specify values for masked areas [0 by default ]
+         -nc4 : output file will be chunked and deflated
+         -o OUT-file : name of output file, instead of <IN-file>_masked
+         -M MSK-var : use MSK-var in the MSK-file, instead of the one defined
+                by default according to the -p option. Overrid -p option.
+       
+      REQUIRED FILES :
+         none, all are given as arguments.
+       
+      OUTPUT : (jvar)
+        The output file is a copy of the input file with only
+        the requested variable masked.
+        netcdf file : IN-file_masked unless specified with -o 
+          variables : IN-var (same as input).
+ +

cdfmoc

+ +
  usage : cdfmoc  V_file [-full] [-decomp ] [T_file] [S_file] [U_file] ...
+                 [-o OUT-file] [-rapid] 
+      PURPOSE :
+        Computes the MOC for oceanic sub basins as described 
+        in new_maskglo.nc
+       
+      ARGUMENTS :
+        V_file : file with meridional velocity component (mandatory).
+        T_file : file with temperature and salinity
+                (required only for -decomp option).
+        S_file  (required only for -rapid option, might be the same as T_file).
+        U_file  (required only for -rapid option).
+       
+      OPTIONS :
+        [-full ] : use full step instead of default partial step
+        [-decomp ] : decompose MOC in 3 components: Geostrophic,
+                  Barotropic,  Ageostrophic). For this option a 
+                  gridT file is required.
+        [-rapid ] : Compute the AMOC at 26.5 N in the same waay than the
+                   RAPID MOCHA array, separating the Gulfstream transport,
+                   and the contribution of different water masses :
+                    - 0-800m      : Thermocline recirculation
+                    - 800-1100m   : AIW recirculation
+                    - 1100-3000m  : upper-NADW recirculation
+                    - 3000-5000m  : lower-NADW recirculation
+                    - 5000-bottom : AABW recirculation
+        [-o OUT-file ] : specify output file instead of moc.nc
+       
+      REQUIRED FILES :
+        Files mesh_hgr.nc mesh_hgr.nc and mask.nc
+        File new_maskglo.nc. If this latter file is not available 
+              only the MOC for the global domain is computed
+       
+      OUTPUT : 
+        netcdf file : moc.nc
+        variables zomsfglo : Global ocean 
+        variables zomsfatl : Atlantic Ocean 
+        variables zomsfinp : Indo Pacific 
+        variables zomsfind : Indian Ocean alone
+        variables zomsfpac : Pacific Ocean alone
+        variables zomsfinp0 : Indo Pacific Net
+       
+        If decomposition is required , ( option -decomp ) add 3 additional
+        variables per basin with suffixes _sh, _bt, _ag.
+       
+        If option -rapid is used the output file (rapid_moc.nc) is degenerated
+        into 6 scalar values : tr_gs, tr_THERM, tr_AIW, tr_UNADW, tr_LNADW, 
+        tr_BW and a vertical profile of the AMOC at 26.5N, as computed
+        traditionally.
+        Additional variables are also computed following CLIVAR-GODAE 
+        reanalysis intercomparison project recommendations. 
+ +

cdfmocsig

+ +
  usage : cdfmocsig  V_file T_file depth_ref [-eiv] [-full]  ... 
+          ...  [-sigmin sigmin] [-sigstp sigstp] [-nbins nbins] [-isodep] [-v]
+      PURPOSE : 
+        Computes the MOC in density-latitude coordinates. The global value
+        is always computed. Values for oceanic sub-basins are calculated
+        if the file new_maskglo.nc is provided.
+        Last arguments is the reference depth for potential density, in m.
+        Actually only 0 1000 or 2000 are available with standard values for
+        density bins. If you specify another reference depth, you must also
+        specify the minimum density, the bin size and the number of bins,
+        with the options -sigmin, -sigstp, -nbins
+       
+      ARGUMENTS :
+         V_file  : Netcdf gridV file
+         T_file  : Netcdf gridT file
+         depth_ref : reference depth for density 
+                for depth values of 0 1000 or 2000, pre-defined limits for
+                minimum density, number of density bins and width of density
+                bins are provided. For other reference depth, you must use
+                -sigmin, -sigstp and -nbins options (see below).
+                Keyword 'ntr' can also be used in place of depth_ref in 
+                order to use neutral density (no default bin defined so far).
+       
+      OPTIONS :
+        [-eiv ] : takes into account VEIV Meridional eddy induced velocity
+                  -> To be used only if Gent and McWilliams parameterization 
+                     has been used 
+        [ -full ] : Works with full step instead of standard partial steps
+        [ -sigmin ] : Specify minimum of density for bining
+        [ -sigstp ] : Specify density step for bining
+        [ -nbins ]  : Specify the number of density bins you want
+        [ -isodep]  : Compute the zonal mean of isopycnal depths used for mocsig
+        [ -v  ]     : Verbose option for more info during execution
+       
+      REQUIRED FILES :
+         Files mesh_zgr.nc, mesh_hgr.nc, mask.nc
+         File new_maskglo.nc is optional [sub basins masks]
+       
+      OUTPUT : 
+        netcdf file : mocsig.nc
+        variables zomsfglo : Global ocean 
+        variables zomsfatl : Atlantic Ocean 
+        variables zomsfinp : Indo Pacific 
+        variables zomsfind : Indian Ocean alone
+        variables zomsfpac : Pacific Ocean alone
+        If file new_maskglo.nc is not present, mask.nc file
+        is used and only zomsfglo is produced.
+        If option -isodep is used, each MOC variable is complemented by a iso
+        variable, giving the zonal mean of ispycnal depth (e.g.zoisoglo).
+ +

cdfmoy

+ +
  usage : cdfmoy list_of_model_files [-spval0] [-cub ] [-zeromean] [-max]
+                [-nomissincl] [-nc4 ] [-o output_file_root ]
+       
+      PURPOSE :
+        Computes the time average of a list of files given as arguments.
+        The program assumes that all files in the list are of same
+        type (shape, variables etc...). 
+        For some variables, the program also computes the time average 
+        of the squared variables, which is used in other cdftools 
+        (cdfeke, cdfrmsssh, cdfstdevw, cdfstddevts ... The actual variables
+        selected for squared average are :
+          - vozocrtx
+          - vomecrty
+          - vovecrtz
+          - sossheig
+        This selection can be adapted with the nam_cdf_namelist process.
+        (See cdfnamelist -i for details).
+        If you want to compute the average of already averaged files,
+        consider using cdfmoy_weighted instead, in order to take into
+        account a particular weight for each file in the list.
+       
+      ARGUMENTS :
+        A list of similar model output files. 
+       
+      OPTIONS :
+        [ -spval0 ] :  set missing_value attribute to 0 for all output
+                variables and take care of the input missing_value.
+                This option is usefull if missing_values differ from files 
+                to files; it was formely done by cdfmoy_chsp).
+        [ -cub ] :  use this option if you want to compute third order moments
+                for the eligible variables, which are at present :
+               - sossheig
+               - votemper
+               This selection can be adapted with the nam_cdf_namelist process.
+               (See cdfnamelist -i for details).
+        [ -zeromean ] : with this option, the spatial mean value for each 
+               time frame is substracted from the original field before 
+               averaging, square averaging and eventually cubic averaging.
+        [-max ] : with this option, a file with the minimum and maximum values
+               of the variables is created.
+        [-nomissincl ] : with this option, the output mean is set to missing
+               value at any gridpoint where the variable contains a  missing
+               value for at least one timestep. You should combine with option
+               -spval0 if missing values are not 0 in all  the input files.
+        [ -nc4 ] Use netcdf4 output with chunking and deflation level 1
+                This option is effective only if cdftools are compiled with
+                a netcdf library supporting chunking and deflation.
+        [ -o output file root ] Default is cdfmoy
+       
+      REQUIRED FILES :
+        If -zeromean option is used, need mesh_hgr.nc and mask.nc
+       
+      OUTPUT : 
+        netcdf file : cdfmoy.nc and cdfmoy2.nc
+        variables : are the same than in the input files. For squared averages
+        _sqd is append to the original variable name.
+        If -cub option is used, the file cdfmoy3.nc is also created
+        with _cub append to the original variable name.
+        If -max option is used, file cdfmoy_minmax.nc is also created, with 
+        same variable names.
+       
+      SEE ALSO :
+        cdfmoy_weighted, cdfstdev
+       
+ +

cdfmoy_freq

+ +
  usage : cdfmoy_freq -i IN-file -f averaging-length [ -v3d] [-v4d] 
+               [-nc4] [-o output root] 
+       
+      PURPOSE :
+        This program takes a file covering 1 year of data (evenly spaced)
+        and sub-samples the data by performing box averages, which span is given
+        as argument.  The original data sampling can be hours, days or monthes 
+        or even seasons.
+        The program recognizes leap years, and when feb. 29 is found, it is 
+        included in the current 'box' (averaging length is thus increased
+        by 1 day.
+       
+      ARGUMENTS :
+        -i IN-file : gives the name of the yearly file containing either 365 
+                   or 366 days
+        -f averaging-length : Set the time size of the averaging box. 
+                  Averaging length is specified using XIOS convention (e.g. 1d,
+                  5d, 1mo, 1y ; 4mo stands for seasonal means )
+       
+      OPTIONS :
+        [-v3d] : use 3d variable (x,y,t) : save execution time, increase memory
+        [-v4d] : use 4d variable (x,y,z,t): save execution time, increase memory
+        [-nc4] : use netcdf4 with chunking and deflation for the output file
+        [-o output_root] : specify the root of the output file name instead 
+                    of cdfmoy_. Final name will have <freq> appened
+                    to the root.
+       
+      REQUIRED FILES :
+         none.
+       
+      OUTPUT : 
+        netcdf file :  cdfmoy_output<freq>.nc
+          variables :  same as variables in input file.
+       
+      SEE ALSO :
+       cdfmoy, cdfmoy_weighted
+       
+ +

cdfmoy_weighted

+ +
  usage : cdfmoy_weighted list of files [-old5d ] [-month] [-leap] ...
+       [-skip variable] [-nc4] [-o output file]
+      PURPOSE :
+        Compute weight average of files. The weight for each file is
+        read from the iweight attribute. In particular, this attribute
+        is set to the number of elements used when computing a time
+        average (cdfmoy program). A primary application is thus for
+        computing annual mean from monthly means.
+       
+      ARGUMENTS :
+        The list of files to be averaged, which are supposed to be of
+        the same type and to contain the same variables. This list MUST
+        be given before any options
+       
+      OPTIONS :
+        [-old5d ] : This option is used to mimic/replace the cdfmoy_annual
+                    which is no longer available. With this option, 12 monthly
+                    files must be given, and it is assumed that the monthly
+                    means were computed from 5d output of a simulation using
+                    a noleap calendar ( weights are fixed, predetermined)
+        [-month ] : This option is used to build annual mean from true month
+                    output (1mo) in XIOS output for instance.
+        [-leap ] : This option has only effect together with the -month option.
+                   When used set 29 days in february
+        [-skip variable ] : name of variable to skip 
+        [ -nc4 ] : Use netcdf4 chunking and deflation in output file.
+        [-o output file ] : Specify the name for output file instead of the
+                  default name cdfmoy_weighted.nc
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        netcdf file : cdfmoy_weighted.nc
+        variables : same as in the input files
+ +

cdfmoyt

+ +
  usage : cdfmoyt list_of_model_files [-spval0]  
+      PURPOSE :
+        Compute the time average of a list of files given as arguments.
+        This program handle multi time-frame files is such a way that
+        the output files are also multi time-frame, each frame being
+        the average across the files given in the list.
+        
+        The program assume that all files in the list are of same
+        type (shape, variables , and number of time frames ). 
+        For some variables, the program also compute the time average 
+        of the squared variables, which is used in other cdftools 
+        (cdfeke, cdfrmsssh, cdfstdevw, cdfstddevts ... The actual variables
+        selected for squared average are :
+          - vozocrtx
+          - vomecrty
+          - vovecrtz
+          - sossheig
+        This selection can be adapted with the nam_cdf_namelist process.
+        (See cdfnamelist -i for details).
+        If you want to compute the average of already averaged files,
+        consider using cdfmoy_weighted instead, in order to take into
+        account a particular weight for each file in the list.
+       
+      ARGUMENTS :
+        A list of similar model output files. 
+       
+      OPTIONS :
+        [ -spval0 ] :  set missing_value attribute to 0 for all output
+                variables and take care of the input missing_value.
+                This option is usefull if missing_values differ from files 
+                to files; it was formely done by cdfmoy_chsp).
+       
+      REQUIRED FILES :
+        none 
+       
+      OUTPUT : 
+        netcdf file : cdfmoy.nc and cdfmoy2.nc
+        variables : are the same than in the input files. For squared averages
+        _sqd is append to the original variable name.
+ +

cdfmoyuvwt

+ +
  usage : cdfmoyuv CONFCASE [-zoom imin imax jmin jmax ] 'list of tags' 
+       
+      PURPOSE :
+        Compute temporal mean fields for velocity components (u,v,w) and
+        temperature (t), as well as second order moments ( u2, v2, t2, uv, ut,
+        vt, wt).
+         These fields are required in other cdftools which computes either 
+         barotropic (cdfbti) or baroclinic (cdfbci) instabilities, and a global
+         energy balance (cdfnrjcomp)
+       
+      ARGUMENTS :
+        CONFCASE : the root name for the data files. Grid files are assumed to
+                   be gridT, gridU, gridV, gridW. ( grid_T, grid_U, grid_V and
+                   grid_W are also supported.
+        List_of_tags : The list of time tags corresponding to the time serie
+                   whose mean is being computed.
+       
+      OPTIONS :
+        [-zoom imin imax jmin jmax ] : limit the mean computation to the 
+                   specified sub area.
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        netcdf file : moyuvwt.nc
+          variables :  There are 11 variables produced by this program.
+                  tbar, t2bar : mean t (Kelvin) and mean t^2 (K^2)   [T-point]
+                  ubar, u2bar : mean u (m/s) and mean u^2 (m2/s2)    [U-point]
+                  vbar, v2bar : mean v (m/s) and mean v^2 (m2/s2)    [V-point]
+                  wbar        : mean w (m/s)                         [W-point]
+                  uvbar       : mean product u . v (m2/s2)           [T-point]
+                  utbar, vtbar, wtbar : mean product [uvw].t (m/s.K) [T-point]
+       
+      SEE ALSO :
+       cdfbti, cdfbci and cdfnrjcomp
+       
+ +

cdfmppini

+ +
  usage : cdfmppini jpni jpnj [m/b/z] [-jperio jperio]
+       
+      PURPOSE :
+        Perform the mpp initialisation with NEMO routine mpp_init2 and
+        give some statistics about the domains. Save the layout on a 
+        text file.
+       
+      ARGUMENTS :
+        jpni : number of domains in the i direction.
+        jpnj : number of domains in the j direction.
+       
+      OPTIONS :
+        [m/b/z] : use one of these letter to choose the land/sea mask.
+                m  : take mask from mask.nc (tmask) [ default ]
+                b  : take mask from bathy_meter.nc (Bathymetry)
+                z  : take mask from mesh_zgr.nc (mbathy)
+                    Default is m
+        [-jperio jperio ] : specify jperio. 
+                          default value is  6
+       
+      REQUIRED FILES :
+        one of mask.nc, bathy_meter.nc or mesh_zgr.nc according to option
+       
+      OUTPUT : 
+        - Standard output
+        - ASCII file mppini.txt
+ +

cdfmxl

+ +
  usage : cdfmxl T-file [S-file] [-nc4] [-o output file]
+       
+      PURPOSE :
+        Compute 7 estimates of the mixed layer depth from temperature
+        and salinity given in the input file, based on 3 different criteria:
+        1- Density criterium (0.01 kg/m3 difference between surface and MLD)
+        2- Density criterium (0.03 kg/m3 difference between surface and MLD)
+        3- Temperature criterium (0.2 C absolute difference between surface 
+           and MLD)
+        4- Temperature criterium (0.2 C absolute difference between T at 10m 
+           and MLD)
+        5- Temperature criterium (0.5 C absolute difference between T at 10m 
+           and MLD)
+        6- Density criterium (0.03 kg/m3 difference between rho at 10m and MLD) 
+        7- Density criterium (0.125 kg/m3 difference between rho at 10m and MLD)
+  
+       
+      ARGUMENTS :
+        T-file   : input netcdf file (gridT)
+        [S-file] : input netcdf file (gridS) Optional if vosaline not in T-file
+       
+      OPTIONS :
+        [-nc4] : use netcdf4 chunking and deflation on output 
+        [-o output file] : specify the name of output file instead of 
+                 default name mxl.nc
+       
+      REQUIRED FILES :
+         mesh_zgr.nc
+          In case of FULL STEP configuration, bathy_level.nc is also required.
+       
+      OUTPUT : 
+        netcdf file : mxl.nc
+          variables : somxl010    = mld on density criterium 0.01 ref. surf.
+                      somxl030    = mld on density criterium 0.03 ref. surf.
+                      somxlt02    = mld on temperature criterium -0.2 ref. surf.
+                      somxlt02z10 = mld on temperature criterium -0.2 ref. 10m
+                      somxlt05z10 = mld on temperature criterium -0.5 ref. 10m
+                      somxl030z10 = mld on density criterium 0.03 ref. 10m
+                      somxl125z10 = mld on density criterium 0.125 ref. 10m
+ +

cdfmxlhcsc

+ +
  usage : cdfmxlhcsc T-file criteria value [hmin]
+       
+      PURPOSE :
+        Compute the mixed layer depth, the heat content and salt content.
+       
+      ARGUMENTS :
+        T-file : netcdf input file for temperature and salinity (gridT).
+        criteria : one of temperature, t,  T for temperature criteria.
+                   or density, d,  D  for density criteria.
+        value  : value of the criteria (eg: 0.2 for temp, 0.01 or 0.03 for dens)
+       
+      OPTIONS :
+        [ hmin ] : limit the vertical integral from hmin to mld. By default, 
+                   hmin is set to 0 so that the integral is performed on the
+                   whole mixed layer.
+       
+      REQUIRED FILES :
+        mesh_hgr.nc mesh_zgr.nc and mask.nc
+       
+      OUTPUT : 
+        netcdf file : mxlhcsc.nc
+          variables : -  somxl010 (mld based on density criterium 0.01)
+           (2D)          or somxl030 (mld on density criterium 0.03)
+                         or somxlt02 (mld on temperature criterium -0.2)
+                         -  somxlheatc (heat content computed in the MLD)
+                         -  somxlsaltc (salt content computed in the MLD)
+       
+      SEE ALSO :
+        cdfmxl, cdfmxlheatc and  cdfmxlsaltc.
+       
+ +

cdfmxlheatc

+ +
  usage : cdfmxlheatc T-file [-full]
+       
+      PURPOSE :
+        Computed the heat content in the mixed layer (Joules/m2).
+       
+      ARGUMENTS :
+        T-file : netcdf input file with temperature and mld (gridT).
+       
+      OPTIONS :
+        [ -full ] : for full step configurations, default is partial step.
+        [-o OUT-file ] : specify output file instead of mxlheatc.nc
+       
+       
+      REQUIRED FILES :
+        mesh_zgr.nc and mask.nc
+       
+      OUTPUT : 
+        netcdf file : mxlheatc.nc
+          variables : somxlheatc (Joules/m2)
+       
+      SEE ALSO :
+        cdfmxl, cdfmxlhcsc and  cdfmxlsaltc.
+       
+ +

cdfmxlsaltc

+ +
  usage : cdfmxlsaltc T-file [-full ]
+       
+      PURPOSE :
+        Compute the salt content in the mixed layer.
+       
+      ARGUMENTS :
+        T-file : netcdf file with salinity and mixed layer deptht.
+       
+      OPTIONS :
+        [-full ] : indicate a full step configuration.
+        [-o OUT-file ] : specify output file instead of mxlsaltc.nc
+       
+      REQUIRED FILES :
+        mesh_zgr.nc and mask.nc
+       
+      OUTPUT : 
+        netcdf file : mxlsaltc.nc
+          variables : somxlsaltc (kg/m2 )
+       
+      SEE ALSO :
+        cdfmxl, cdfmxlhcsc, cdfmxlheatc 
+       
+ +

cdfnamelist

+ +
  usage :  cdfnamelist [-i] [-p]
+       
+      PURPOSE :
+        Give information [-i option] on the namelist mechanism implemented
+        in CDFTOOLS v3. Write a namelist template [-p option ] to initialize
+        the mechanism.
+       
+      ARGUMENTS :
+        none
+       
+      OPTIONS :
+        [ -i ] : print informations 
+        [ -p ] : write a template namelist.
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        with option -p, print a template namelist : PrintCdfNames.namlist
+       
+ +

cdfnan

+ +
  usage : cdfnan list_of_model_output_files [-value replace] [-absmax rabsmax ] 
+       
+      PURPOSE :
+        Detect NaN values in the input files, and change them to 
+        either spval (missing_value) or the value given as option.
+        Does the same for absolute values > huge(0.0)
+       
+      ARGUMENTS :
+        list of model output files. They must be of same type and have
+        similar sizes. CAUTION : input files are rewritten !
+       
+      OPTIONS :
+        [-value replace ] : use replace instead of missing_value for
+                            changing NaN.
+        [-absmax rabsmax ] : replace values whose absolute value is greater 
+                            than rabsmax.
+       
+      OUTPUT : 
+        netcdf file : input file is rewritten without NaN.
+          variables : same name as input.
+ +

cdfnorth_unfold

+ +
  usage : cdfnorth_unfold IN-file jatl jpacif pivot Cgrid_point
+       
+      PURPOSE :
+        Unfold the Artic Ocean in an ORCA configuration. Produce a netcdf
+        file with the Artic ocean as a whole. The area can be adjusted on
+        both Atlantic and Pacific sides.
+       
+      ARGUMENTS :
+        IN-file     : netcdf file to be unfolded.
+        jatl        : J index to start the unfold process in the Atlantic.
+        jpacif      : J index to start the unfold process in the Pacific.
+        pivot       : type of pivot for the north fold condition ( T or F )
+        Cgrid_point : grid point where the variables in the input file are
+                      located. If all variables in a single file are not on
+                      the same C-grid location, there might be a problem ...
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : unfold.nc
+          variables : same name and units than in the input file.
+ +

cdfnrjcomp

+ +
  usage : cdfnrjcomp IN-file
+       
+      PURPOSE :
+        Compute contributing terms of the energy equation at T-points.
+        Input file contains mean values processed by cdfmoyuvwt.
+        The means must have been computed on long enough period
+        for the statistics to be meaningful
+       
+      ARGUMENTS :
+        IN-file   : netcdf file produced by cdfmoyuvwt.
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        netcdf file : nrjcomp.nc
+          all variables are located at T point.
+          variables : tbar : mean temperature 
+                      ubar : mean zonal velocity
+                      vbar : mean meridional velocity
+                      anotsqrt : mean squared temperature anomaly
+                      anousqrt : mean squared zonal velocity anomaly
+                      anovsqrt : mean squared meridional velocity anomaly
+ +

cdfokubo-w

+ +
  usage : cdfokubow U-file V-file U-var V-var lev
+       
+      PURPOSE :
+        Compute Okubo-Weiss parameter of a vector field, at a specified level.
+        If level is specified as 0, assume that the input files are
+        forcing files, presumably on A-grid. In this latter case, the
+        vector field is interpolated on the C-grid. In any case, the
+        curl is computed on the F-point.
+       
+      ARGUMENTS :
+        U-file : zonal component of the vector field.
+        V-file : meridional component of the vector field.
+        U-var  : zonal component variable name
+        V-var  : meridional component variable name.
+        lev    : level to be processed. If set to 0, assume forcing file 
+                 in input.
+       
+      REQUIRED FILES :
+         mesh_hgr.nc and mask.nc
+       
+      OUTPUT : 
+        netcdf file : okubow.nc
+          variables : sokubow (s^-2)
+ +

cdfovide

+ +
 usage : cdfovide gridTfile gridUfile gridVfile 
+      Files mesh_hgr.nc and mesh_zgr.nc must be in te current directory 
+      Output on netcdf file ovide.nc
+ +

cdfpendep

+ +
  usage :  cdfpendep TRC-file INV-file  ... 
+                     ... [-inv inventory_name -trc trc_name ]
+       
+      PURPOSE :
+         Compute the penetration depth for passive tracers. It is the
+         ratio between the inventory and the surface concentration of
+         the tracer.
+       
+      ARGUMENTS :
+        TRC-file : netcdf file with tracer concentration.
+        INV-file : netcdf file with inventory of the tracer.
+       
+      OPTIONS :
+        [-inv inventory_name ] : specify netcdf variable name for inventory.
+                                 Default is INVCFC
+        [-trc tracer_name ]    : specify netcdf variable name for tracer.
+                                 Default is CFC11
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : pendep.nc
+          variables : pendep (m)
+ +

cdfpolymask

+ +
  usage : cdfpolymask POLY-file REF-file [ -r]
+       
+      PURPOSE :
+        Create a maskfile with polymask variable having 1
+        inside the polygon, and 0 outside. Option -r revert
+        the behaviour (0 inside, 1 outside).
+       
+      ARGUMENTS :
+        POLY-file : input ASCII file describing a polyline in I J grid.
+             This file is structured by block, one block corresponding 
+             to a polygon:
+               1rst line of the block gives a polygon name
+               2nd line gives the number of vertices (nvert) and a dummy 0
+               the block finishes  with nvert pairs of (I,J) describing 
+               the polygon vertices.
+        REF-file  : reference netcdf file for header of polymask file.
+       
+      OPTIONS :
+         [ -r ] : revert option. When used, 0 is inside the polygon,
+                  1 outside.
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        netcdf file : polymask.nc
+          variables : polymask
+ +

cdfprobe

+ +
  usage :  cdfprobe IN-file ilook jlook cdfvar [level]
+       
+      PURPOSE :
+       Display a 2 columns output time (in days), value.
+       
+      ARGUMENTS :
+        IN-file : input file to look for
+        ilook jlook : i,j position of the probe.
+        cdfvar : name of the cdf variabled to be displayed
+       
+      OPTIONS :
+        [level] : This optional last argument is used
+                to specify a model level, instead of first.
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        2 columns ( time , value ) ASCII output on display
+        time are given in days since the begining of the run.
+ +

cdfprofile

+ +
  usage : cdfprofile  I J IN-file IN-var [-dep depth ]
+       
+      PURPOSE :
+        Extract a vertical profile at location I J, for a variable
+        in an input file.
+       
+      ARGUMENTS :
+        I   J   : I, J position of the point to extract from file.
+        IN-file : input file to work with.
+        IN-var  : variable name whose profile is requested.
+       
+      OPTIONS :
+        -dep depth : specify a depth where vertical value will be
+                      interpolated.
+       
+      REQUIRED FILES :
+         none 
+       
+      OUTPUT : 
+        netcdf file : profile.nc
+           variable : name given as argument.
+        Profile is also written on standard output.
+ +

cdfpsi

+ +
  usage : cdfpsi U-file V-file [V] [-full ] [-mask ] [-mean] [-nc4 ] ...
+           ... [-ssh T-file ] [-open ] [-ref iref jref ] [-o OUT-file]
+       
+      PURPOSE :
+        Computes the barotropic stream function (a proxy ) as the integral of 
+        the transport.
+       
+      ARGUMENTS :
+        U-file  : netcdf file of zonal velocity.
+        V-file  : netcdf file of meridional velocity.
+       
+      OPTIONS :
+        [V] : use V field instead of U field for integration.
+        [ -full ] : indicates a full step case. Default is partial steps.
+        [ -mask ] : mask output fields. Note that the land value is significant.
+                    It correspond to the potential on this continent.
+        [ -mean ] : save the average of the computations done with U and V.
+        [ -nc4  ] : use netcdf4 output files with chunking and deflation
+        [ -ssh T-file ] : compute the transport in the 'ssh' layer, using 
+                   surface velocities. Take the ssh from T-file specified in 
+                   this option. This is a experimental option, not certified ...
+        [ -open ] : for open domain configuration. See also -ref to set 
+                    reference point.
+        [ -ref iref jref ] : Set the reference point in i,j coordinates.
+                    BSF at reference point is arbitrarly set to zero.
+        [ -o  OUT-file ] : specify output file name instead of default psi.nc
+       
+      REQUIRED FILES :
+        mesh_hgr.nc and mesh_zgr.nc.
+        mask.nc is required only if -mask option used.
+       
+      OUTPUT : 
+        netcdf file : psi.nc
+          variables : sobarstf (m3/s )
+        If option -ssh is used, 2 additional variables are added to the file :
+                      sobarstfssh (m3/s ) : contribution of SSH
+                      sobarstftotal (m3/s ) : total BSF
+       
+ +

cdfpsi_level

+ +
  Usage : cdfpsi_level  Ufile Vfile <V> (optional argument)
+  Computes the barotropic stream function as the integral of the transport
+  PARTIAL CELLS VERSION
+  Files mesh_hgr.nc, mesh_zgr.nc ,mask.nc must be in te current directory
+  Output on psi_level.nc, variables sobarstf on f-points
+  Default works well for a global ORCA grid. use V 3rdargument for North Atlanti
+ c
+ +

cdfpvor

+ +
  usage : cdfpvor T-file  U-file V-file [-full] [-lspv ] [-nc4] [-o output file]
+       
+      PURPOSE :
+        Compute the Ertel potential vorticity and save the relative  
+        vorticity, the stretching and the total potential vorticity. 
+        Qtot = ( f + xsi ) . D(rho)/D(z)  = Qstrech + Qrel           
+        With -lspv option, compute only Qstretch or Large Scale P V 
+       
+      ARGUMENTS :
+        T-file : netcdf file for temperature and salinity.           
+        U-file : netcdf file for zonal component of the velocity.    
+        V-file : netcdf file for meridional component of the velocity.
+       
+      OPTIONS :
+        [-full ] : indicate a full step configuration.                
+        [-lspv ] : calculate only the large scale potential vorticity.
+                   ( replace the old cdflspv tool).
+                   If used only T-file is required, no need for velocities.
+        [-nc4 ] :  use netcdf4 with chunking and deflation 
+        [-o output file ] : use output file instead of default pvor.nc
+       
+      REQUIRED FILES :
+        mesh_hgr.nc and mesh_zgr.nc
+       
+      OUTPUT : 
+        netcdf file : pvor.nc
+          variables : vorelvor (1.e-7 kg.m-4.s-1 ) relative vorticity
+                      vostrvor (1.e-7 kg.m-4.s-1 ) stretching vorticity
+                      vototvor (1.e-7 kg.m-4.s-1 ) total potential vorticity
+                   Ertel PV are located at T points.
+            
+        With option -lspv :
+        netcdf file : lspv.nc
+          variables :  volspv  (1.e-7 kg.m-4.s-1 ) large scale potential vortici
+ ty
+                   LSPV is  located at W points.
+       
+      SEE ALSO :
+        cdfcurl ( compute only the curl on 1 level)
+       
+ +

cdfrhoproj

+ +
  usage : cdfrhoproj IN-var RHO-file List_of_IN-files [VAR-type] [-debug ]... 
+        ... [-isodep] [-s0 sig0 | -s0 sigmin,sigstp,nbins ] [-sig sigma_name]..
+        ... [-noiso]
+       
+      PURPOSE :
+        Project IN-var on isopycnal surfaces. The isosurfaces can be defined in
+        many ways : (1) In a pre-defined ASCII file named rho_levsee format
+        below.  (2) using -s0 option.
+        IN-var will be interpolated on the T point of the C-grid, previous
+        to projection on isopycnal.
+        
+        WARNING: This cdftool is one of the few using 3D arrays. Further 
+        development is required to work with vertical slabs instead.
+       
+      ARGUMENTS :
+        IN-var   : name of the input variable to be projected
+        RHO-file : netcdf file with potential density field. If not a sigma0
+                   file, use -sig option to indicate the name of the density
+                   variable.
+        List_of_IN-file  : netcdf files with IN-var 
+       
+      OPTIONS :
+        [-s0 sigma  | -s0 sigmin,sigstp,nbins ]  : In the first form define a 
+                     single sigma surface on the command line, while in the 2nd
+                     form, it uses the same numbers than cdfmocsig to define
+                     equally spaced (sigstp) density surfaces, starting from 
+                     sigmin and up to sigmin + (nbins)*sigstp
+                     This option prevails the use of rho_lev file.
+        [VAR-type] : position of IN-var on the C-grid ( either T U V F W S )
+                     default is 'T'. 
+                     S is used in case of section files (cdf_xtract_brokenline).
+        [-sig sigma_name] : name of the density variable in RHO_file.
+                     default is vosigma0
+        [-isodep ] : only compute the isopycnal depth. then stop. In this case
+                     you must still specify a IN-var variable (in fact a dummy
+                      name).
+        [-noiso]   : do not save isopycnal depth (suitable for big files).
+        [-debug]   : produce extra prints. Must be use before other options ..
+       
+      REQUIRED FILES :
+        no metrics, information is taken from depth variable in input files.
+        rho_lev if not using -s0 option.
+        rho_lev is an ascii file, first line giving the number of isopycnal
+                            following lines with isopycnal value, 1 per line.
+       
+      OUTPUT : 
+        There are as many output files as input files.
+        netcdf file : IN-file.interp
+          variables : VAR-in (unit is the same as input var)
+                      vodepiso (m) : depth of isopycnal.
+       
+        If option -isodep is used, only isopycnal depth is output :
+        netcdf file : isopycdep.nc
+          variables : vodepiso (m) 
+       
+      SEE ALSO :
+        replace cdfisopycdep when using -isodep option,  cdfmocsig
+        
+ +

cdfrichardson

+ +
  usage : cdfrichardson  gridT gridU gridV [ W ] [-full]
+      PURPOSE :
+        Compute the Richardson Number (Ri) according to
+        temperature, salinity and velocity components
+        given in the input files.
+       
+      ARGUMENTS :
+        gridT : input gridT file for temperature and salinity
+        gridU : input gridU file for zonal velocity component
+        gridV : input gridV file for meridional velocity component
+       
+      OPTIONS :
+        [ W ] : keep N2 at W points. Default is to interpolate N2
+              at T point on the vertical
+        [ -full ] : indicate a full step configuration instead of
+                 the default partial steps.
+       
+      REQUIRED FILES :
+        mesh_zgr.nc is needed for this program.
+       
+      OUTPUT : 
+        netcdf file : richardson.nc
+        variables : voric
+ +

cdfrmsssh

+ +
  usage : cdfrmsssh T-file T2-file [-nc4] [-o outputfile]
+       
+      PURPOSE :
+        Compute the standard deviation of the SSH from its
+        mean value and its mean square value. 
+       
+        Note that what is computed in this program is stictly the
+        standard deviation. It is very often called RMS, which is
+        an abuse. It is the same only in the case of zero mean value.
+        However, for historical reason, the name of this tool, remains
+        unchanged: cdfrmsssh
+       
+      ARGUMENTS :
+        T-file  : netcdf file with mean values for SSH
+        T2-file : netcdf file with mean squared values for SSH
+       
+      OPTIONS :
+        [-nc4] : use netcdf4 with chunking and deflation 
+        [-o output file ] : specify the name of the output file instead
+                           of default name rms.nc
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        netcdf file : rms.nc
+          variables : sossheig_rms, same unit than the input.
+       
+      SEA ALSO :
+        cdfstd, cdfstdevw, cdfstdevts.
+ +

cdfscale

+ +
  usage : cdfscale INOUT-file IN-var scale 
+       
+      PURPOSE :
+        Replace IN-var in INOUT-file by its values x scale.
+       
+      ARGUMENTS :
+        INOUT-file : netcdf input file (!overwritten!).
+        IN-var : netcdf variable to be scaled.
+        scale : Scale value to be used (multiplication factor).
+       
+      OUTPUT : 
+        netcdf file : input file is rewritten 
+          variables : same name as input.
+ +

cdfsections

+ +
 Usage : 
+  cdfsections  Ufile Vfile Tfile larf lorf Nsec lat1 lon1 lat2 lon2 n1
+               [ lat3 lon3 n2 ] [ lat4 lon4 n3 ] ....
+    
+  Computes temperature, salinity, sig0, sig1, sig2, sig4, Uorth, Utang 
+  along a section made of Nsec linear segments (see output attributes).
+  Output is section.nc, var. as a function of X(km), depth(m) and time.
+    
+ Arguments : 
+  # larf and lorf -> location of X=0 for the X-absice (may be out of section)
+  # Nsec -> number of segments used to compute the whole section.
+  # lat1,lat2,lat3,... -> extrema latitudes of the segments (from -90 to 90)
+  # lon1,lon2,lon3,... -> extrema latitudes of the segments (from 0 to 360)
+  # n1, n2, ...        -> number of output points on each segment.
+    (you have to give Nsec+1 values of lati/loni and Nsec values of ni)
+  
+  It is recommended to put a lot of points on each section if the aim
+  is to compute X-integrations along the section (10 x the model resolution).
+ NB : sections cannot cross the Greenwich line !!
+ NB : Not yet tested north of 60N.
+ NB : require a large amount of memory !
+      -> reduce domain size with  ncks -d  if insufficient memory error.
+  
+ Example for one linear section : 
+  cdfsections U.nc V.nc T.nc 48.0 305.0 1 49.0 307.0 50.5 337.5 20
+ Example for a section made of 2 linear segments : 
+  cdfsections U.nc V.nc T.nc 48.0 305.0 2 49.0 307.0 50.5 337.5 20 40.3 305.1 50
+ +

cdfsig0

+ +
  usage : cdfsig0 -t T-file [-sal SAL-name] [-tem TEM-name] [-nc4] [-o OUT-file]
+       
+      PURPOSE :
+        Compute potential density (sigma-0) refered to the surface.
+       
+      ARGUMENTS :
+        -t T-file  : netcdf file with temperature and salinity.
+          (for backward compatibility, -t can be ommited when T-file is the only
+          argument.)
+       
+      OPTIONS :
+        [-sal SAL-name]  : name of salinity variable
+        [-tem TEM-name]  : name of temperature variable
+        [-nc4]  : enable chunking and compression
+        [-o OUT-file]    : specify output filename instead of sig0.nc
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : sig0.nc
+          variables : vosigma0 ( kg/m3 - 1000 )
+       
+      SEE ALSO :
+        cdfsigi
+ +

cdfsigi

+ +
  usage : cdfsigi T-file Ref-dep(m) 
+       
+      PURPOSE :
+        Compute potential density refered to the depth given in arguments.
+       
+      ARGUMENTS :
+        T-file : netcdf file with temperature and salinity
+        Ref-dep : reference depth in meter.
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : sigi.nc
+          variables : vosigmai (kg/m3 -1000 )
+       
+      SEE ALSO :
+       cdfsig0
+       
+ +

cdfsiginsitu

+ +
  usage : cdfsiginsitu -t T-file [-sal SAL-name] [-tem TEM-name ] ...
+                 [-dep depth] [-o OUT-file ] [-nc4 ] 
+       
+      PURPOSE :
+        Compute in situ density from temperature and salinity.
+        Depths are taken from input file.
+       
+      ARGUMENTS :
+        -t T-file : netcdf file with temperature and salinity.
+          (for backward compatibility, -t can be ommited when T-file is the only
+          argument.)
+       
+      OPTIONS :
+        [-sal SAL-name] : name of salinity variable
+        [-tem TEM-name] : name of temperature variable
+        [-dep depth ]   : depth to be used in case of 2D input file (only)
+        [-nc4]          : enable chunking and compression
+        [-o OUT-file]   : specify output filename instead of siginsitu.nc
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : siginsitu.ncor the file name specified 
+                    with -o option
+          variables : vosigmainsitu (kg/m3 -1000 )
+       
+      SEE ALSO :
+       cdfsig0, cdfsigi 
+       
+ +

cdfsigintegr

+ +
  usage : cdfsigintegr IN-var RHO-file list_of_files [ VAR-type ] ...
+               ... [ -sig sigma_name] [ -full ] 
+       
+      PURPOSE :
+        Take a list of input files with specific IN-var variable, associated
+        with a reference density file. A set of isopycnal surfaces is defined
+        in an ASCII file (rho_lev by default), using same depth reference than
+        the input reference density file. This program computes the integral of
+        IN-var between the isopycnals defined in rho_lev. It also gives the 
+        isopycnal depth and thickness of density layers.
+       
+        Rho_lev file first line indicates the number of following isopycnals.
+        Then a list of the densities is given, one per line.
+       
+      ARGUMENTS :
+        IN-var : input variable to be integrated
+        RHO-file : netcdf file with already computed density
+        list_of_files : a list of model netcdf files containing IN-var.
+       
+      OPTIONS :
+        [ VAR-type ] : one of T U V F W which defined the position on
+                IN-var in the model C-grid. Default is T
+        [ -sig sigma_name ] : give the name of sigma variable in RHO-file.
+                Default is vosigma0
+        [ -full ] : indicate a full step configuration.
+        [ -rholev  file] : indicates name of file defining the limits for 
+                integration. Default is rho_lev
+       
+      REQUIRED FILES :
+        mesh_zgr.nc and rho_lev
+       
+      OUTPUT : 
+        netcdf file : IN-file.integr
+          variables : inv_IN-var  : inventory of IN-var from input file.
+                      vodepiso (m) : depth of isopycnal.
+                      isothick (m) : thickness of isopycnal layer.
+                      mean_IN-var (same unit as IN-var) : mean IN-var in the iso
+ pycnal
+       
+      SEE ALSO :
+       cdfrhoproj, cdfsigtrp, cdfisopycdep
+       
+ +

cdfsigntr

+ +
  usage : cdfsigntr T-file
+       
+      PURPOSE :
+        Compute neutral volumic mass (kg/m3) from temperature and salinity.
+       
+      ARGUMENTS :
+        T-file  : netcdf file with temperature and salinity.
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : signtr.nc
+          variables : vosigntr ( kg/m3 )
+       
+      SEE ALSO :
+        cdfsig0, cdfsigi, cdfsiginsitu
+ +

cdfsigtrp

+ +
  usage :  cdfsigtrp T-file U-file V-file sigma_min sigma_max nbins ...
+               ... [-print ] [-bimg ] [-full ] [ -refdep ref_depth] ...
+               ... [-neutral ] [-section file ] [-temp ]
+       
+      PURPOSE :
+        Compute density class transports, according to the density class
+        definition ( minimum, maximum and number of bins) given in arguments.
+        Section position are given in dens_section.dat, an ASCII file 
+        with pairs of lines giving section name and section location as
+        imin imax jmin jmax. Only zonal or meridional section are allowed.
+        The name of this file can be specified with the -section option, if
+        it differs from the standard name. Optionaly, a netcdf root variable 
+        name and a netcdf root long-name can be provided on the line giving 
+        the section name.
+       
+        This program can also be used to compute transport by class of 
+        temperatures, provided the temperatures decrease monotonically 
+        downward. In this case, use -temp option and of course specify
+        sigma_min, sigma_max as temperatures.
+       
+      ARGUMENTS :
+        T-file : netcdf file with temperature and salinity
+        U-file : netcdf file with zonal velocity component
+        V-file : netcdf file with meridional velocity component
+        sigma_min : minimum density for binning
+        sigma_max : maximum density for binning
+        nbins : number of bins. This will fix the bin 'width' 
+       
+      OPTIONS :
+        [ -full ] : for full step configuration
+        [ -bimg ] : produce extra bimg output file which shows the details
+                of the sections (normal velocity, density, temperature, 
+                salinity, transports, isopycnal depths. (to be change to 
+                netcdf files for more common use.
+        [ -ncdf ] : produce extra netcdf output file which shows the details
+                of the sections (normal velocity, density, temperature, 
+                salinity, transports, isopycnal depths. 
+        [ -print ]: write the binned transports on standard output, for each
+                sections.
+        [ -refdep ref_depth ]: give a reference depths for the computation of
+                potential density. Sigma_min, sigma_max must be adapted 
+                accordingly.
+        [ -neutral ]: use neutral density instead of potential density 
+        [ -section file] : give the name of section file.
+                Default is dens_section.dat
+        [ -temp ] : use temperature instead of density for binning
+       
+      REQUIRED FILES :
+        mesh_hgr.nc, mesh_zgr.nc and dens_section.dat
+       
+      OUTPUT : 
+        Netcdf file : There is 1 netcdf file per section. File name is build
+          from section name : Section_name_trpsig.nc
+          variables : sigma_class (upper limit of the bin)
+                      sigtrp : transport (Sv per bin)
+       
+        ascii file  : trpsig.txt
+       
+        bimg  file  :  There are 2 bimg files whose name is build from section
+          name : section_name_trpdep.bimg and section_name_trpsig.bimg.
+          This file is written only if -bimg option is used.
+       
+       Standard output : the results are written on standard output only if 
+          the -print option is used.
+       
+      SEE ALSO :
+       cdfrhoproj, cdftransport, cdfsigintegr 
+       
+ +

cdfsigtrp_broken

+ +
  usage :  cdfsigtrp_broken TSV-file sigma_min sigma_max nbins ...
+               ... [-print ] [-bimg ] [-full ] [ -refdep ref_depth] ...
+               ... [-neutral ] [-section file ] [-temp ]
+       
+      PURPOSE :
+        Compute density class transports, according to the density class
+        definition ( minimum, maximum and number of bins) given in arguments.
+        Section position are given in dens_section.dat, an ASCII file 
+        with pairs of lines giving section name and section location as
+        imin imax jmin jmax. Only zonal or meridional section are allowed.
+        The name of this file can be specified with the -section option, if
+        it differs from the standard name. Optionaly, a netcdf root variable 
+        name and a netcdf root long-name can be provided on the line giving 
+        the section name.
+        In this particular tool, the section used is the result of 
+        cdf_xtrac_brokenline. In this way, it is possible to calculate the
+        transport of density class in oblicous sections (non dependance on 
+        zonal or meridional).
+       
+        This program can also be used to compute transport by class of 
+        temperatures, provided the temperatures decrease monotonically 
+        downward. In this case, use -temp option and of course specify
+        sigma_min, sigma_max as temperatures.
+       
+      ARGUMENTS :
+        TSV-file : netcdf_broken_line file with temperature, salinity
+        and the normal velocity through the section
+        sigma_min : minimum density for binning
+        sigma_max : maximum density for binning
+        nbins : number of bins. This will fix the bin 'width' 
+       
+      OPTIONS :
+        [ -full ] : for full step configuration
+        [ -bimg ] : produce extra bimg output file which shows the details
+                of the sections (normal velocity, density, temperature, 
+                salinity, transports, isopycnal depths. (to be change to 
+                netcdf files for more common use.
+        [ -ncdf ] : produce extra netcdf output file which shows the details
+                of the sections (normal velocity, density, temperature, 
+                salinity, transports, isopycnal depths. 
+        [ -print ]: write the binned transports on standard output, for each
+                sections.
+        [ -refdep ref_depth ]: give a reference depths for the computation of
+                potential density. Sigma_min, sigma_max must be adapted 
+                accordingly.
+        [ -neutral ]: use neutral density instead of potential density 
+        [ -section file] : give the name of section file.
+                Default is dens_section.dat
+        [ -temp ] : use temperature instead of density for binning
+       
+      REQUIRED FILES :
+        mesh_zgr.nc and dens_section.dat
+       
+      OUTPUT : 
+        Netcdf file : There is 1 netcdf file per section. File name is build
+          from section name : Section_name_trpsig.nc
+          variables : sigma_class (upper limit of the bin)
+                      sigtrp : transport (Sv per bin)
+       
+        ascii file  : trpsig.txt
+       
+        bimg  file  :  There are 2 bimg files whose name is build from section
+          name : section_name_trpdep.bimg and section_name_trpsig.bimg.
+          This file is written only if -bimg option is used.
+       
+       Standard output : the results are written on standard output only if 
+          the -print option is used.
+       
+      SEE ALSO :
+       cdfrhoproj, cdftransport, cdfsigintegr, cdfsigtrp, cdf_xtrac_brokenline 
+       
+ +

cdfsmooth

+ +
  usage : cdfsmooth -f IN-file -c ncut [-t filter_type] [ -k level_list ] ...
+        [-a anisotripoc ratio ] [-nc4 ] 
+       
+      PURPOSE :
+        Perform a spatial smoothing on the file using a particular
+        filter as specified in the option. Available filters
+        are : Lanczos, Hanning, Shapiro, Box car average. Default
+        is Lanczos filter.
+       
+      ARGUMENTS :
+        -f  IN-file  : input data file. All variables will be filtered
+        -c  ncut     : number of grid step to be filtered, or number
+                     of iteration of the Shapiro filter.
+       
+      OPTIONS :
+        -t filter_type : Lanczos      , L, l  (default)
+                         Hanning      , H, h
+                         Shapiro      , S, s
+                         Box          , B, b
+        -a aniso       : anisotropic ratio for Box car 
+        -k level_list  : levels to be filtered (default = all levels)
+                level_list is a comma-separated list of levels.
+                   the syntax 1-3,6,9-12 will select 1 2 3 6 9 10 11 12
+        -nc4 : produce netcdf4 output file with chunking and deflation.
+       
+      OUTPUT : 
+        Output file name is build from input file name with indication
+        of the filter type (1 letter) and of ncut.
+        netcdf file :   IN-file[LHSB]ncut
+          variables : same as input variables.
+ +

cdfspeed

+ +
  usage : cdfspeed  U-file V-file U-var V-var [-t T-file] ...
+             ... [-nc4] [-o OUT-file ] [-lev level_list]
+     PURPOSE :
+        Computes the speed of ocean currents or wind speed
+        
+        If the input files are 3D, the input is assumed to be 
+        a model output on native C-grid. Speed is computed on the A-grid.
+        
+        If the input file is 2D and then we assume that this is 
+        a forcing file already on the A-grid.
+     
+     ARGUMENTS :
+        U-file : netcdf file for U component
+        V-file : netcdf file for V component
+        U-var  : netcdf variable name for U component
+        V-var  : netcdf variable name for V component
+     
+     OPTIONS :
+        -t T-file  : indicate any file on gridT for correct header
+                  of the output file (usefull for 3D files)
+        -lev level_list  : indicate a list of levels to be processed
+                  If not used, all levels are processed.
+                  This option should be the last on the command line
+        -nc4 : use netcdf4 output with chunking and deflation
+        -o OUT-file : use specified output file instead of speed.nc
+     
+     OUTPUT :
+        Output on speed.nc  variable U 
+ +

cdfspice

+ +
  usage : cdfspice -t T-file [-sal SAL-name] [-tem TEM-name] ...
+         ... [-nc4] [-o OUT-file]
+       
+      PURPOSE :
+        Compute the spiceness corresponding to temperatures and salinities
+        given in the input file.
+       
+        spiciness = sum(i=0,5)[sum(j=0,4)[b(i,j)*theta^i*(s-35)^j]]
+                  with:  b     -> coefficients
+                         theta -> potential temperature
+                         s     -> salinity
+       
+      ARGUMENTS :
+        -t T-file : netcdf file with temperature and salinity (gridT)
+            Single argument T-file can also be used, for backward compatibility
+      
+      OPTIONS :
+        [-sal SAL-name]  : name of salinity variable
+        [-tem TEM-name]  : name of temperature variable
+        [-nc4]  : enable chunking and compression
+        [-o OUT-file]    : specify output filename instead of spice.nc
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        netcdf file : spice.nc
+          variables : vospice
+       
+      REFERENCE :
+        Flament (2002) "A state variable for characterizing 
+              water masses and their diffusive stability: spiciness."
+              Progress in Oceanography Volume 54, 2002, Pages 493-501.
+ +

cdfsstconv

+ +
  Usage : cdfflxconv YEAR config 
+     Output 6 cdf files : for emp, qnet, qsr, sst, taux, tauy with standard var 
+ name :
+         sowaflup, sohefldo, soshfldo, sst, sozotaux, sometauy 
+     coordinates.diags ( clipper like) is required in current dir 
+ +

cdfstatcoord

+ +
  usage : cdfstatcoord COOR-file MSK-file [ MSK-var ]
+       
+      PURPOSE :
+        Computes and displays statistics about grid metrics vs latitude.
+        Bins e1 and e2 by latitude bins, and compute the mean of each bin.
+       
+      ARGUMENTS :
+        COOR-file : coordinates file with e1 e2 metrics
+        MSK-file  : mask file 
+       
+      OPTIONS :
+        [MSK-var] : mask variable name. Default is tmask
+       
+      REQUIRED FILES :
+        none apart those requested on command line.
+       
+      OUTPUT : 
+        Standard output
+ +

cdfstats

+ +
  usage : cdfstats IN-file REF-file ncy [VAR-name1 [VAR-name2]] ...
+                 [-m mesh_mask file ]
+       
+      PURPOSE :
+             This tool computes some statistics (rms, correlation, 
+          signal/noise ratio and signal ratio [ratio of std 
+          deviation]) between to files. In this tool, the files
+          are supposed to hold monthly averages values, for many 
+          years. Specifying ncy=12, allows to remove the seasonal
+          cycle of the data.
+             This program was initially written for SSH statistics
+          between model output and AVISO files (default variable
+          names are sossheig for this reason ). It can
+          now be used with any variables.
+       
+      ARGUMENTS :
+         IN-file  : First data file ( usually model output) 
+         REF-file : Second data file ( usually observation file) 
+         ncy      : 1 or 12. If set to 12, annual cycle is removed 
+                    from the data 
+         [VAR-name1 [VAR-name2]] : If variable names of input files
+                  are not sossheig they can be specified
+                  on the command line. If only one name is given, it is
+                  assumed that both file use same variable name.
+       
+      OPTIONS :
+         -m mesh_mask file : specify a mesh_mask file holding the tmaskutil
+                  and the horizontal metrics. If this option is not used,
+                  mask are taken in mask.nc and horizontal metric
+                  is taken in mesh_hgr.nc
+       
+      REQUIRED FILES :
+        mask.nc and mesh_hgr.nc
+            or mesh_mask file specified in -m option
+       
+      OUTPUT : 
+         netcdf file : stats.nc
+          variables are : 
+                rms    : RMS between the input files
+                correl : CORREL between the input files
+                rrat   : Signal to noise ratio 
+                srat   : Signal ratio (stdev ratio) 
+       
+ +

cdfstd

+ +
  usage : cdfstd [-save] [-spval0] [-nomissincl] [-stdopt] list_of files 
+       
+      PURPOSE :
+        Compute the standard deviation of the variables belonging to a set of
+        files given as arguments.  This computation is direct and does not 
+        required a pre-processing with any of the cdfmoy tools.
+       
+      ARGUMENTS :
+        List on netcdf files of the same type, forming a time-series
+       
+      OPTIONS :
+        [ -save ] : Save the mean value of the field, in addition to the 
+            std deviation. If used must be appear before list of files.
+        [ -spval0 ] :  set missing_value attribute to 0 for all output
+            variables and take care of the input missing_value.
+            This option is usefull if missing_values differ from files 
+            to files.
+            If used it should be called  before the list of input files.
+        [-nomissincl ] : with this option, the output std and mean are set to
+            missing value at any gridpoint where the variable contains a 
+            missing value for at least one timestep. You should combine 
+            with -spval0 if missing values are not 0 in all the input files.
+            If used it should be called  before the list of input files.
+        [ -stdopt ]:  use a  more optimal algorithm to compute std
+            and std is unbiased.  If used it should be called  before
+             the list of input files.
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        - netcdf file : cdfstd.nc
+            variables :  IN-var_std, same units than input variables.
+        - netcdf file : cdfmoy.nc in case of -save option.
+            variables :  IN-var, same units than input variables.
+       
+      SEE ALSO :
+         cdfmoy, cdfrmsssh, cdfstdevw
+ +

cdfstdevts

+ +
  usage : cdfstdevts T-file T2-file 
+       
+      PURPOSE :
+        Compute the standard deviation of the temperature
+        and salinity from their mean and  mean square values. 
+       
+      ARGUMENTS :
+        T-file  : netcdf file with mean values for T, S
+        T2-file : netcdf file with mean squared values for T,S
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        netcdf file : stdevts.nc
+          variables : votemper_stdev, same unit than the input.
+                      vosaline_stdev, same unit than the input.
+       
+      SEA ALSO :
+        cdfstd, cdfrmsssh, cdfstdevw.
+ +

cdfstdevw

+ +
  usage : cdfstdevw W-file W2-file [varname] [-o output_file] [-nc4 ]
+       
+      PURPOSE :
+        Computes the standard deviation of the vertical velocity
+        from its mean value and its mean square value. If a variable name 
+        is given, then computes rms of this variable instead of the vertical 
+        velocity.
+       
+        Note that what is computed in this program is stictly the
+        standard deviation. It is very often called RMS, which is
+        an abuse. It is the same only in the case of zero mean value.
+       
+      ARGUMENTS :
+        W-file  : netcdf file with mean values for w ( or given variable)
+        W2-file : netcdf file with mean squared values for w (or given variable)
+       
+      OPTIONS: 
+         varname : give name of variable if not vovecrtz
+       
+      REQUIRED FILES :
+        none
+       
+      OUTPUT : 
+        netcdf file : rmsw.nc (if varname specified, output file is rms_var.nc)
+          variables : vovecrtz_rms, (or varname_rms)  same unit than the input.
+       
+      SEA ALSO :
+        cdfstd, cdfrmsssh, cdfstdevts.
+ +

cdfstrconv

+ +
  Usage : cdfstrconv YEAR config 
+     Output 6 cdf files : for emp, qnet, qsr, sst, taux, tauy with standard var 
+ name :
+         sowaflup, sohefldo, soshfldo, sst, sozotaux, sometauy 
+     coordinates.diags ( clipper like) is required in current dir 
+ +

cdfsum

+ +
  usage : cdfsum IN-file IN-var T| U | V | F | W  ... 
+              ... [imin imax jmin jmax kmin kmax] [-full ] 
+       
+      PURPOSE :
+        Computes the sum value of the field (3D, weighted)
+        This sum can be optionally limited to a sub-area.
+       
+      ARGUMENTS :
+        IN-file : netcdf input file.
+        IN-var  : netcdf variable to work with.
+        T| U | V | F | W : C-grid point where IN-var is located.
+       
+      OPTIONS :
+        [imin imax jmin jmax kmin kmax] : limit of the sub area to work with.
+               if imin=0 all i are taken
+               if jmin=0 all j are taken
+               if kmin=0 all k are taken
+       
+      REQUIRED FILES :
+       mesh_hgr.nc, mesh_zgr.nc and mask.nc
+       
+      OUTPUT : 
+        Standard output.
+        netcdf file : cdfsum.nc with 2 variables : vertical profile of sum
+                      and 3D sum.
+ +

cdftempvol-full

+ +
 Usage : cdftempvol-full  gridTfile  imin, imax, jmin, jmax temp_max temp_min nbins [options]
+            imin, imax, jmin, jmax : horizontal limit of the box
+            temp_max, temp_min : limit for temperature bining 
+                           nbins : number of bins to use 
+     Possible options :
+         -print :additional output is send to std output
+         -bimg : 2D (x=lat/lon, y=temp) output on bimg file for hiso, cumul trp, trp
+ Files mesh_hgr.nc, mesh_zgr.nc must be in the current directory
+ Output on voltemp.txt
+ +

cdftransport

+ +
  usage : cdftransport [-test  u v ] [-noheat ] [-plus_minus ] [-obc]...
+                   ... [VT-file] U-file V-file [-full] |-time jt] ...
+                   ... [-time jt ] [-zlimit limits of level]
+       
+     PURPOSE :
+       Compute the transports accross a section.
+       The name of the section and the imin, imax, jmin, jmax for the section 
+       is read from the standard input. To finish the program use the key name
+       'EOF' for the section name.
+       OBC U,V files can be used if -obc option is specified.
+       
+      ARGUMENTS :
+       [VT-file ] : netcdf file with mean values of vt, vs, ut, us for heat and
+                    salt transport. If options -noheat or -plus_minus are used
+                    this file name must be omitted.
+       [U-file ] : netcdf file with the zonal velocity component.
+       [V-file ] : netcdf file with the meridional velocity component.
+       
+      OPTIONS :
+       [-test u v ]: use constant the u and v velocity components for sign 
+                     test purpose.
+       [-noheat ]  : use when heat and salt transport are not requested.
+                     This option must come before the file names, and if used
+                     VT file must not be given.
+       [ -plus_minus or -pm ] : separate positive and negative contribution to
+                     the volume transport. This option implicitly set -noheat,
+                     and must be used before the file names.
+       [-obc ]    : indicates that input files are obc files (vertical slices)
+                     Take care that for this case, mesh files must be adapted.
+                     This option implicitly set -noheat, and must be used before
+                     the file names.
+       [-full ]   :  use for full step configurations.
+       [-time jt ]:  compute transports for time index jt. Default is 1.
+       [-zlimit list of depth] : Specify depths limits defining layers where the
+                     transports will be computed. If not used, the transports 
+                     are computed for the whole water column. If used, this 
+                     option must be the last on the command line.
+       
+      REQUIRED FILES :
+       Files mesh_hgr.nc, mesh_zgr.nc must be in the current directory.
+       
+      OUTPUT : 
+       - Standard output 
+       - ASCII file reflecting the standard output: section_trp.dat
+       - ASCII files for volume, heat and salt transport: vtrp.txt, htrp.txt 
+           and strp.txt.
+       - Netcdf files for each section. name of the file is buildt
+           from section name.
+       
+      SEE ALSO :
+        cdfsigtrp
+       
+ +

cdfuv

+ +
  usage : cdfuv CONFIG-CASE 'list_of_tags' 
+      PURPOSE :
+        Compute the time average values for U.V  product, at T point.
+        Mean U and V values at T points, and mean U'.V' product are 
+        saved as well.
+       
+      ARGUMENTS :
+        CONFIG-CASE is the config name of a given experiment (eg ORCA025-G70)
+             The program will look for gridU and gridV files for
+             this config (grid_U and grid_V are also accepted).
+        list_of_tags : a list of time tags that will be used for time
+             averaging. e.g. y2000m01d05 y2000m01d10 ...
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : uv.nc
+        variables : vouv  : Mean U.V at T point
+                    vozocrtx_t : Mean U at T point
+                    vomecrty_t : Mean V at T point
+                    vouv_prime : Mean U'.V' at T point
+ +

cdfvFWov

+ +
  usage : cdfvFWov V-secfile S-secfile ZGR-secfile HGR-secfile MSK-secfile
+      PURPOSE :
+         Compute the fresh water transport and its overturning component through
+         a section specified by the input files (data and metrics).
+       
+      ARGUMENTS :
+         All arguments are 'section files', which are assumed to be files with
+         2 zonal lines of data ( j and j+1 ): 
+          - V_secfile : meridional velocity section file.
+          - S_secfile : salinity section file.
+          - ZGR_secfile : mesh_zgr section file 
+          - HGR_secfile : mesh_hgr section file 
+          - MSK_secfile : mask section file 
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : vFWov.nc
+        variables : netvFW, totvFW, ovFW
+        Output file only has time relevant dimension. Other dims are set to 1.
+        Degenerated dimensions can be removed with :
+            ncwga -a x,y,depthw vFWov.nc -o out.nc
+ +

cdfvT

+ +
  usage : cdfvT CONFIG-CASE [-o output_file ] [-nc4 ] 'list_of_tags' 
+      PURPOSE :
+        Compute the time average values for second order products 
+        V.T, V.S, U.T and U.S used in heat and salt transport computation.
+       
+      ARGUMENTS :
+        CONFIG-CASE is the config name of a given experiment (eg ORCA025-G70)
+             The program will look for gridT, gridU and gridV files for
+             this config ( grid_T, grid_U and grid_V are also accepted).
+             Additionaly, if gridS or grid_S file is found, it will be taken
+             in place of gridT for the salinity variable.
+        [-nc4 ] use netcdf4 output with chunking and deflation 1
+        [-o output file ] default :vt.nc  must be before tag list
+        list_of_tags : a list of time tags that will be used for time
+             averaging. e.g. y2000m01d05 y2000m01d10 ...
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : vt.nc
+        variables : vozout, vozous, vomevt and vomevs
+ +

cdfvar

+ +
  usage : cdfbathy/cdfvar -f IN-file [options]
+       
+      PURPOSE :
+        Allow manual modification of the input file. Very convenient
+        for bathymetric files, can also be used with any model file
+        Keep a log.f90 file of the modifications for automatic reprocessing
+       
+      ARGUMENTS :
+        IN-file : original input file. The program works on a copy of the
+                 original file (default)
+       
+      OPTIONS :
+        -file (or -f )       : name of input file 
+        -var  (or -v )       : name of cdf variable [default: Bathymetry]
+        -lev  (or -l )       : level to work with 
+        -time (or -t )       : time to work with 
+        -scale  s            : use s as a scale factor (divide when read the file)
+        -zoom (or -z )       : sub area of the bathy file to work with (imin imax jmin jmax)
+        -fillzone (or -fz )  : sub area will be filled with 0 up to the first coast line 
+        -fillpool (or -fp ) [ icrit ] : the whole file is check and fill all the pool smaller than (icrit) cell by 0
+        -raz_zone (or -raz ) : sub area will be filled with 0 up 
+        -raz_below depmin    : any depth less than depmin in subarea will be replaced by 0 
+           (or -rb depmin )  
+        -set_below depmin    : any depth less than depmin in subarea will be replaced by depmin 
+           (or -sb depmin ) 
+        -fullstep depmin     : sub area will be reshaped as full-step, below depmin
+           (or -fs depmin )    requires the presence of the file zgr_bat.txt (from ocean.output, eg )
+        -dumpzone (or -d )   : sub area will be output to an ascii file, which can be used by -replace
+                               after manual editing 
+        -nicedumpzone        : sub area will be output to an ascii file (nice output)
+                 (or -nd )
+        -replace (or -r )    : sub area defined by the file will replace the original bathy
+        -append (or -a )     : fortran log file (log.f90) will be append with actual modif
+                               Standard behaviour is to overwrite/create log file
+        -overwrite (or -o )  : input bathy file will be used as output.
+                               Standard behaviour is to use a work copy of the original file
+                               (indexed from 01 to 99 if necessary ) 
+        -log logfile         : log file for change (default is log.f90) 
+       
+      OUTPUT : 
+           netcdf file : according to used options, if the original file is to be modified
+                  a sequence number is added at the end of the input file name, to keep
+                  modifications.
+             variables : same as input file
+ +

cdfvertmean

+ +
  usage :  cdfvertmean [-debug] IN-file IN-var1,var2,.. v-type dep1 dep2 [-full]
+               ... [-o OUT-file ]
+       
+      PURPOSE :
+        Compute the vertical mean between dep1 and dep2 given in m,
+        for variable IN-var in the input file.
+       
+      ARGUMENTS :
+        IN-file  : netcdf input file.
+        IN-var1,var2,.. : Comma separated list of input variables to process.
+        v-type   : one of T U V W indicating position of variable on C-grid
+        dep1 dep2 : depths limit for vertical integration (meters), from top 
+                 to bottom, positive depths.
+       
+      OPTIONS :
+        [-full  ] : for full step configurations. Default is partial step.
+        [-debug ] : print some extra informations.
+        [-o OUT-file ] : specify output file instead of vertmean.nc
+       
+      REQUIRED FILES :
+        mesh_zgr.nc and mask.nc
+       
+      OUTPUT : 
+        netcdf file : vertmean.nc
+          variables : varin_vertmean (same units as input variable)
+       
+ +

cdfvhst

+ +
  usage : cdfvhst  VTfile [-full ]
+      PURPOSE :
+          Computes the vertically integrated heat and salt transports 
+          at each grid cell.
+       
+      ARGUMENTS :
+          VTfile : file which contains UT, VT, US, VS quantities
+               (produced by cdfvT.f90)
+       
+      OPTIONS :
+          [ -full ] : use full step computation (default is partial steps).
+       
+      REQUIRED FILES :
+          Files mesh_hgr.nc, mesh_zgr.nc
+       
+      OUTPUT : 
+          Netcdf file : trp.nc
+          Variables : somevt, somevs, sozout and  sozous
+ +

cdfvint

+ +
  usage : cdfvint T-file [IN-var] [-GSOP] [-OCCI] [-full] [-nc4] [-o OUT-file]
+                  [-tmean] [-smean]
+       
+      PURPOSE :
+           Compute the vertical integral of the variable from top 
+        to bottom, and save the cumulated valued, level by level.
+        For temperature (default var), the integral is transformed
+        to Heat Content ( 10^6 J/m2) hence for salinity, the integral
+        represents PSU.m 
+       
+      ARGUMENTS :
+          T-file : gridT file holding either temperature or salinity 
+         [IN-var ] : name of input variable to process. Default is 
+                votemper. Can also be vosaline
+       
+      OPTIONS :
+         -GSOP : Use 7 GSOP standard level for the output 
+                 Default is to take the model levels for the output
+         -OCCI : Use 3 levels for the output: 700m, 2000m and bottom
+                 Default is to take the model levels for the output
+         -full : for full step computation 
+         -nc4  : use netcdf4 output with chunking and deflation
+         -tmean : output mean temperature instead of heat content
+         -smean : output mean salinity instead of PSU.m
+         -o OUT-file : use specified output file instead of <IN-var>.nc
+       
+      REQUIRED FILES :
+        mask.nc, mesh_hgr.nc and mesh_zgr.nc
+       
+      OUTPUT : 
+        netcdf file :  VAR-name.nc (or specified with -o option)
+          variables :  either voheatc or vohsalt, unless -tmean or -smean used
+                In this latter case, variables are votemper and 
+               vosaline
+       
+      SEE ALSO :
+         cdfvertmean, cdfheatc, cdfmxlhcsc and  cdfmxlheatc
+       
+ +

cdfvita

+ +
  usage : cdfvita U-file V_file T-file [-w W-file] [-geo ] [-cubic] [-nc4] ...
+                  ... [-o OUT-file] [-lev level_list]
+       
+      PURPOSE :
+        Create a file with velocity components, module  and direction
+        at T points from file on C-grid. T-file is used only for
+        getting the header of the output file. Any file on T grid
+        can be used.
+       
+      ARGUMENTS :
+        U-file  : netcdf file with zonal component of velocity
+        V-file  : netcdf file with meridional component of velocity
+        T-file  : netcdf file with T points header OK.
+       
+      OPTIONS :
+        [ -w W-file ] : if used, also compute vertical velocities at
+                        T points.
+        [ -geo ]     : indicate that input velocity files are produced 
+                       by cdfgeo-uv, hence ugeo on V-point, vgeo on U-points
+                       ( U-file and V_file are the same !)
+        [ -cubic ]   : Save the cube of the veocity module 
+        [ -nc4 ]     : Use netcdf4 output with chunking and deflation level 1
+                  This option is effective only if cdftools are compiled with
+                  a netcdf library supporting chunking and deflation.
+        [ -o OUT-file ] : Specify name of output file instead of vita.nc
+        [ -lev level_list] : specify a list of level to be used 
+                    (default option is to use all input levels).
+                    This option MUST be the last on the command line !!
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : vita.nc unless -o option is used
+          variables : sovitua, sovitva, sovitmod, sovitdir, [sovitmod3], [sovitw
+ a]
+ +

cdfvita-geo

+ +
  usage : cdfvita-geo  Ugeo-file Vgeo_file T-file [-w W-file] [-lev level_list]
+       
+      PURPOSE :
+        Create a file with velocity components and module computed
+        at T points from file on C-grid. T-file is used only for
+        getting the header of the output file. Any file on T grid
+        can be used.
+       
+      ARGUMENTS :
+        Ugeo-file  : netcdf file with zonal component of velocity
+        Vgeo-file  : netcdf file with meridional component of velocity
+        T-file  : netcdf file with T points header OK.
+       
+      OPTIONS :
+        [ -w W-file ] : if used, also compute vertical velocities at
+                        T points.
+        [ -lev level_list] : specify a list of level to be used 
+                    (default option is to use all input levels).
+                    This option MUST be the last on the command line !!
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : vita.nc
+          variables : sovitua, sovitva, sovitmod, [sovitwa]
+ +

cdfvsig

+ +
  usage : cdfvsig CONFIG  [-no-w] [-no-sig]  [-no-uv] [-T ] [-pref pref1,pref2,.
+ ..]
+         ... 'list_of_tags' 
+      PURPOSE :
+        Compute the time average values for second order products 
+        U.sig,  V.sig and W.sig.  Also save mean sigma-0 interpolated at
+        velocity points, as well as mean velocity component, for further use.
+       
+      ARGUMENTS :
+        CONFIG is the config name of a given experiment (eg ORCA025-G70)
+             The program will look for gridT, gridU, gridV  and gridW files for
+             this config ( grid_T, grid_U, grid_V and grid_W are also accepted).
+        list_of_tags : a list of time tags that will be used for time
+             averaging. e.g. y2000m01d05 y2000m01d10.
+             ! IMPORTANT : list_of_tag are at the end of the command line ! 
+       
+      OPTIONS ( to be used before the list_of tags ):
+         -T : compute u and v at T points, so that usig, vsig will be at T point
+         -no-w : no computation of vertical products
+         -no-sig : no output of density on U V points
+         -no-uv : no output of mean velocity components
+         -pref pref1,pref2,..: give comma separated list of reference depths for
+              density computation. eg : -pref 0,2000,3000  If not specified 
+              assumes pref=0.
+       
+      REQUIRED FILES :
+         mask.nc
+       
+      OUTPUT : 
+        netcdf file : usig.nc, vsig.nc and wsig.nc
+        variables : vousig, vovsig, vowsig : mean product v x sigma-0 
+                                             at velocity point.
+                    vosigu, vosigv, vosigw : mean sigma-0 at velocity point.
+                    vozocrtx, vomecrty, vovecrtz : mean velocity components.
+ +

cdfvtrp

+ +
  usage : cdfvtrp  U-file V-file [ -full ] [ -bathy ]
+      PURPOSE :
+        Computes the vertically integrated transports at each grid cell.
+       
+      ARGUMENTS :
+        U-file : netcdf gridU file
+        V-file : netcdf gridV file
+       
+      REQUIRED FILES :
+         mesh_hgr.nc and mesh_zgr.nc
+         mask.nc is required only with -bathy option.
+       
+      OPTIONS :
+        [-full ]  : To be used in case of full step configuration.
+                    Default is partial steps.
+        [-bathy ] : When used, cdfvtrp also compute the along slope
+                    and cross slope transport components.
+                    Bathymetry is read from mesh_zgr.nc file.
+       
+      OUTPUT : 
+        netcdf file : trp.nc
+        variables : 
+            sozoutrp : zonal transport.
+            somevtrp : meridional transport.
+           If option -bathy is used :
+            soastrp : along slope transport
+            socstrp : cross slope transport
+ +

cdfw

+ +
  usage : cdfw U-file V-file [ U-var V-var ] [ -full]
+       
+      PURPOSE :
+        Compute the vertical velocity from the vertical integration of
+        of the horizontal divergence of the velocity.
+       
+      ARGUMENTS :
+        U-file : netcdf file with the zonal velocity component.
+        V-file : netcdf file with the meridional velocity component.
+       
+      OPTIONS :
+        [ U-var V-var ] : names of the zonal and meridional velocity 
+                          components. Default are vozocrtx and vomecrty
+        [ -full ] : in case of full step configuration. Default is partial step.
+       
+      REQUIRED FILES :
+        mesh_hgr.nc and mesh_zgr.nc
+       
+      OUTPUT : 
+        netcdf file : w.nc
+          variables : vovecrtz (m/s)
+ +

cdfweight

+ +
  usage : cdfweight  [-f] IN-file [-c COORD-file] ... 
+               ...  [-t point_type] [-2d] [-v] 
+       
+      PURPOSE :
+        Produce a weight file for further bilinear collocalisation 
+        with cdfcoloc program. It takes the position of the points
+        to be collocated into a simple ascii file. 
+       
+      ARGUMENTS :
+        [-f ] IN-file   : input file is a iyxz ASCII file, 1 line per point.
+       
+      OPTIONS :
+        [-c COORD-file] : coordinate file [coordinates.nc]
+        [-t point_type] : point type on C-grid (either T U V or F ) [F]
+        [-2d ]          : tell cdfweight that only 2D weights are to be computed
+ .
+        [-v ]           : Verbose mode for extra information (debug mode).
+       
+      REQUIRED FILES :
+         coordinates.nc file if not passed as argument.
+         If working with 3D files, mesh_zgr.nc is required.
+       
+      OUTPUT : 
+        binary weight file : weight_point_type.bin
+        standard output : almost the same info that is saved in the binary file
+                    When using -v option, even more informations !
+ +

cdfwflx

+ +
  usage : cdfwflx T-file Runoff
+       
+      PURPOSE :
+        Computes the water fluxes components. Suitable for 
+        annual means files. All output variables are in mm/days.
+       
+      ARGUMENTS :
+        T-file  : model output file with water fluxes (gridT) 
+        Runoff : file with the climatological runoff on the
+                 model grid.
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        netcdf file : wflx.nc
+        variables : soevap, soprecip, sorunoff, sowadmp, sowaflux
+ +

cdfwhereij

+ +
  usage : cdfwhereij  imin imax jmin jmax [-c COOR-file ] [ -p point_type]
+       
+      PURPOSE :
+        Return the geographical coordinates of a model sub-area specified
+        in i,j space on the command line.
+       
+      ARGUMENTS :
+        imin imax jmin jmax : (i,j) space window coordinates
+       
+      OPTIONS :
+        [-c COOR_file  ] : specify a coordinates file.
+                       default is coordinates.nc
+        [-p point type ] : specify a point type on the C-grid (T U V F) 
+                       default is T
+       
+      REQUIRED FILES :
+        coordinates.nc or COOR-file given in the -c option
+       
+      OUTPUT : 
+        Standard output
+ +

cdfzisot

+ +
  usage : cdfzisot T-file RefTemp [Output File]
+       
+      PURPOSE :
+        Compute depth of an isotherm given as argument
+       
+      ARGUMENTS :
+        T-file  : input netcdf file (gridT)
+        RefTemp : Temperature of the isotherm.
+        Output File : netCDF Optional (defaults: zisot.nc)
+       
+      REQUIRED FILES :
+         mesh_zgr.nc
+          In case of FULL STEP configuration, bathy_level.nc is also required.
+       
+      OUTPUT : 
+        netcdf file : zisot.nc
+ +

cdfzonalmean

+ +
  usage : cdfzonalmean IN-file point_type [ BASIN-file] [-debug]...
+        ...[-var var1,var2,..] [-max ] [-pdep | --positive_depths]
+       
+      PURPOSE :
+        Compute the zonal mean of all the variables available in the
+        input file. This program assume that all the variables are
+        located on the same C-grid point, specified on the command line.
+          Using -var option limits the variables to be processed.
+       
+        Zonal mean is in fact the mean value computed along the I coordinate.
+        The result is a vertical slice, in the meridional direction.
+       
+        REMARK : partial step are not handled properly (but probably 
+                 minor impact on results).
+       
+      ARGUMENTS :
+        IN-file    : input netcdf file.
+        point_type : indicate the location on C-grid (T|U|V|F|W)
+       
+      OPTIONS :
+        [BASIN-file] : netcdf file describing sub basins, similar to 
+                       new_maskglo.nc. If this name is not given 
+                       as option, only the global zonal mean is computed.
+        [-max     ] : output the zonal maximum and minimum of the variable 
+        [-var var1,var2,.. ] : Comma separated list of selected variables
+        [-pdep | --positive_depths ] : use positive depths in the output file.
+                       Default behaviour is to have negative depths.
+        [-ndep_in ] : negative depths are used in the input file.
+                       Default behaviour is to have positive depths.
+        [-debug   ] : add some print for debug
+       
+      REQUIRED FILES :
+        mesh_hgr.nc, mesh_zgr.nc and mask.nc
+       
+      OUTPUT : 
+        netcdf file : zonalmean.nc
+          variables : output variable names are built with the following
+                      convention: zoxxxx_bas
+                       where zo replace vo/so prefix of the input variable
+                       where bas is a suffix for each sub-basins (or glo)
+                       if a BASIN-file is used.
+                  If option -max is used, each standard output variable
+                      is associated with a var_max variable.
+ +

cdfzonalmeanvT

+ +
  usage : cdfzonalmeanvT [-b BASIN-file] [-pdep |--positive_depths] ... 
+                    ...  [-ndep_in]   CONFIG-CASE  'list_of_tags' 
+       
+      PURPOSE :
+        Compute the mean product of zonal mean V by zonal mean of T and S.
+       
+        Zonal mean is in fact the mean value computed along the I coordinate.
+        The result is a vertical slice, in the meridional direction.
+       
+        REMARK : partial step are not handled properly (but probably 
+                 minor impact on results).
+       
+      ARGUMENTS :
+        CONFIG-CASE is the config name of a given experiment (eg ORCA025-G70)
+             The program will look for gridT, gridU and gridV files for
+             this config ( grid_T, grid_U and grid_V are also accepted).
+             Additionaly, if gridS or grid_S file is found, it will be taken
+             in place of gridT for the salinity variable.
+        list_of_tags : a list of time tags that will be used for time
+             averaging. e.g. y2000m01d05 y2000m01d10 ...
+       
+      OPTIONS :
+        [-b BASIN-file] : netcdf file describing sub basins, similar to 
+                       new_maskglo.nc. If this name is not given 
+                       as option, only the global zonal mean is computed.
+        [-pdep | --positive_depths ] : use positive depths in the output file.
+                       Default behaviour is to have negative depths.
+        [-ndep_in ] : negative depths are used in the input file.
+                       Default behaviour is to have positive depths.
+        [-debug   ] : add some print for debug
+       
+      REQUIRED FILES :
+        mesh_hgr.nc, mesh_zgr.nc and mask.nc
+       
+      OUTPUT : 
+        netcdf file : zonalmeanvt.nc
+          variables : zovzot : mean product of zonal_mean(V) x zonal_mean(T)
+                      zovzot : mean product of zonal_mean(V) x zonal_mean(S)
+                        A suffix _bas is append to variable name oin order to
+                      indicate the basin (atl, inp, ind, pac) or glo for global
+          
+ +

cdfzonalout

+ +
  usage :  cdfzonalout ZONAL-file
+       
+      PURPOSE :
+         This is a formatting program for zonal files, either mean or integral.
+         It displays results on the standard output from the input zonal file.
+         It only works with 1D zonal variables, skipping 2D variables, that
+         cannot be easily displayed !
+       
+      ARGUMENTS :
+         ZONAL-file : input netcdf zonal file produced by one of the zonal
+                      tools.
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+         - Standard output,  structured in columns:
+              J  LAT  ( zonal mean, var = 1--> nvar) 
+ +

cdfzonalsum

+ +
  usage : cdfzonalsum IN-file point_type [ BASIN-file] ...
+                   ... [-var var1,var2,..] [-pdep | --positive_depths]
+                   ... [-pdeg | --per_degree] [-debug]
+       
+      PURPOSE :
+        Compute the zonal sum of all the variables available in the
+        input file. This program assume that all the variables are
+        located on the same C-grid point, specified on the command line.
+          Using -var option limits the variables to be processed.
+       
+        Zonal sum is in fact the integral value computed along the I coordinate.
+        The result is a vertical slice, in the meridional direction.
+       
+        REMARK : partial step are not handled properly (but probably 
+                 minor impact on results).
+       
+      ARGUMENTS :
+        IN-file    : input netcdf file.
+        point_type : indicate the location on C-grid (T|U|V|F|W)
+       
+      OPTIONS :
+        [BASIN-file] : netcdf file describing sub basins, similar to 
+                       new_maskglo.nc. If this name is not given 
+                       as option, only the global zonal integral is computed.
+        [-var var1,var2,.. ] : Comma separated list of selected variables
+        [-pdep | --positive_depths ] : use positive depths in the output file.
+                       Default behaviour is to have negative depths.
+        [-pdeg | --per_degree ] : When using this option, the zonal integral
+                       is normalized per degree of latitude. This was formally
+                       done with cdfzonalintdeg program, which is now merged
+                       in this one.
+                       Default behaviour is not to normalize.
+        [-debug ] : add some print for debug
+       
+      REQUIRED FILES :
+        mesh_hgr.nc, mesh_zgr.nc and mask.nc
+       
+      OUTPUT : 
+        netcdf file : zonalsum.nc or zonalintdeg.nc (-pdeg option)
+          variables : output variable names are built with the following
+                      convention: zoixxxx_bas
+                       where zoi replace vo/so prefix of the input variable
+                       where bas is a suffix for each sub-basins (or glo)
+                       if a BASIN-file is used.
+             Units are modified by adding '.m2' at the end. Can be improved !
+             In addition, '.degree-1' is append to unit with -pdeg option.
+ +

cdfzoom

+ +
  usage : cdfzoom -f file -zoom imin imax jmin jmax  ...
+                ... -var cdfvar [-lev kmin kmax ] ...
+                ... [ -time tmin tmax ] [ -fact factor] 
+      PURPOSE :
+       Display the numerical values of a zoomed area. By
+       default, all times and levels are shown. If the zoomed
+       area is degenerated to a single line, then the vertical
+       slab is displayed.
+       
+      ARGUMENTS :
+        -f file : name of input file
+        -zoom imin imax jmin jmax : spatial window definition
+        -var cdfvar : cdf variable name to work with.
+       
+      OPTIONS :
+        [-lev kmin kmax ]  : vertical limits for display.
+        [-time tmin tmax ] : time limits for display.
+        [-fact factor ]    : use a scaling factor for display.
+                             Values are DIVIDED by factor
+       
+      REQUIRED FILES :
+         none
+       
+      OUTPUT : 
+        display on standard output
+ 
+ +

AUTHORS

+ +

Project headed by Jean-Marc Molines, (IGE, Grenoble - France)

+ +

Contributors (alphabetic order ) : C.Q. Akuetevi, M. Balmaseda, E. Behrens, F. Castruccio, M. Chekki, P. Colombo, J. Deshayes, N. Djath, N. Ducousso, C. Dufour, R. Dussin, N. Ferry, F. Hernandez, M. Juza, A. Lecointre, S. Leroux, G. Mainsant, P. Mathiot, A. Melet, X. Meunier, G. Moreau, N. Merino, W. Rath, J. Regidor, M. Scheinert, A.M. Treguier

+ +

LICENSE AND COPYRIGHT

+ +

Copyright (C) 1998-2016 IGE-MEOM (Jean-Marc.Molines@univ-grenoble-alpes.fr )

+ +

This software is governed by the CeCILL license under French law and abiding by the rules of distribution of free software. You can use, modify and/ or redistribute the software under the terms of the CeCILL license as circulated by CEA, CNRS and INRIA at the following URL "http://www.cecill.info".

+ +

As a counterpart to the access to the source code and rights to copy, modify and redistribute granted by the license, users are provided only with a limited warranty and the software's author, the holder of the economic rights, and the successive licensors have only limited liability.

+ +

In this respect, the user's attention is drawn to the risks associated with loading, using, modifying and/or developing or reproducing the software by the user in light of its specific status of free software, that may mean that it is complicated to manipulate, and that also therefore means that it is reserved for developers and experienced professionals having in-depth computer knowledge. Users are therefore encouraged to load and test the software's suitability as regards their requirements in conditions enabling the security of their systems and/or data to be ensured and, more generally, to use and operate it in the same conditions as regards security.

+ +

The fact that you are presently reading this means that you have had knowledge of the CeCILL license and that you accept its terms.

+ + + + + + + diff --git a/src/.gitignore b/src/.gitignore new file mode 100644 index 0000000..2d19fc7 --- /dev/null +++ b/src/.gitignore @@ -0,0 +1 @@ +*.html diff --git a/src/Makefile b/src/Makefile index c26ef39..d55c4cd 100644 --- a/src/Makefile +++ b/src/Makefile @@ -581,6 +581,7 @@ installman: @mkdir -p $(INSTALL_MAN)/man1; \cp -f cdftools.1 $(INSTALL_MAN)/man1/; for s in $$( cd $(BINDIR); ls -1 ); do ( cd $(INSTALL_MAN)/man1/; ln -sf cdftools.1 $$s.1 ); done; + \cp -f cdftools.html ../DOC/ f2py: f2py -c --fcompiler=gnu95 -m cdftoolspython cdficediags.f90 cdfio.o modcdfnames.o -I$(EBROOTNETCDFMINFORTRAN)/include -L$(EBROOTNETCDFMINFORTRAN)/lib64 -lnetcdf -lnetcdff From 2ccd0f069d40a6b1d5d6854ea9bcbcb1878e767a Mon Sep 17 00:00:00 2001 From: jmm Date: Wed, 11 Jan 2017 11:22:18 +0100 Subject: [PATCH 08/33] final fixes in the cdficb series: * add references in modcdfname for cn_icbmass and cn_icbmelt * rename tools to have the prefic cdficb_xxx * update the html doc file --- DOC/cdftools.html | 41 ++++++++++++++++++++++ src/Makefile | 13 +++---- src/{cdficbclimato.f90 => cdficb_clim.f90} | 8 ++--- src/{cdficbdiags.f90 => cdficb_diags.f90} | 10 +++--- src/modcdfnames.f90 | 3 ++ 5 files changed, 60 insertions(+), 15 deletions(-) rename src/{cdficbclimato.f90 => cdficb_clim.f90} (97%) rename src/{cdficbdiags.f90 => cdficb_diags.f90} (97%) diff --git a/DOC/cdftools.html b/DOC/cdftools.html index dec036f..28e7ddb 100644 --- a/DOC/cdftools.html +++ b/DOC/cdftools.html @@ -64,6 +64,8 @@
  • cdfheatc
  • cdfhflx
  • cdfhgradb
  • +
  • cdficb_clim
  • +
  • cdficb_diags
  • cdficediags
  • cdfimprovechk
  • cdfinfo
  • @@ -1559,6 +1561,45 @@

    cdfhgradb

    cdfbuoyflx +

    cdficb_clim

    + +
      usage : cdficb_clim 12-ICB-monthly-means-files
    +       
    +      PURPOSE :
    +         Compute the 2D field of icb mass and icb melt.
    +       
    +      ARGUMENTS :
    +        ICE-file : netcdf icb file
    +       
    +      REQUIRED FILES :
    +         mesh_hgr.nc and mask.nc
    +       
    +      OUTPUT : 
    +        netcdf file : icbdiags.nc
    +          variables : Mass  (Kg/m2 )
    +                      Melt  (Kg/m2/s )
    + +

    cdficb_diags

    + +
      usage : cdficb_diags ICB-file  
    +       
    +      PURPOSE :
    +         Compute the spatially integrated icb mass and melt flux.
    +       
    +      ARGUMENTS :
    +        ICB-file : a single netcdf icb file
    +       
    +      REQUIRED FILES :
    +         mesh_hgr.nc and mask.nc
    +       
    +      OUTPUT : 
    +        netcdf file : icbdiags.nc
    +          variables : [NS]Mass  (Kg )
    +                      [NS]Melt    (Kg/s )
    +                N = northern hemisphere
    +                S = southern hemisphere
    +        standard output
    +

    cdficediags

      usage : cdficediag ICE-file [-lim3] 
    diff --git a/src/Makefile b/src/Makefile
    index d55c4cd..17f54aa 100644
    --- a/src/Makefile
    +++ b/src/Makefile
    @@ -32,6 +32,7 @@ EXEC = cdfmoy cdfmoyt cdfstd  cdfmoy_weighted cdfmoy_freq cdfvT cdfuv\
            cdfprofile  cdfwhereij cdffindij cdfweight cdfmaxmoc cdfcensus cdfzoom cdfmax cdfprobe cdfinfo \
            cdf16bit cdfvita cdfvita-geo cdfconvert cdfflxconv cdfclip cdfsstconv cdfstrconv cdfbathy cdfvar \
            cdfisf_fill cdfisf_forcing cdfisf_rnf cdfisf_poolchk \
    +       cdficb_clim cdficb_diags \
            cdfcsp cdfcoloc cdfmltmask cdfstatcoord  cdfpolymask cdfsmooth cdfmkmask cdfdifmask\
            cdfgradT cdfhgradb cdfeddyscale_pass1 cdfeddyscale \
            cdfkempemekeepe cdfbci cdfbti cdfnrjcomp cdfcofdis cdfsections cdfnorth_unfold cdfovide cdfmppini\
    @@ -324,12 +325,6 @@ cdfmxlhcsc: cdfio.o  eos.o cdfmxlhcsc.f90
     cdficediags: cdfio.o  cdficediags.f90
     	$(F90) cdficediags.f90 -o $(BINDIR)/cdficediags cdfio.o modcdfnames.o $(FFLAGS)
     
    -cdficbclimato: cdfio.o  cdficbclimato.f90
    -	$(F90) cdficbclimato.f90 -o $(BINDIR)/cdficbclimato cdfio.o modcdfnames.o $(FFLAGS)
    -
    -cdficbdiags: cdfio.o  cdficbdiags.f90
    -	$(F90) cdficbdiags.f90 -o $(BINDIR)/cdficbdiags cdfio.o modcdfnames.o $(FFLAGS)
    -
     cdfzonalmean: cdfio.o  cdfzonalmean.f90
     	$(F90) $(OMP) cdfzonalmean.f90 -o $(BINDIR)/cdfzonalmean cdfio.o modcdfnames.o $(FFLAGS) 
     
    @@ -500,6 +495,12 @@ cdfisf_rnf: cdfio.o  cdfisf_rnf.f90
     cdfisf_poolchk: cdfio.o  modutils.o cdfisf_poolchk.f90
     	$(F90)   cdfisf_poolchk.f90  -o $(BINDIR)/cdfisf_poolchk cdfio.o modutils.o modcdfnames.o $(FFLAGS)
     
    +cdficb_clim: cdfio.o  cdficb_clim.f90
    +	$(F90) cdficb_clim.f90 -o $(BINDIR)/cdficb_clim cdfio.o modcdfnames.o $(FFLAGS)
    +
    +cdficb_diags: cdfio.o  cdficb_diags.f90
    +	$(F90) cdficb_diags.f90 -o $(BINDIR)/cdficb_diags cdfio.o modcdfnames.o $(FFLAGS)
    +
     cdfovide: cdfio.o  cdfovide.f90
     	$(F90) cdfovide.f90  -o $(BINDIR)/cdfovide cdfio.o modcdfnames.o $(FFLAGS)
     
    diff --git a/src/cdficbclimato.f90 b/src/cdficb_clim.f90
    similarity index 97%
    rename from src/cdficbclimato.f90
    rename to src/cdficb_clim.f90
    index 1744cf5..bea9885 100644
    --- a/src/cdficbclimato.f90
    +++ b/src/cdficb_clim.f90
    @@ -1,6 +1,6 @@
    -PROGRAM cdficbclimato
    +PROGRAM cdficb_clim
       !!======================================================================
    -  !!                     ***  PROGRAM  cdficbclimato  ***
    +  !!                     ***  PROGRAM  cdficb_clim  ***
       !!=====================================================================
       !!  ** Purpose : Compute the iceberg mass and melt
       !!
    @@ -42,7 +42,7 @@ PROGRAM cdficbclimato
     
       narg = iargc()
       IF ( narg == 0 ) THEN
    -     PRINT *,' usage : cdficbclimato 12-ICB-monthly-means-files'
    +     PRINT *,' usage : cdficb_clim 12-ICB-monthly-means-files'
          PRINT *,'      '
          PRINT *,'     PURPOSE :'
          PRINT *,'        Compute the 2D field of icb mass and icb melt.'
    @@ -171,4 +171,4 @@ PROGRAM cdficbclimato
       END DO ! time loop
       ierr = closeout(ncout)
     
    -END PROGRAM cdficbclimato
    +END PROGRAM cdficb_clim
    diff --git a/src/cdficbdiags.f90 b/src/cdficb_diags.f90
    similarity index 97%
    rename from src/cdficbdiags.f90
    rename to src/cdficb_diags.f90
    index e358cf5..f4d339f 100644
    --- a/src/cdficbdiags.f90
    +++ b/src/cdficb_diags.f90
    @@ -1,6 +1,6 @@
    -PROGRAM cdficbdiag
    +PROGRAM cdficb_diags
       !!======================================================================
    -  !!                     ***  PROGRAM  cdficbdiag  ***
    +  !!                     ***  PROGRAM  cdficb_diags  ***
       !!=====================================================================
       !!  ** Purpose : Compute the Ice volume, area and extend for each 
       !!               hemisphere
    @@ -15,7 +15,7 @@ PROGRAM cdficbdiag
       USE modcdfnames
       !!----------------------------------------------------------------------
       !! CDFTOOLS_3.0 , MEOM 2011
    -  !! $Id: cdficbdiags.f90 759 2014-07-21 22:01:28Z molines $
    +  !! $Id: cdficb_diags.f90 759 2014-07-21 22:01:28Z molines $
       !! Copyright (c) 2010, J.-M. Molines
       !! Software governed by the CeCILL licence (Licence/CDFTOOLSCeCILL.txt)
       !!----------------------------------------------------------------------
    @@ -56,7 +56,7 @@ PROGRAM cdficbdiag
     
       narg = iargc()
       IF ( narg == 0 ) THEN
    -     PRINT *,' usage : cdficbdiag ICB-file  '
    +     PRINT *,' usage : cdficb_diags ICB-file  '
          PRINT *,'      '
          PRINT *,'     PURPOSE :'
          PRINT *,'        Compute the spatially integrated icb mass and melt flux.'
    @@ -201,4 +201,4 @@ PROGRAM cdficbdiag
       END DO ! time loop
       ierr = closeout(ncout)
     
    -END PROGRAM cdficbdiag
    +END PROGRAM cdficb_diags
    diff --git a/src/modcdfnames.f90 b/src/modcdfnames.f90
    index 168ec88..e7aec40 100644
    --- a/src/modcdfnames.f90
    +++ b/src/modcdfnames.f90
    @@ -82,6 +82,9 @@ MODULE modCdfNames
       CHARACTER(LEN=256) :: cn_iowaflup='iowaflup' !: Ice Ocean Water flux ( + = freezing, - = melting)
       CHARACTER(LEN=256) :: cn_soicecov='soicecov' !: Ice cover
     
    +  CHARACTER(LEN=256) :: cn_iicbmass='berg_mass'!: Mass of Icebergs (kg/m2)
    +  CHARACTER(LEN=256) :: cn_iicbmelt='berg_melt'!: Melting rate of icebergs (kg/m2/s)
    +
       ! MOC variables
       CHARACTER(LEN=256) :: cn_zomsfatl='zomsfatl' !: moc in the Atlantic
       CHARACTER(LEN=256) :: cn_zomsfglo='zomsfglo' !: moc in the Global ocean
    
    From 1859465329577ab7f0c954a135f557b9c16f1e5e Mon Sep 17 00:00:00 2001
    From: jvegasbsc 
    Date: Thu, 12 Jan 2017 11:42:02 +0100
    Subject: [PATCH 09/33] ERR_HDL now stop programs with exit code != 0
    
    ---
     src/cdfio.F90 | 2 +-
     1 file changed, 1 insertion(+), 1 deletion(-)
    
    diff --git a/src/cdfio.F90 b/src/cdfio.F90
    index 28c268e..5b06ca9 100644
    --- a/src/cdfio.F90
    +++ b/src/cdfio.F90
    @@ -2787,7 +2787,7 @@ SUBROUTINE ERR_HDL(kstatus)
         IF (kstatus /=  NF90_NOERR ) THEN
            PRINT *, 'ERROR in NETCDF routine, status=',kstatus
            PRINT *,NF90_STRERROR(kstatus)
    -       STOP
    +       STOP 1
         END IF
     
       END SUBROUTINE ERR_HDL
    
    From 5e92d6f8155c95f76059560aa79932a3adf09ea7 Mon Sep 17 00:00:00 2001
    From: jmm 
    Date: Sat, 14 Jan 2017 19:45:29 +0100
    Subject: [PATCH 10/33] Add -o option in cdfpolymask. Add -p and -ref switch to
     pass the name of mandatory files
    
    ---
     src/cdfpolymask.f90 | 20 ++++++++++++--------
     1 file changed, 12 insertions(+), 8 deletions(-)
    
    diff --git a/src/cdfpolymask.f90 b/src/cdfpolymask.f90
    index e6f3d06..d619b32 100644
    --- a/src/cdfpolymask.f90
    +++ b/src/cdfpolymask.f90
    @@ -50,7 +50,7 @@ PROGRAM cdfpolymask
     
       narg = iargc()
       IF ( narg < 2 ) THEN
    -     PRINT *,' usage : cdfpolymask POLY-file REF-file [ -r]'
    +     PRINT *,' usage : cdfpolymask -p POLY-file -ref REF-file [ -r] [-o OUT_file]'
          PRINT *,'      '
          PRINT *,'     PURPOSE :'
          PRINT *,'       Create a maskfile with polymask variable having 1'
    @@ -58,18 +58,22 @@ PROGRAM cdfpolymask
          PRINT *,'       the behaviour (0 inside, 1 outside).'
          PRINT *,'      '
          PRINT *,'     ARGUMENTS :'
    -     PRINT *,'       POLY-file : input ASCII file describing a polyline in I J grid.'
    +     PRINT *,'       -p POLY-file : input ASCII file describing a polyline in I J grid.'
          PRINT *,'            This file is structured by block, one block corresponding '
          PRINT *,'            to a polygon:'
          PRINT *,'              1rst line of the block gives a polygon name'
          PRINT *,'              2nd line gives the number of vertices (nvert) and a dummy 0'
          PRINT *,'              the block finishes  with nvert pairs of (I,J) describing '
          PRINT *,'              the polygon vertices.'
    -     PRINT *,'       REF-file  : reference netcdf file for header of polymask file.'
    +     PRINT *,'       -ref REF-file  : reference netcdf file for header of polymask file.'
    +     PRINT *,'             This file will be used to look for domain dimensions, and '
    +     PRINT *,'             in order to build the output file (nav_lon, nav_lat etc ...)'
          PRINT *,'      '
          PRINT *,'     OPTIONS :'
          PRINT *,'        [ -r ] : revert option. When used, 0 is inside the polygon,'
          PRINT *,'                 1 outside.'
    +     PRINT *,'        [ -o OUT-file ] : spefify the name of the output mask file instead'
    +     PRINT *,'                 of ',TRIM(cf_out)
          PRINT *,'      '
          PRINT *,'     REQUIRED FILES :'
          PRINT *,'       none' 
    @@ -81,16 +85,16 @@ PROGRAM cdfpolymask
       ENDIF
     
       ijarg = 1 
    -  CALL getarg (ijarg, cf_poly) ; ijarg = ijarg + 1
    -  CALL getarg (ijarg, cf_ref ) ; ijarg = ijarg + 1
     
       DO WHILE ( ijarg <= narg ) 
          CALL getarg (ijarg, cldum) ; ijarg = ijarg + 1
          SELECT CASE ( cldum ) 
    -     CASE ( '-r' ) ; lreverse = .TRUE.
    +     CASE ( '-p'   ) ; CALL getarg (ijarg, cf_poly ) ; ijarg = ijarg + 1
    +     CASE ( '-ref' ) ; CALL getarg (ijarg, cf_ref  ) ; ijarg = ijarg + 1
    +     CASE ( '-o'   ) ; CALL getarg (ijarg, cf_out  ) ; ijarg = ijarg + 1
    +     CASE ( '-r'   ) ; lreverse = .TRUE.
          CASE DEFAULT
    -        PRINT *,' unknown optional arugment (', TRIM(cldum),' )'
    -        PRINT *,' in actual version only -r -- for reverse -- is recognized '
    +        PRINT *,' unknown optional argument (', TRIM(cldum),' )'
             STOP
          END SELECT
       END DO
    
    From c7a268977b1af1db1be27a6f40a8e3c8ff3e8289 Mon Sep 17 00:00:00 2001
    From: jmm 
    Date: Fri, 20 Jan 2017 11:10:07 +0100
    Subject: [PATCH 11/33] add an option in cdf_xtrac_brokenline for saving VT and
     VS product too
    
    ---
     src/cdf_xtrac_brokenline.f90 | 68 +++++++++++++++++++++++++++++-------
     1 file changed, 55 insertions(+), 13 deletions(-)
    
    diff --git a/src/cdf_xtrac_brokenline.f90 b/src/cdf_xtrac_brokenline.f90
    index 7f104a2..36e68e6 100644
    --- a/src/cdf_xtrac_brokenline.f90
    +++ b/src/cdf_xtrac_brokenline.f90
    @@ -44,8 +44,8 @@ PROGRAM cdf_xtract_brokenline
        INTEGER(KIND=4) :: np_e1vn, np_e3un, np_e3vn       !  "
        INTEGER(KIND=4) :: np_vmod, np_e1v,  np_e3v        !  "
        INTEGER(KIND=4) :: np_vmsk, np_baro, np_bat        !  "
    -   INTEGER(KIND=4) :: np_ssh,  np_mld                 !  "
    -   INTEGER(KIND=4) :: np_icethick, np_icefra         !  "
    +   INTEGER(KIND=4) :: np_ssh,  np_mld,  np_vt, np_vs  !  "
    +   INTEGER(KIND=4) :: np_icethick, np_icefra          !  "
        INTEGER(KIND=4), DIMENSION(:), ALLOCATABLE :: ncout                     ! Netcdf error and ncid
        INTEGER(KIND=4), DIMENSION(:), ALLOCATABLE :: ipk, id_varout  ! netcdf output stuff
     
    @@ -82,7 +82,8 @@ PROGRAM cdf_xtract_brokenline
        REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: temper, saline      ! model Temperature and salinity
        REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: uzonal, vmerid      ! model zonal and meridional velocity
        REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: ssh, rmld           ! model SSH and MLD
    -   REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: ricethick, ricefra    ! ice thickness and fraction
    +   REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: ricethick, ricefra  ! ice thickness and fraction
    +   REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: zvmod               ! ice thickness and fraction
        ! along section array (dimension x,z or x,1 )
        REAL(KIND=4), DIMENSION(:,:),   ALLOCATABLE :: tempersec, salinesec, uzonalsec, vmeridsec
        REAL(KIND=4), DIMENSION(:,:),   ALLOCATABLE :: sshsec, rmldsec
    @@ -98,6 +99,7 @@ PROGRAM cdf_xtract_brokenline
     
        CHARACTER(LEN=255) :: cf_tfil , cf_ufil, cf_vfil   ! input T U V files
        CHARACTER(LEN=255) :: cf_icefil                    ! input ice file
    +   CHARACTER(LEN=255) :: cf_root=''                   ! root name used as prefix
        CHARACTER(LEN=255) :: cf_out                       ! output file
        CHARACTER(LEN=255) :: cf_secdat                    ! output section file (suitable for cdftransport or cdfsigtrp)
        CHARACTER(LEN=255) :: cverb='n'                    ! verbose key for findij
    @@ -112,6 +114,7 @@ PROGRAM cdf_xtract_brokenline
        LOGICAL  :: lssh     = .FALSE.                    ! flag for saving ssh
        LOGICAL  :: lmld     = .FALSE.                    ! flag for saving mld
        LOGICAL  :: lice     = .FALSE.                    ! flag for saving ice*
    +   LOGICAL  :: lvt      = .FALSE.                    ! flag for saving products vt, vs
        LOGICAL  :: ll_ssh, ll_mld, ll_ice                ! working flag for jk =1
     
        TYPE (variable), DIMENSION(:), ALLOCATABLE :: stypvar  ! variable definition and attributes
    @@ -124,7 +127,8 @@ PROGRAM cdf_xtract_brokenline
        narg = iargc()
        IF ( narg < 3 ) THEN
           PRINT *,' usage :  cdf_xtrac_brokenline T-file U-file V-file [ice-file] ....'
    -      PRINT *,'    [-f section_filei,sec_file2, ... ] [-verbose] [-ssh ] [-mld] [-ice]'
    +      PRINT *,'    [-f section_filei,sec_file2, ... ] [-verbose] [-ssh ] [-mld] [-ice] '
    +      PRINT *,'    [-vt] [-o ROOT_name]'
           PRINT *,'      '
           PRINT *,'     PURPOSE :'
           PRINT *,'        This tool extracts model variables from model files for a geographical' 
    @@ -169,15 +173,22 @@ PROGRAM cdf_xtract_brokenline
           PRINT *,'      -ssh     : also save ssh along the broken line.'
           PRINT *,'      -mld     : also save mld along the broken line.'
           PRINT *,'      -ice     : also save ice properties along the broken line.'
    +      PRINT *,'      -vt      : also save products vt and vs along the broken line.'
    +      PRINT *,'      -o ROOT-name : specified the prefix to be used for the output file name.'
    +      PRINT *,'                 Note that it may be a good idea to include a separator '
    +      PRINT *,'                 character such as _ at the end of the ROOT_name.'
           PRINT *,'     '
           PRINT *,'     REQUIRED FILES :'
    -      PRINT *,'      ', TRIM(cn_fhgr),' and ',TRIM(cn_fzgr),' must be in the current directory ' 
    +      PRINT *,'      ', TRIM(cn_fhgr),' and ',TRIM(cn_fzgr),' in the current directory ' 
           PRINT *,'      '
           PRINT *,'     OUTPUT : '
    -      PRINT *,'       netcdf file : section_name.nc'
    +      PRINT *,'       netcdf file : .nc (default). If -o option is used, the'
    +      PRINT *,'                     name will be .nc'
           PRINT *,'         variables : temperature, salinity, normal velocity, pseudo V metrics,'
    -      PRINT *,'                     mask, barotropic transport, bathymetry of velocity points.'
    -      PRINT *,'       ASCII file : section_name_section.dat usefull for cdftransport '
    +      PRINT *,'                    mask, barotropic transport, bathymetry of velocity points.'
    +      PRINT *,'                    Additional variables can be set when using options.'
    +      PRINT *,'       ASCII file : _section.dat usefull for cdftransport, gives'
    +      PRINT *,'                  the position in I,J of the geographical input points.'
           PRINT *,'      '
           PRINT *,'     SEE ALSO :'
           PRINT *,'        cdftransport, cdfmoc, cdfmocsig. This tool replaces cdfovide.' 
    @@ -193,7 +204,9 @@ PROGRAM cdf_xtract_brokenline
           CASE ( '-verbose' ) ; lverbose=.TRUE.  ; cverb='y'
           CASE ( '-ssh'     ) ; lssh    =.TRUE.  ; nvar = nvar + 1  ! 
           CASE ( '-mld'     ) ; lmld    =.TRUE.  ; nvar = nvar + 1  !
    -      CASE ( '-ice'     ) ; lice    =.TRUE.  ; nvar = nvar + 1  !
    +      CASE ( '-ice'     ) ; lice    =.TRUE.  ; nvar = nvar + 2  !
    +      CASE ( '-vt '     ) ; lvt     =.TRUE.  ; nvar = nvar + 2  !
    +      CASE ( '-o '      ) ;  CALL getarg(ijarg, cf_root) ; ijarg = ijarg + 1  !
           CASE ( '-f' )       ;  CALL getarg(ijarg, cldum) ; ijarg = ijarg + 1 ; lsecfile=.TRUE.
              CALL ParseFiles(cldum)        ! many section files can be given separated with comma
           CASE DEFAULT 
    @@ -370,6 +383,7 @@ PROGRAM cdf_xtract_brokenline
        ALLOCATE( batsec   (npsecmax-1,1  ), vmasksec (npsecmax-1,npk) )
        ALLOCATE( tempersec(npsecmax-1,npk), salinesec(npsecmax-1,npk) )
        ALLOCATE( uzonalsec(npsecmax-1,npk), vmeridsec(npsecmax-1,npk) )
    +   ALLOCATE( zvmod (npsecmax-1,1) )  ! working array
        IF ( lssh ) ALLOCATE ( sshsec (npsecmax-1,1) )
        IF ( lmld ) ALLOCATE ( rmldsec(npsecmax-1,1) )
        IF ( lice ) ALLOCATE(ricethicksec(npsecmax-1,1),ricefrasec(npsecmax-1,1))
    @@ -402,8 +416,8 @@ PROGRAM cdf_xtract_brokenline
     
        !  Loop on section for metrics and non z-depending variables
        DO jsec = 1, nsec   ! loop on sections
    -      cf_out    = TRIM(csection(jsec))//'.nc'
    -      cf_secdat = TRIM(csection(jsec))//'_section.dat'
    +      cf_out    = TRIM(cf_root)//TRIM(csection(jsec))//'.nc'
    +      cf_secdat = TRIM(cf_root)//TRIM(csection(jsec))//'_section.dat'
     
           ipoint = 1
           DO jleg=1, nsta(jsec) -1      ! loop on legs 
    @@ -615,12 +629,14 @@ PROGRAM cdf_xtract_brokenline
                 ierr = putvar (ncout(jsec), id_varout(np_una), uzonalsec(:,jk), jk, npsec(jsec)-1, 1, ktime=jt )
                 ierr = putvar (ncout(jsec), id_varout(np_vna), vmeridsec(:,jk), jk, npsec(jsec)-1, 1, ktime=jt )
                 ! along-track normal velocity, horiz. and vert. resolution, and mask
    -            ierr = putvar (ncout(jsec), id_varout(np_vmod),uzonalsec(:,jk) + vmeridsec(:,jk), &
    -                 &                                                  jk, npsec(jsec)-1, 1, ktime=jt ) 
    +            zvmod(:,1)= uzonalsec(:,jk) + vmeridsec(:,jk)
    +            ierr = putvar (ncout(jsec), id_varout(np_vmod), zvmod(:,1),              jk, npsec(jsec)-1, 1, ktime=jt ) 
                 IF (ll_ssh) ierr = putvar (ncout(jsec), id_varout(np_ssh), sshsec (:,jk), 1, npsec(jsec)-1, 1, ktime=jt )
                 IF (ll_mld) ierr = putvar (ncout(jsec), id_varout(np_mld), rmldsec(:,jk), 1, npsec(jsec)-1, 1, ktime=jt )
                 IF (ll_ice) ierr = putvar (ncout(jsec), id_varout(np_icethick), ricethicksec(:,jk), 1, npsec(jsec)-1, 1, ktime=jt )
                 IF (ll_ice) ierr = putvar (ncout(jsec), id_varout(np_icefra), ricefrasec(:,jk), 1, npsec(jsec)-1, 1, ktime=jt )
    +            IF (lvt )   ierr = putvar (ncout(jsec), id_varout(np_vt ), zvmod(:,1)*tempersec(:,jk), 1, npsec(jsec)-1, 1, ktime=jt )
    +            IF (lvt )   ierr = putvar (ncout(jsec), id_varout(np_vs ), zvmod(:,1)*salinesec(:,jk), 1, npsec(jsec)-1, 1, ktime=jt )
     
                 IF ( jt == 1 ) THEN   ! output of time independent variables at first time step only
                    ! save a mask of the section
    @@ -868,6 +884,7 @@ SUBROUTINE CreateOutputFile(ksec)
              stypvar(ivar)%cshort_name = cn_iicethic
              stypvar(ivar)%caxis       = 'TX'
              ipk(ivar)                 = 1     
    +         ivar = ivar + 1
        
              np_icefra = ivar
              stypvar(ivar)%cname       = cn_ileadfra
    @@ -878,6 +895,31 @@ SUBROUTINE CreateOutputFile(ksec)
              stypvar(ivar)%cshort_name = cn_ileadfra
              stypvar(ivar)%caxis       = 'TX'
              ipk(ivar)                 = 1
    +         ivar = ivar + 1
    +      ENDIF
    +     
    +      IF ( lvt ) THEN
    +         np_vt = ivar
    +         stypvar(ivar)%cname       = cn_vomevt
    +         stypvar(ivar)%cunits      = 'C.m/s'
    +         stypvar(ivar)%valid_min   = -10000.
    +         stypvar(ivar)%valid_max   = 1000000.
    +         stypvar(ivar)%clong_name  = 'VT product along '//TRIM(csection(ksec))//' section'
    +         stypvar(ivar)%cshort_name = cn_vomevt
    +         stypvar(ivar)%caxis       = 'TX'
    +         ipk(ivar)                 = 1
    +         ivar = ivar + 1
    +
    +         np_vs = ivar
    +         stypvar(ivar)%cname       = cn_vomevs
    +         stypvar(ivar)%cunits      = 'C.m/s'
    +         stypvar(ivar)%valid_min   = -10000.
    +         stypvar(ivar)%valid_max   = 1000000.
    +         stypvar(ivar)%clong_name  = 'VS product along '//TRIM(csection(ksec))//' section'
    +         stypvar(ivar)%cshort_name = cn_vomevs
    +         stypvar(ivar)%caxis       = 'TX'
    +         ipk(ivar)                 = 1
    +         ivar = ivar + 1
           ENDIF
     
           ! create output fileset
    
    From 9e387079cc192276c12f81f5251985813005b22d Mon Sep 17 00:00:00 2001
    From: jmm 
    Date: Fri, 20 Jan 2017 11:11:08 +0100
    Subject: [PATCH 12/33] update documentation html file for new optiosn in
     cdf_xtrac_brokenline
    
    ---
     DOC/cdftools.html | 18 +++++++++++++-----
     1 file changed, 13 insertions(+), 5 deletions(-)
    
    diff --git a/DOC/cdftools.html b/DOC/cdftools.html
    index 28e7ddb..e284a5a 100644
    --- a/DOC/cdftools.html
    +++ b/DOC/cdftools.html
    @@ -284,7 +284,8 @@ 

    cdf2matlab

    cdf_xtrac_brokenline

      usage :  cdf_xtrac_brokenline T-file U-file V-file [ice-file] ....
    -     [-f section_filei,sec_file2, ... ] [-verbose] [-ssh ] [-mld] [-ice]
    +     [-f section_filei,sec_file2, ... ] [-verbose] [-ssh ] [-mld] [-ice] 
    +     [-vt] [-o ROOT_name]
            
           PURPOSE :
              This tool extracts model variables from model files for a geographical
    @@ -329,15 +330,22 @@ 

    cdf_xtrac_brokenline

    -ssh : also save ssh along the broken line. -mld : also save mld along the broken line. -ice : also save ice properties along the broken line. + -vt : also save products vt and vs along the broken line. + -o ROOT-name : specified the prefix to be used for the output file name. + Note that it may be a good idea to include a separator + character such as _ at the end of the ROOT_name. REQUIRED FILES : - mesh_hgr.nc and mesh_zgr.nc must be in the current directory + mesh_hgr.nc and mesh_zgr.nc in the current directory OUTPUT : - netcdf file : section_name.nc + netcdf file : <section_name>.nc (default). If -o option is used, the + name will be <ROOT-name><section_name>.nc variables : temperature, salinity, normal velocity, pseudo V metrics, - mask, barotropic transport, bathymetry of velocity points. - ASCII file : section_name_section.dat usefull for cdftransport + mask, barotropic transport, bathymetry of velocity points. + Additional variables can be set when using options. + ASCII file : <section_name>_section.dat usefull for cdftransport, gives + the position in I,J of the geographical input points. SEE ALSO : cdftransport, cdfmoc, cdfmocsig. This tool replaces cdfovide. From 3e6997a7aac046f03cd2ce120e1ab9823caa5de3 Mon Sep 17 00:00:00 2001 From: jmm Date: Fri, 20 Jan 2017 12:58:13 +0100 Subject: [PATCH 13/33] add -o option in cdfheatc in order to have netcdf output as well * also rationalize the options adding -f and -zoom --- src/cdfheatc.f90 | 132 +++++++++++++++++++++++++++++++++++++---------- 1 file changed, 106 insertions(+), 26 deletions(-) diff --git a/src/cdfheatc.f90 b/src/cdfheatc.f90 index 4fb73e0..fdd627f 100644 --- a/src/cdfheatc.f90 +++ b/src/cdfheatc.f90 @@ -19,6 +19,7 @@ PROGRAM cdfheatc !!---------------------------------------------------------------------- IMPLICIT NONE + INTEGER(KIND=4), PARAMETER :: jp_hc3d=1, jp_hc2d=2 , jp_hcvol=3 INTEGER(KIND=4) :: jk, jt ! dummy loop index INTEGER(KIND=4) :: ik ! working integer INTEGER(KIND=4) :: ierr ! working integer @@ -28,12 +29,15 @@ PROGRAM cdfheatc INTEGER(KIND=4) :: mxloption=0 ! mixed layer option INTEGER(KIND=4) :: narg, iargc, ijarg ! command line INTEGER(KIND=4) :: npiglo, npjglo ! size of the domain - INTEGER(KIND=4) :: npk, npt ! size of the domain + INTEGER(KIND=4) :: npk, npkk,npt ! size of the domain INTEGER(KIND=4) :: nvpk ! vertical levels in working variable + INTEGER(KIND=4) :: ncout + INTEGER(KIND=4), DIMENSION(:), ALLOCATABLE :: ipk, id_varout ! for output variables REAL(KIND=4), PARAMETER :: pprho0=1020. ! water density (kg/m3) REAL(KIND=4), PARAMETER :: ppcp=4000. ! calorific capacity (J/kg/m3) + REAL(KIND=4), DIMENSION(1,1) :: zdum ! working pseudo array for nc output REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: e1t, e2t ! horizontal metrics REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: e3t ! vertical metric REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: temp ! temperature @@ -49,84 +53,96 @@ PROGRAM cdfheatc REAL(KIND=8) :: dsum2d ! weigthed sum per layer REAL(KIND=8) :: dsurf ! surface of a layer + TYPE(variable), DIMENSION(:), ALLOCATABLE :: stypvar ! structure for attributes + CHARACTER(LEN=256) :: cf_tfil ! input gridT file + CHARACTER(LEN=256) :: cf_out='heatc.nc' ! netcdf output file CHARACTER(LEN=256) :: cldum ! dummy character variable LOGICAL :: lfull=.FALSE. ! flag for full step computation LOGICAL :: lchk ! flag for missing files + + ! NETCDF OUTPUT !!---------------------------------------------------------------------- CALL ReadCdfNames() narg = iargc() IF ( narg == 0 ) THEN - PRINT *,' usage : cdfheatc T-file ...' - PRINT *,' ... [imin imax jmin jmax kmin kmax] [-full] ' + PRINT *,' usage : cdfheatc -f T-file [-mxloption option] ...' + PRINT *,' [-zoom imin imax jmin jmax kmin kmax] [-full] [-o OUT-file]' PRINT *,' ' PRINT *,' PURPOSE :' - PRINT *,' Computes the heat content in the specified area (Joules)' - PRINT *,' A sub-domain can be specified in option.' + PRINT *,' Computes the heat content in the specified 3D area (Joules)' PRINT *,' ' PRINT *,' ARGUMENTS :' - PRINT *,' T-file : a file with temperature and salinity' + PRINT *,' -f T-file : name of the input file with temperature (and MLD if needed).' PRINT *,' ' PRINT *,' OPTIONS :' - PRINT *,' [imin imax jmin jmax kmin kmax] : limit of a sub domain where' + PRINT *,' [-zoom imin imax jmin jmax kmin kmax] : limit of a sub domain where' PRINT *,' the heat content will be calculated.' PRINT *,' - if imin = 0 then ALL i are taken' PRINT *,' - if jmin = 0 then ALL j are taken' PRINT *,' - if kmin = 0 then ALL k are taken' PRINT *,' [-full ] : assume full step model output instead of default' PRINT *,' partial steps.' - PRINT *,' [-mxloption ] : pass 1 to compute only in the mixed layer, -1 to exclude' - PRINT *,' it from the calculations ' + PRINT *,' [-mxloption option]: option= 1 : compute only in the mixed layer,' + PRINT *,' option=-1 : exclude mixed layer in the computation' + PRINT *,' option= 0 : [Default], do not take care of mxl.' + PRINT *,' [-o OUT-file ] : specify netcdf output filename instead of ',TRIM(cf_out) PRINT *,' ' PRINT *,' REQUIRED FILES :' PRINT *,' Files ',TRIM(cn_fhgr),', ',TRIM(cn_fzgr),' and ',TRIM(cn_fmsk) PRINT *,' ' PRINT *,' OUTPUT : ' - PRINT *,' netcdf file : to be done ....' + PRINT *,' netcdf file : heatc.nc unless -o option is used.' + PRINT *,' variables: heatc3d (Joules)' + PRINT *,' : heatc(dep) (Joules) ' + PRINT *,' : heatc3dpervol (Joules/m3) ' PRINT *,' Standard output' STOP ENDIF ijarg = 1 - CALL getarg (ijarg, cf_tfil) ; ijarg = ijarg + 1 - - lchk = chkfile(cn_fhgr) - lchk = chkfile(cn_fzgr) .OR. lchk - lchk = chkfile(cn_fmsk) .OR. lchk - lchk = chkfile(cf_tfil) .OR. lchk - IF ( lchk ) STOP ! missing files - DO WHILE ( ijarg <= narg ) CALL getarg ( ijarg, cldum) ; ijarg = ijarg + 1 SELECT CASE ( cldum ) + CASE ( '-f' ) ; CALL getarg ( ijarg, cf_tfil) ; ijarg = ijarg + 1 CASE ( '-full' ) ; lfull = .true. - CASE ( '-mxloption' ) ; - CALL getarg ( ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) mxloption - CASE DEFAULT - PRINT *,' Reading 6 values : imin imax jmin jmax kmin kmax' - READ(cldum,*) iimin + CASE ( '-mxloption' ) ; CALL getarg ( ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) mxloption + CASE ( '-o ' ) ; CALL getarg ( ijarg, cf_out) ; ijarg = ijarg + 1 + CASE ( '-zoom' ) + 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 CALL getarg ( ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) ikmin CALL getarg ( ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) ikmax + CASE DEFAULT + PRINT *,' A single argument is considered as a T-file' + CALL getarg ( ijarg, cf_tfil) ; ijarg = ijarg + 1 END SELECT END DO + lchk = chkfile(cn_fhgr) + lchk = chkfile(cn_fzgr) .OR. lchk + lchk = chkfile(cn_fmsk) .OR. lchk + lchk = chkfile(cf_tfil) .OR. lchk + IF ( lchk ) STOP ! missing files + npiglo = getdim (cf_tfil,cn_x) npjglo = getdim (cf_tfil,cn_y) npk = getdim (cf_tfil,cn_z) npt = getdim (cf_tfil,cn_t) + npkk=npk + IF (iimin /= 0 ) THEN ; npiglo = iimax - iimin + 1; ELSE ; iimin=1 ; ENDIF IF (ijmin /= 0 ) THEN ; npjglo = ijmax - ijmin + 1; ELSE ; ijmin=1 ; ENDIF - IF (ikmin /= 0 ) THEN ; npk = ikmax - ikmin + 1; ELSE ; ikmin=1 ; ENDIF + IF (ikmin /= 0 ) THEN ; npkk = ikmax - ikmin + 1; ELSE ; ikmin=1 ; ikmax=npk ; ENDIF nvpk = getvdim(cf_tfil,cn_votemper) IF (nvpk == 2 ) nvpk = 1 - IF (nvpk == 3 ) nvpk = npk + IF (nvpk == 3 ) nvpk = npkk PRINT *, 'npiglo = ', npiglo PRINT *, 'npjglo = ', npjglo @@ -158,6 +174,8 @@ PROGRAM cdfheatc IF ( lfull ) e31d(:) = getvare3(cn_fzgr, cn_ve3t, npk) + CALL CreateOutput + DO jt=1,npt dvol = 0.d0 dsum = 0.d0 @@ -172,7 +190,7 @@ PROGRAM cdfheatc ! get e3t at level ik ( ps...) IF ( lfull ) THEN - e3t(:,:) = e31d(jk) + e3t(:,:) = e31d(ik) ELSE e3t(:,:) = getvar(cn_fzgr, 'e3t_ps', ik, npiglo, npjglo, kimin=iimin, kjmin=ijmin, ldiom=.TRUE.) ENDIF @@ -196,11 +214,73 @@ PROGRAM cdfheatc ELSE PRINT *, ' No points in the water at level ',ik,'(',gdepw(ik),' m) ' ENDIF + zdum(1,1) = pprho0*ppcp*dsum2d + ierr = putvar(ncout, id_varout(jp_hc2d), zdum(:,:),jk, 1, 1, ktime=jt ) END DO PRINT * ,' Total Heat content : ', pprho0*ppcp*dsum ,' Joules' PRINT * ,' Total Heat content/volume : ', pprho0*ppcp*dsum/dvol ,' Joules/m3 ' + zdum(1,1)=pprho0*ppcp*dsum + ierr = putvar(ncout, id_varout(jp_hc3d), zdum(:,:),1, 1, 1, ktime=jt ) + zdum(1,1)=zdum(1,1)/dvol + ierr = putvar(ncout, id_varout(jp_hcvol), zdum(:,:),1, 1, 1, ktime=jt ) END DO + ierr = closeout(ncout ) +CONTAINS + SUBROUTINE CreateOutput + !!--------------------------------------------------------------------- + !! *** ROUTINE CreateOutput *** + !! + !! ** Purpose : Create the netcdf outputfile + !! + !!---------------------------------------------------------------------- + ! so far in cdfheatc, only 4 variables willbe output. + ! indeed 4 scalar but that will be considered as (x,y,t) ie (1,1,t) + INTEGER(KIND=4) :: ivar=3, ierr + REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: zdumlon, zdumlat +! INTEGER(KIND=4), PARAMETER :: jp_hc3d=1; jp_hc2d=2 ; jp_hcvol=3 + !!---------------------------------------------------------------------- + ALLOCATE(stypvar(ivar) ) + ALLOCATE( ipk(ivar), id_varout(ivar) ) + ALLOCATE( zdumlon(1,1), zdumlat(1,1) ) + zdumlon(:,:) = 0. + zdumlat(:,:) = 0. + ipk(:)= 1 + ! define new variables for output + + stypvar%scale_factor = 1. + stypvar%add_offset = 0. + stypvar%savelog10 = 0. + stypvar%conline_operation = 'N/A' + stypvar%caxis = 'T' + + stypvar(jp_hc3d)%cname = 'heatc3d' + stypvar(jp_hc3d)%cunits = 'Joules' + stypvar(jp_hc3d)%clong_name = 'Total Heat Content' + stypvar(jp_hc3d)%cshort_name = 'heatc3d' + + stypvar(jp_hcvol)%cname = 'heatc3dpervol' + stypvar(jp_hcvol)%cunits = 'Joules/m3' + stypvar(jp_hcvol)%clong_name = 'Total Heat Content per unit volume' + stypvar(jp_hcvol)%cshort_name = 'heatc3dpervol' + + ipk(jp_hc2d) = npkk + stypvar(jp_hc2d)%cname = 'heatc2d' + stypvar(jp_hc2d)%cunits = 'Joules' + stypvar(jp_hc2d)%clong_name = 'Heat Content at each selected level' + stypvar(jp_hc2d)%cshort_name = 'heatc2d' + + ncout = create (cf_out, 'none', 1, 1, npkk, cdep='depthw' ) + ierr = createvar (ncout, stypvar, ivar, ipk, id_varout ) + ierr = putheadervar(ncout, cf_tfil, 1, 1, npkk, & + & pnavlon=zdumlon, pnavlat=zdumlat, & + & pdep=gdepw(ikmin:ikmax), & + & cdep='depthw' ) + tim(:)= putvar1d(ncout, tim, npt, 'T') + + DEALLOCATE( zdumlon, zdumlat) + + END SUBROUTINE CreateOutput END PROGRAM cdfheatc From 809c4b3b86bd8cf607fbdd40589e63540725d5a2 Mon Sep 17 00:00:00 2001 From: jmm Date: Fri, 20 Jan 2017 13:00:38 +0100 Subject: [PATCH 14/33] update documentation for last version of cdfheatc --- DOC/cdftools.html | 22 +++++++++++++--------- 1 file changed, 13 insertions(+), 9 deletions(-) diff --git a/DOC/cdftools.html b/DOC/cdftools.html index e284a5a..d29accb 100644 --- a/DOC/cdftools.html +++ b/DOC/cdftools.html @@ -1482,32 +1482,36 @@

    cdfhdy3d

    cdfheatc

    -
      usage :  cdfheatc  T-file ...
    -     ... [imin imax jmin jmax kmin kmax] [-full] 
    +
      usage :  cdfheatc  -f T-file [-mxloption option] ...
    +      [-zoom imin imax jmin jmax kmin kmax] [-full] [-o OUT-file]
            
           PURPOSE :
    -         Computes the heat content in the specified area (Joules)
    -         A sub-domain can be specified in option.
    +         Computes the heat content in the specified 3D area (Joules)
            
           ARGUMENTS :
    -        T-file : a file with temperature and salinity
    +        -f T-file : name of the input file with temperature (and MLD if needed).
            
           OPTIONS :
    -        [imin imax jmin jmax kmin kmax] : limit of a sub domain where
    +        [-zoom imin imax jmin jmax kmin kmax] : limit of a sub domain where
                            the heat content will be calculated.
                         - if imin = 0 then ALL i are taken
                         - if jmin = 0 then ALL j are taken
                         - if kmin = 0 then ALL k are taken
             [-full ] : assume full step model output instead of default
                        partial steps.
    -        [-mxloption ] : pass 1 to compute only in the mixed layer, -1 to exclude
    -                        it from the calculations 
    +        [-mxloption option]: option= 1 : compute only in the mixed layer,
    +                             option=-1 : exclude mixed layer in the computation
    +                             option= 0 : [Default], do not take care of mxl.
    +        [-o OUT-file ] : specify netcdf output filename instead of heatc.nc
            
           REQUIRED FILES :
             Files mesh_hgr.nc, mesh_zgr.nc and mask.nc
            
           OUTPUT : 
    -        netcdf file : to be done ....
    +        netcdf file : heatc.nc unless -o option is used.
    +               variables: heatc3d (Joules)
    +                        : heatc(dep) (Joules) 
    +                        : heatc3dpervol (Joules/m3) 
             Standard output

    cdfhflx

    From b143b73fabcac9e157b1bd03644b45685e7fdd2b Mon Sep 17 00:00:00 2001 From: jmm Date: Fri, 20 Jan 2017 17:28:30 +0100 Subject: [PATCH 15/33] add -o option in cdfsum * also add keys for options : -f file -p type -v var -o out-file etc ... --- src/cdfsum.f90 | 170 ++++++++++++++++++++++++++++++------------------- 1 file changed, 104 insertions(+), 66 deletions(-) diff --git a/src/cdfsum.f90 b/src/cdfsum.f90 index 7eb37c0..c2eef79 100644 --- a/src/cdfsum.f90 +++ b/src/cdfsum.f90 @@ -30,9 +30,9 @@ PROGRAM cdfsum INTEGER(KIND=4) :: ijmin=0, ijmax=0 ! domain limitation for computation INTEGER(KIND=4) :: ikmin=0, ikmax=0 ! domain limitation for computation INTEGER(KIND=4) :: ierr ! working integer - INTEGER(KIND=4) :: narg, iargc ! command line + INTEGER(KIND=4) :: narg, iargc,ijarg ! command line INTEGER(KIND=4) :: npiglo, npjglo ! size of the domain - INTEGER(KIND=4) :: npk, npt ! size of the domain + INTEGER(KIND=4) :: npk, npkk, npt ! size of the domain INTEGER(KIND=4) :: nvpk ! vertical levels in working variable INTEGER(KIND=4) :: numout=10 ! logical unit INTEGER(KIND=4) :: ncout ! for netcdf output @@ -43,7 +43,6 @@ PROGRAM cdfsum REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: zmask ! npiglo x npjglo REAL(KIND=4), DIMENSION(:), ALLOCATABLE :: gdep ! depth REAL(KIND=4), DIMENSION(:), ALLOCATABLE :: tim ! time - REAL(KIND=4), DIMENSION(1,1) :: rdumlon, rdumlat ! dummy latitude and longitude REAL(KIND=4), DIMENSION(1,1) :: rdummy ! dummy 2d variable for result REAL(KIND=8) :: dvol, dvol2d ! volume of the ocean/ layer @@ -68,42 +67,82 @@ PROGRAM cdfsum LOGICAL :: lforcing ! forcing flag LOGICAL :: lchk ! flag for missing files + LOGICAL :: lerror=.FALSE. ! flag for missing arguments !!---------------------------------------------------------------------- CALL ReadCdfNames() narg= iargc() IF ( narg == 0 ) THEN - PRINT *,' usage : cdfsum IN-file IN-var T| U | V | F | W ... ' - PRINT *,' ... [imin imax jmin jmax kmin kmax] [-full ] ' + PRINT *,' usage : cdfsum -f IN-file -v IN-var -p T| U | V | F | W ... ' + PRINT *,' ... [-zoom imin imax jmin jmax kmin kmax] [-full ] [-o OUT-file] ' PRINT *,' ' PRINT *,' PURPOSE :' PRINT *,' Computes the sum value of the field (3D, weighted)' - PRINT *,' This sum can be optionally limited to a sub-area.' + PRINT *,' This sum can be optionally limited to a 3D sub-area.' PRINT *,' ' PRINT *,' ARGUMENTS :' - PRINT *,' IN-file : netcdf input file.' - PRINT *,' IN-var : netcdf variable to work with.' - PRINT *,' T| U | V | F | W : C-grid point where IN-var is located.' + PRINT *,' -f IN-file : netcdf input file.' + PRINT *,' -v IN-var : netcdf variable to work with.' + PRINT *,' -p T| U | V | F | W : C-grid point where IN-var is located.' PRINT *,' ' PRINT *,' OPTIONS :' - PRINT *,' [imin imax jmin jmax kmin kmax] : limit of the sub area to work with.' + PRINT *,' [-zoom imin imax jmin jmax kmin kmax] : limit of the 3D sub area. ' PRINT *,' if imin=0 all i are taken' PRINT *,' if jmin=0 all j are taken' PRINT *,' if kmin=0 all k are taken' + PRINT *,' [ -full : ] Use full steps instead of default partial steps' + PRINT *,' [-o OUT-file ] : name of the output file instead of', TRIM(cf_out) PRINT *,' ' PRINT *,' REQUIRED FILES :' PRINT *,' ', TRIM(cn_fhgr),', ',TRIM(cn_fzgr),' and ',TRIM(cn_fmsk) PRINT *,' ' PRINT *,' OUTPUT : ' PRINT *,' Standard output.' - PRINT *,' netcdf file : ',TRIM(cf_out),' with 2 variables : vertical profile of sum' - PRINT *,' and 3D sum.' + PRINT *,' netcdf file : ',TRIM(cf_out),' unless modified with -o option. ' + PRINT *,' - 2 variables : vertical profile of sum and 3D sum.' + PRINT *,' names are sum_ and sum3D_.' + PRINT *,' ' + PRINT *,' SEE ALSO: ' + PRINT *,' cdfmean ' STOP ENDIF - CALL getarg (1, cf_in) - CALL getarg (2, cv_in) - CALL getarg (3, cvartype) + ijarg=1 + ! mandatory arguments are set to none by default for further check + cf_in='none' ; cv_in='none'; cvartype='none' + DO WHILE ( ijarg <= narg ) + CALL getarg( ijarg, cldum) ; ijarg=ijarg+1 + SELECT CASE (cldum) + CASE ( '-f ' ) ; CALL getarg(ijarg, cf_in ) ; ijarg=ijarg+1 + CASE ( '-v ' ) ; CALL getarg(ijarg, cv_in ) ; ijarg=ijarg+1 + CASE ( '-p ' ) ; CALL getarg(ijarg, cvartype) ; ijarg=ijarg+1 + CASE ( '-o ' ) ; CALL getarg(ijarg, cf_out ) ; ijarg=ijarg+1 + CASE ( '-zoom' ) ; + 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 + CALL getarg(ijarg, cldum ) ; ijarg=ijarg+1 ; READ(cldum,*) ikmin + CALL getarg(ijarg, cldum ) ; ijarg=ijarg+1 ; READ(cldum,*) ikmax + CASE DEFAULT + PRINT *,' Option ', TRIM(cldum),' not understood ...' + STOP + END SELECT + ENDDO + + IF ( cf_in == 'none' ) THEN + PRINT *,' You must specify an input file with -f option' + lerror= lerror .OR. .TRUE. + ENDIF + IF ( cv_in == 'none' ) THEN + PRINT *,' You must specify an input variable with -v option' + lerror= lerror .OR. .TRUE. + ENDIF + IF ( cvartype == 'none' ) THEN + PRINT *,' You must specify a point type with -p option' + lerror= lerror .OR. .TRUE. + ENDIF + IF (lerror ) STOP lchk = chkfile(cn_fhgr) lchk = chkfile(cn_fzgr) .OR. lchk @@ -111,33 +150,19 @@ PROGRAM cdfsum lchk = chkfile(cf_in ) .OR. lchk IF ( lchk ) STOP ! missing file - IF (narg > 3 ) THEN - IF ( narg /= 9 ) THEN - PRINT *, ' ERROR : You must give 6 optional values (imin imax jmin jmax kmin kmax)' - STOP - ELSE - ! input optional iimin iimax ijmin ijmax - CALL getarg ( 4,cldum) ; READ(cldum,*) iimin - CALL getarg ( 5,cldum) ; READ(cldum,*) iimax - CALL getarg ( 6,cldum) ; READ(cldum,*) ijmin - CALL getarg ( 7,cldum) ; READ(cldum,*) ijmax - CALL getarg ( 8,cldum) ; READ(cldum,*) ikmin - CALL getarg ( 9,cldum) ; READ(cldum,*) ikmax - ENDIF - ENDIF - npiglo = getdim (cf_in,cn_x) npjglo = getdim (cf_in,cn_y) npk = getdim (cf_in,cn_z) nvpk = getvdim(cf_in,cv_in) npt = getdim (cf_in,cn_t) + npkk = npk IF (iimin /= 0 ) THEN ; npiglo = iimax - iimin + 1; ELSE ; iimin = 1 ; ENDIF IF (ijmin /= 0 ) THEN ; npjglo = ijmax - ijmin + 1; ELSE ; ijmin = 1 ; ENDIF - IF (ikmin /= 0 ) THEN ; npk = ikmax - ikmin + 1; ELSE ; ikmin = 1 ; ENDIF + IF (ikmin /= 0 ) THEN ; npkk = ikmax - ikmin + 1; ELSE ; ikmin = 1 ; ikmax = npk ; ENDIF IF (nvpk == 2 ) nvpk = 1 - IF (nvpk == 3 ) nvpk = npk + IF (nvpk == 3 ) nvpk = npkk PRINT *, 'Size of the extracted area :' PRINT *, ' npiglo = ', npiglo @@ -201,39 +226,7 @@ PROGRAM cdfsum e2(:,:) = getvar (cn_fhgr, cv_e2, 1, npiglo, npjglo, kimin=iimin, kjmin=ijmin) gdep(:) = getvare3(cn_fzgr, cv_dep, npk ) - rdumlon = 0. ; rdumlat = 0. - ipk(1) = nvpk ! vertical profile - ipk(2) = 1 ! 3D sum - ierr=getvaratt (cf_in, cv_in, clunits, zspval, cllong_name, clshort_name) - - ! define new variables for output - stypvar%rmissing_value = 99999. - stypvar%valid_min = -1000. - stypvar%valid_max = 1000. - stypvar%scale_factor = 1. - stypvar%add_offset = 0. - stypvar%savelog10 = 0. - stypvar%conline_operation = 'N/A' - - stypvar(1)%cname = 'sum_'//TRIM(cv_in) - stypvar(1)%cunits = TRIM(clunits)//'.m2' - stypvar(1)%clong_name = 'sum'//TRIM(cllong_name) - stypvar(1)%cshort_name = 'sum'//TRIM(clshort_name) - stypvar(1)%caxis = 'ZT' - - stypvar(2)%cname = 'sum_3D'//TRIM(cv_in) - stypvar(2)%cunits = TRIM(clunits)//'.m3' - stypvar(2)%clong_name = 'sum_3D'//TRIM(cllong_name) - stypvar(2)%cshort_name = 'sum_3D'//TRIM(clshort_name) - stypvar(2)%caxis = 'T' - - ncout = create (cf_out, 'none', 1, 1 , nvpk, cdep=cv_dep) - ierr = createvar (ncout, stypvar, 2 , ipk, id_varout ) - ierr = putheadervar(ncout, cf_in, 1, 1, npk, pnavlon=rdumlon, pnavlat=rdumlat, pdep=gdep(1:nvpk), cdep=cv_dep) - tim = getvar1d(cf_in, cn_vtimec, npt) - ierr = putvar1d(ncout, tim, npt, 'T') - - + CALL CreateOutput dsumt = 0.d0 DO jt = 1,npt @@ -242,7 +235,7 @@ PROGRAM cdfsum zv = 0. DO jk = 1,nvpk ik = jk + ikmin -1 - ! Get velocities v at ik + ! Get field at ik zv (:,:) = getvar(cf_in, cv_in, ik, npiglo, npjglo, ktime=jt, kimin=iimin, kjmin=ijmin) zmask(:,:) = getvar(cn_fmsk, cv_msk, ik, npiglo, npjglo, kimin=iimin, kjmin=ijmin) ! zmask(:,npjglo)=0. @@ -286,4 +279,49 @@ PROGRAM cdfsum CLOSE(numout) ierr=closeout(ncout) + CONTAINS + SUBROUTINE CreateOutput + !!--------------------------------------------------------------------- + !! *** ROUTINE CreateOutput *** + !! + !! ** Purpose : Create netcdf output file + !!---------------------------------------------------------------------- + REAL(KIND=4), DIMENSION(1,1) :: zdumlon, zdumlat ! dummy latitude and longitude + !! + ! define new variables for output + zdumlon = 0. ; zdumlat = 0. + ierr=getvaratt (cf_in, cv_in, clunits, zspval, cllong_name, clshort_name) + stypvar%rmissing_value = 99999. + stypvar%valid_min = -1000. + stypvar%valid_max = 1000. + stypvar%scale_factor = 1. + stypvar%add_offset = 0. + stypvar%savelog10 = 0. + stypvar%conline_operation = 'N/A' + + ipk(1) = nvpk ! vertical profile + stypvar(1)%cname = 'sum_'//TRIM(cv_in) + stypvar(1)%cunits = TRIM(clunits)//'.m2' + stypvar(1)%clong_name = 'sum'//TRIM(cllong_name) + stypvar(1)%cshort_name = 'sum'//TRIM(clshort_name) + stypvar(1)%caxis = 'ZT' + + ipk(2) = 1 ! 3D sum + stypvar(2)%cname = 'sum_3D'//TRIM(cv_in) + stypvar(2)%cunits = TRIM(clunits)//'.m3' + stypvar(2)%clong_name = 'sum_3D'//TRIM(cllong_name) + stypvar(2)%cshort_name = 'sum_3D'//TRIM(clshort_name) + stypvar(2)%caxis = 'T' + + ncout = create (cf_out, 'none', 1, 1 , nvpk, cdep=cv_dep) + ierr = createvar (ncout, stypvar, 2 , ipk, id_varout ) + ierr = putheadervar(ncout, cf_in, 1, 1, npk, & + & pnavlon=zdumlon, pnavlat=zdumlat, & + & pdep=gdep(ikmin:ikmax), & + & cdep=cv_dep ) + tim = getvar1d(cf_in, cn_vtimec, npt) + ierr = putvar1d(ncout, tim, npt, 'T') + + END SUBROUTINE CreateOutput + END PROGRAM cdfsum From 65e21adc8ff80a2165245a0360980aea0ee8cf0c Mon Sep 17 00:00:00 2001 From: jmm Date: Fri, 20 Jan 2017 17:43:10 +0100 Subject: [PATCH 16/33] Fix problem of deptht variable in cdfsum --- src/cdfsum.f90 | 20 +++++++++++++------- 1 file changed, 13 insertions(+), 7 deletions(-) diff --git a/src/cdfsum.f90 b/src/cdfsum.f90 index c2eef79..f4ffadc 100644 --- a/src/cdfsum.f90 +++ b/src/cdfsum.f90 @@ -53,7 +53,8 @@ PROGRAM cdfsum CHARACTER(LEN=256) :: cldum ! dummy string CHARACTER(LEN=256) :: cf_in ! file name CHARACTER(LEN=256) :: cf_out='cdfsum.nc' ! output file name - CHARACTER(LEN=256) :: cv_dep ! depth name + CHARACTER(LEN=256) :: cv_dep ! depth name in mesh_zgr + CHARACTER(LEN=256) :: cdep ! depth name in output file CHARACTER(LEN=256) :: cv_in ! variable name CHARACTER(LEN=20) :: cv_e1, cv_e2, cv_e3 ! name of the horiz/vert metrics CHARACTER(LEN=20) :: cv_msk ! name of mask variable @@ -193,30 +194,35 @@ PROGRAM cdfsum cv_e3 = 'e3t_ps' cv_msk = 'tmask' cv_dep = cn_gdept + cdep = cn_vdeptht CASE ( 'U' ) cv_e1 = cn_ve1u cv_e2 = cn_ve2u cv_e3 = 'e3t_ps' cv_msk = 'umask' cv_dep = cn_gdept + cdep = cn_vdepthu CASE ( 'V' ) cv_e1 = cn_ve1v cv_e2 = cn_ve2v cv_e3 = 'e3t_ps' cv_msk = 'vmask' cv_dep = cn_gdept + cdep = cn_vdepthv CASE ( 'F' ) cv_e1 = cn_ve1f cv_e2 = cn_ve2f cv_e3 = 'e3t_ps' cv_msk = 'fmask' cv_dep = cn_gdept + cdep = cn_vdeptht CASE ( 'W' ) cv_e1 = cn_ve1t cv_e2 = cn_ve2t cv_e3 = 'e3w_ps' cv_msk = 'tmask' cv_dep = cn_gdepw + cdep = cn_vdepthw CASE DEFAULT PRINT *, 'this type of variable is not known :', TRIM(cvartype) STOP @@ -313,12 +319,12 @@ SUBROUTINE CreateOutput stypvar(2)%cshort_name = 'sum_3D'//TRIM(clshort_name) stypvar(2)%caxis = 'T' - ncout = create (cf_out, 'none', 1, 1 , nvpk, cdep=cv_dep) - ierr = createvar (ncout, stypvar, 2 , ipk, id_varout ) - ierr = putheadervar(ncout, cf_in, 1, 1, npk, & - & pnavlon=zdumlon, pnavlat=zdumlat, & - & pdep=gdep(ikmin:ikmax), & - & cdep=cv_dep ) + ncout = create (cf_out, 'none', 1, 1 , nvpk, cdep=cdep) + ierr = createvar (ncout, stypvar, 2 , ipk, id_varout ) + ierr = putheadervar(ncout, cf_in, 1, 1, npkk, & + & pnavlon=zdumlon, pnavlat=zdumlat, & + & pdep=gdep(ikmin:ikmax), & + & cdep=cdep ) tim = getvar1d(cf_in, cn_vtimec, npt) ierr = putvar1d(ncout, tim, npt, 'T') From 3120aeffcf51f05b6e0b3db18945dee14fca7f29 Mon Sep 17 00:00:00 2001 From: jmm Date: Sat, 21 Jan 2017 14:17:42 +0100 Subject: [PATCH 17/33] Add -o option in cdfmhst.f90 for choosing the name of the output file --- src/cdfmhst.f90 | 252 ++++++++++++++++++++++++------------------------ 1 file changed, 127 insertions(+), 125 deletions(-) diff --git a/src/cdfmhst.f90 b/src/cdfmhst.f90 index a0bd6ae..0fba492 100644 --- a/src/cdfmhst.f90 +++ b/src/cdfmhst.f90 @@ -106,7 +106,7 @@ PROGRAM cdfmhst narg= iargc() IF ( narg == 0 ) THEN PRINT *,' usage : cdfmhst VT-file | (V-file T-file [S-file]) [MST] [-full] ...' - PRINT *,' ... [-Zdim] ' + PRINT *,' ... [-Zdim] [-o OUT-file]' PRINT *,' ' PRINT *,' PURPOSE :' PRINT *,' Compute the meridional heat/salt transport as a function of ' @@ -125,6 +125,7 @@ PROGRAM cdfmhst PRINT *,' If not specified, only the MHT is output.' PRINT *,' [-full ] : to be set for full step case.' PRINT *,' [-Zdim ] : to be set to output vertical structure of Heat/salt transport' + PRINT *,' [-o OUT-file ] : change name of the output file. Default:', TRIM(cf_outnc) PRINT *,' ' PRINT *,' REQUIRED FILES :' PRINT *,' ', TRIM(cn_fhgr),', ',TRIM(cn_fzgr),' and ',TRIM(cn_fmsk) @@ -134,16 +135,16 @@ PROGRAM cdfmhst PRINT *,' OUTPUT : ' PRINT *,' ASCII files : ', TRIM(cf_outh),' : Meridional Heat Transport' PRINT *,' ', TRIM(cf_outs),' : Meridional Salt Transport' - PRINT *,' netcdf file : ', TRIM(cf_outnc) + PRINT *,' netcdf file : ', TRIM(cf_outnc),' unless -o option is used.' PRINT *,' variables : ( [... ] : MST option ) ' PRINT *,' ', TRIM(cv_zomht),cbasin(1),' : Meridional Heat Transport (global)' PRINT *,' [ ', TRIM(cv_zomst),cbasin(1),' : Meridional Salt Transport (global) ] ' PRINT *,' If ',TRIM(cn_fbasins),' is available, per basin meridional transport ' PRINT *,' are also available:' - DO jbasins=2, 6 - PRINT *,' ', TRIM(cv_zomht),cbasin(jbasins),' : Meridional Heat Transport' - PRINT *,' [ ', TRIM(cv_zomst),cbasin(jbasins),' : Meridional Salt Transport ]' - END DO + DO jbasins=2, 6 + PRINT *,' ', TRIM(cv_zomht),cbasin(jbasins),' : Meridional Heat Transport' + PRINT *,' [ ', TRIM(cv_zomst),cbasin(jbasins),' : Meridional Salt Transport ]' + END DO STOP ENDIF @@ -158,13 +159,14 @@ PROGRAM cdfmhst CASE ( 'MST' ) ; npvar = 2 CASE ( '-full' ) ; lfull = .TRUE. CASE ( '-Zdim' ) ; lzdim = .TRUE. + CASE ( '-o' ) ; CALL getarg(ijarg, cf_outnc) ; ijarg = ijarg+1 CASE DEFAULT ; ifile = ifile + 1 - SELECT CASE (ifile) - CASE ( 1) ; cf_vtfil = cldum - CASE ( 2) ; cf_tfil = cldum - CASE ( 3) ; cf_sfil = cldum - CASE DEFAULT ; PRINT *,' WARNING: more than 3 files in input : weird ' - END SELECT + SELECT CASE (ifile) + CASE ( 1) ; cf_vtfil = cldum + CASE ( 2) ; cf_tfil = cldum + CASE ( 3) ; cf_sfil = cldum + CASE DEFAULT ; PRINT *,' WARNING: more than 3 files in input : weird ' + END SELECT END SELECT END DO @@ -258,7 +260,7 @@ PROGRAM cdfmhst ! Allocate output variables ALLOCATE(stypvar(nbasinso*npvar), cvarname(nbasinso*npvar) ) ALLOCATE( ipk(nbasinso*npvar), id_varout(nbasinso*npvar) ) - + ipk(:)=npko ! all output variables either 1 or npko levels DO jbasins = 1,nbasinso cvarname(jbasins) = TRIM(cv_zomht)//TRIM(cbasin(jbasins)) @@ -307,11 +309,11 @@ PROGRAM cdfmhst PRINT *,'level ',jk ! Get temperature and salinity at jk IF ( lsepf ) THEN - zv(:,:)= getvar(cf_vfil, cn_vomecrty, jk, npiglo, npjglo, ktime=jt) - zt(:,:)= getvar(cf_tfil, cn_votemper, jk, npiglo, npjglo, ktime=jt) - zs(:,:)= getvar(cf_sfil, cn_vosaline, jk, npiglo, npjglo, ktime=jt) - zvt(:,:)=0. - zvs(:,:)=0. + zv(:,:)= getvar(cf_vfil, cn_vomecrty, jk, npiglo, npjglo, ktime=jt) + zt(:,:)= getvar(cf_tfil, cn_votemper, jk, npiglo, npjglo, ktime=jt) + zs(:,:)= getvar(cf_sfil, cn_vosaline, jk, npiglo, npjglo, ktime=jt) + zvt(:,:)=0. + zvs(:,:)=0. DO ji=1, npiglo DO jj = 1, npjglo -1 zvt(ji,jj) = 0.5 * ( zt(ji,jj) + zt(ji,jj+1) )*zv(ji,jj) ! temper at Vpoint @@ -320,8 +322,8 @@ PROGRAM cdfmhst END DO ELSE - zvt(:,:)= getvar(cf_vtfil, cn_vomevt, jk, npiglo, npjglo, ktime=jt) - zvs(:,:)= getvar(cf_vtfil, cn_vomevs, jk, npiglo, npjglo, ktime=jt) + zvt(:,:)= getvar(cf_vtfil, cn_vomevt, jk, npiglo, npjglo, ktime=jt) + zvs(:,:)= getvar(cf_vtfil, cn_vomevs, jk, npiglo, npjglo, ktime=jt) ENDIF ! get e3v at level jk IF ( lfull ) THEN @@ -337,124 +339,124 @@ PROGRAM cdfmhst dtrps(:,:) = dtrps(:,:) + dwks(:,:) - !global - zmask(:,:) = getvar(cn_fmsk, 'vmask', 1, npiglo, npjglo) - DO jj=1,npjglo - dzonal_heat_glo(jj) = SUM( dtrph(2:npiglo-1,jj)*zmask(2:npiglo-1,jj) ) - dzonal_salt_glo(jj) = SUM( dtrps(2:npiglo-1,jj)*zmask(2:npiglo-1,jj) ) - END DO - - IF ( llglo ) THEN - ! Zonal mean with mask - ! Atlantic - zmask(:,:) = getvar(cn_fbasins, 'tmaskatl', 1, npiglo, npjglo) + !global + zmask(:,:) = getvar(cn_fmsk, 'vmask', 1, npiglo, npjglo) DO jj=1,npjglo - dzonal_heat_atl(jj) = SUM( dtrph(:,jj)*zmask(:,jj) ) - dzonal_salt_atl(jj) = SUM( dtrps(:,jj)*zmask(:,jj) ) + dzonal_heat_glo(jj) = SUM( dtrph(2:npiglo-1,jj)*zmask(2:npiglo-1,jj) ) + dzonal_salt_glo(jj) = SUM( dtrps(2:npiglo-1,jj)*zmask(2:npiglo-1,jj) ) END DO - ! Pacific - zmask(:,:) = getvar(cn_fbasins, 'tmaskpac', 1, npiglo, npjglo) - DO jj=1,npjglo - dzonal_heat_pac(jj) = SUM( dtrph(:,jj)*zmask(:,jj) ) - dzonal_salt_pac(jj) = SUM( dtrps(:,jj)*zmask(:,jj) ) - END DO + IF ( llglo ) THEN + ! Zonal mean with mask + ! Atlantic + zmask(:,:) = getvar(cn_fbasins, 'tmaskatl', 1, npiglo, npjglo) + DO jj=1,npjglo + dzonal_heat_atl(jj) = SUM( dtrph(:,jj)*zmask(:,jj) ) + dzonal_salt_atl(jj) = SUM( dtrps(:,jj)*zmask(:,jj) ) + END DO - ! Indian - zmask(:,:) = getvar(cn_fbasins, 'tmaskind', 1, npiglo, npjglo) - DO jj=1,npjglo - dzonal_heat_ind(jj) = SUM( dtrph(:,jj)*zmask(:,jj) ) - dzonal_salt_ind(jj) = SUM( dtrps(:,jj)*zmask(:,jj) ) - END DO + ! Pacific + zmask(:,:) = getvar(cn_fbasins, 'tmaskpac', 1, npiglo, npjglo) + DO jj=1,npjglo + dzonal_heat_pac(jj) = SUM( dtrph(:,jj)*zmask(:,jj) ) + dzonal_salt_pac(jj) = SUM( dtrps(:,jj)*zmask(:,jj) ) + END DO - ! Austral - dzonal_heat_aus = 0.d0 - dzonal_salt_aus = 0.d0 - ! zmask(:,:)=getvar(cn_fbasins,'tmaskant',1,npiglo,npjglo) - ! DO jj=1,npjglo - ! dzonal_heat_aus(jj)= SUM( dtrph(:,jj)*zmask(:,jj)) - ! dzonal_salt_aus(jj)= SUM( dtrps(:,jj)*zmask(:,jj)) - ! END DO - - ! ! Med - dzonal_heat_med = 0.d0 - dzonal_salt_med = 0.d0 - - ! zmask(:,:)=getvar(cn_fbasins,'tmaskmed',1,npiglo,npjglo) - ! DO jj=1,npjglo - ! dzonal_heat_med(jj)= SUM( dtrph(:,jj)*zmask(:,jj)) - ! dzonal_salt_med(jj)= SUM( dtrps(:,jj)*zmask(:,jj)) - ! END DO - ENDIF - - IF ( lzdim .OR. ( jk == npk ) ) THEN !output this level - IF ( lzdim ) THEN ; ik0 = jk ; ELSE ; ik0 = 1 ; ENDIF - - DO jvar=1,npvar ! MHT [ and MST ] (1 or 2 ) - IF ( jvar == 1 ) THEN - ! MHT - ivar=1 - dmtrp(:) = dzonal_heat_glo(:)/1.d15 ! GLO - WHERE ( dmtrp == 0 ) dmtrp = ppspval - ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) - ivar=ivar+1 - IF ( nbasins == 5 ) THEN - dmtrp(:) = dzonal_heat_atl(:)/1.d15 ! ATL - WHERE ( dmtrp == 0 ) dmtrp = ppspval - ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) - ivar=ivar+1 - dmtrp(:) = (dzonal_heat_ind(:) + dzonal_heat_pac(:))/1.d15 ! INP - WHERE ( dmtrp == 0 ) dmtrp = ppspval - ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) - ivar=ivar+1 - dmtrp(:) = dzonal_heat_ind(:)/1.d15 ! IND - WHERE ( dmtrp == 0 ) dmtrp = ppspval - ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) - ivar=ivar+1 - dmtrp(:) = dzonal_heat_pac(:)/1.d15 ! PAC - WHERE ( dmtrp == 0 ) dmtrp = ppspval - ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) - ivar=ivar+1 - ! now inp0 - dmtrp(:) = ( dzonal_heat_glo(:) - dzonal_heat_atl(:) )/1.d15 ! INP0 - WHERE ( dmtrp == 0 ) dmtrp = ppspval - ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) - ivar=ivar+1 - ENDIF - ELSE - ! MST - dmtrp(:) = dzonal_salt_glo(:)/1.d6 ! GLO - WHERE ( dmtrp == 0 ) dmtrp = ppspval - ierr=putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) - ivar=ivar+1 - IF ( nbasins == 5 ) THEN - dmtrp(:) = dzonal_salt_atl(:)/1.d6 ! ATL - WHERE ( dmtrp == 0 ) dmtrp = ppspval - ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) - ivar=ivar+1 - dmtrp(:) = (dzonal_salt_ind(:) + dzonal_salt_pac(:))/1.d6 ! INP - WHERE ( dmtrp == 0 ) dmtrp = ppspval - ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) - ivar=ivar+1 - dmtrp(:) = dzonal_salt_ind(:)/1.d6 ! IND + ! Indian + zmask(:,:) = getvar(cn_fbasins, 'tmaskind', 1, npiglo, npjglo) + DO jj=1,npjglo + dzonal_heat_ind(jj) = SUM( dtrph(:,jj)*zmask(:,jj) ) + dzonal_salt_ind(jj) = SUM( dtrps(:,jj)*zmask(:,jj) ) + END DO + + ! Austral + dzonal_heat_aus = 0.d0 + dzonal_salt_aus = 0.d0 + ! zmask(:,:)=getvar(cn_fbasins,'tmaskant',1,npiglo,npjglo) + ! DO jj=1,npjglo + ! dzonal_heat_aus(jj)= SUM( dtrph(:,jj)*zmask(:,jj)) + ! dzonal_salt_aus(jj)= SUM( dtrps(:,jj)*zmask(:,jj)) + ! END DO + + ! ! Med + dzonal_heat_med = 0.d0 + dzonal_salt_med = 0.d0 + + ! zmask(:,:)=getvar(cn_fbasins,'tmaskmed',1,npiglo,npjglo) + ! DO jj=1,npjglo + ! dzonal_heat_med(jj)= SUM( dtrph(:,jj)*zmask(:,jj)) + ! dzonal_salt_med(jj)= SUM( dtrps(:,jj)*zmask(:,jj)) + ! END DO + ENDIF + + IF ( lzdim .OR. ( jk == npk ) ) THEN !output this level + IF ( lzdim ) THEN ; ik0 = jk ; ELSE ; ik0 = 1 ; ENDIF + + DO jvar=1,npvar ! MHT [ and MST ] (1 or 2 ) + IF ( jvar == 1 ) THEN + ! MHT + ivar=1 + dmtrp(:) = dzonal_heat_glo(:)/1.d15 ! GLO WHERE ( dmtrp == 0 ) dmtrp = ppspval ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) ivar=ivar+1 - dmtrp(:) = dzonal_salt_pac(:)/1.d6 ! PAC + IF ( nbasins == 5 ) THEN + dmtrp(:) = dzonal_heat_atl(:)/1.d15 ! ATL + WHERE ( dmtrp == 0 ) dmtrp = ppspval + ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) + ivar=ivar+1 + dmtrp(:) = (dzonal_heat_ind(:) + dzonal_heat_pac(:))/1.d15 ! INP + WHERE ( dmtrp == 0 ) dmtrp = ppspval + ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) + ivar=ivar+1 + dmtrp(:) = dzonal_heat_ind(:)/1.d15 ! IND + WHERE ( dmtrp == 0 ) dmtrp = ppspval + ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) + ivar=ivar+1 + dmtrp(:) = dzonal_heat_pac(:)/1.d15 ! PAC + WHERE ( dmtrp == 0 ) dmtrp = ppspval + ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) + ivar=ivar+1 + ! now inp0 + dmtrp(:) = ( dzonal_heat_glo(:) - dzonal_heat_atl(:) )/1.d15 ! INP0 + WHERE ( dmtrp == 0 ) dmtrp = ppspval + ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) + ivar=ivar+1 + ENDIF + ELSE + ! MST + dmtrp(:) = dzonal_salt_glo(:)/1.d6 ! GLO WHERE ( dmtrp == 0 ) dmtrp = ppspval ierr=putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) ivar=ivar+1 - ! now inp0 - dmtrp(:) = ( dzonal_salt_glo(:) - dzonal_salt_atl(:) )/1.d6 ! INP0 - WHERE ( dmtrp == 0 ) dmtrp = ppspval - ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) - ivar=ivar+1 + IF ( nbasins == 5 ) THEN + dmtrp(:) = dzonal_salt_atl(:)/1.d6 ! ATL + WHERE ( dmtrp == 0 ) dmtrp = ppspval + ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) + ivar=ivar+1 + dmtrp(:) = (dzonal_salt_ind(:) + dzonal_salt_pac(:))/1.d6 ! INP + WHERE ( dmtrp == 0 ) dmtrp = ppspval + ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) + ivar=ivar+1 + dmtrp(:) = dzonal_salt_ind(:)/1.d6 ! IND + WHERE ( dmtrp == 0 ) dmtrp = ppspval + ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) + ivar=ivar+1 + dmtrp(:) = dzonal_salt_pac(:)/1.d6 ! PAC + WHERE ( dmtrp == 0 ) dmtrp = ppspval + ierr=putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) + ivar=ivar+1 + ! now inp0 + dmtrp(:) = ( dzonal_salt_glo(:) - dzonal_salt_atl(:) )/1.d6 ! INP0 + WHERE ( dmtrp == 0 ) dmtrp = ppspval + ierr = putvar(ncout, id_varout(ivar), REAL(dmtrp), ik0, 1, npjglo, ktime=jt) + ivar=ivar+1 + ENDIF ENDIF - ENDIF - END DO + END DO - ENDIF ! end loop on check for ouptut - END DO ! loop to next level + ENDIF ! end loop on check for ouptut + END DO ! loop to next level WRITE(numouth,*)'! Zonal heat transport (integrated alon I-model coordinate) (in Pw)' From a41e641561a8fe5736e0f273bc58b6abba9f2301 Mon Sep 17 00:00:00 2001 From: jmm Date: Sat, 21 Jan 2017 14:18:37 +0100 Subject: [PATCH 18/33] Modify cdftransport so that it can use T file to compute UT, VT, US and TS * When working with almost instantaneous output files, we do not need the VT file computed with cdfVT as a temporal mean. * having this -TS option allows to pass T file instead of VT file --- src/cdftransport.f90 | 38 +++++++++++++++++++++++++++++--------- 1 file changed, 29 insertions(+), 9 deletions(-) diff --git a/src/cdftransport.f90 b/src/cdftransport.f90 index f06c1d5..b4caa7d 100644 --- a/src/cdftransport.f90 +++ b/src/cdftransport.f90 @@ -109,6 +109,7 @@ PROGRAM cdftransport REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: gphif ! latitudes of F points REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: zu, zut, zus ! Zonal velocities and uT uS REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: zv, zvt, zvs ! Meridional velocities and uT uS + REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: zt, zs ! temperature and salinity REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: rdum ! dummy (1x1) array for ncdf output REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: zuobc, zvobc ! arrays for OBC files (vertical slice) REAL(KIND=4), DIMENSION(:), ALLOCATABLE :: tim ! time counter @@ -193,13 +194,14 @@ PROGRAM cdftransport LOGICAL :: lobc = .FALSE. ! flag for obc input files LOGICAL :: l_merid = .FALSE. ! flag for meridional obc LOGICAL :: l_zonal = .FALSE. ! flag for zonal obc + LOGICAL :: l_tsfil = .FALSE. ! flag for using T file instead of VT file !!---------------------------------------------------------------------- CALL ReadCdfNames() narg= iargc() ! Print usage if no argument IF ( narg == 0 ) THEN - PRINT *,' usage : cdftransport [-test u v ] [-noheat ] [-plus_minus ] [-obc]...' + PRINT *,' usage : cdftransport [-test u v ] [-noheat ] [-plus_minus ] [-obc] [-TS] ' PRINT *,' ... [VT-file] U-file V-file [-full] |-time jt] ...' PRINT *,' ... [-time jt ] [-zlimit limits of level]' PRINT *,' ' @@ -227,9 +229,11 @@ PROGRAM cdftransport PRINT *,' the volume transport. This option implicitly set -noheat,' PRINT *,' and must be used before the file names.' PRINT *,' [-obc ] : indicates that input files are obc files (vertical slices)' - PRINT *,' Take care that for this case, mesh files must be adapted.' - PRINT *,' This option implicitly set -noheat, and must be used before' - PRINT *,' the file names.' + PRINT *,' Take care that for this case, mesh files must be adapted.' + PRINT *,' This option implicitly set -noheat, and must be used before' + PRINT *,' the file names.' + PRINT *,' [ -TS ] : Indicate that UT VT US VS will be recomputed from T U V ' + PRINT *,' files. T-file is passed as the first file instead of VT ' PRINT *,' [-full ] : use for full step configurations.' PRINT *,' [-time jt ]: compute transports for time index jt. Default is 1.' PRINT *,' [-zlimit list of depth] : Specify depths limits defining layers where the' @@ -282,8 +286,11 @@ PROGRAM cdftransport lheat = .FALSE. CASE ('-obc' ) - lobc = .TRUE. + lobc = .TRUE. lheat = .FALSE. + + CASE ( '-TS' ) + l_tsfil = .TRUE. CASE ('-zlimit' ) ! this should be the last option on the line nxtarg = ijarg - 1 @@ -393,6 +400,9 @@ PROGRAM cdftransport ALLOCATE ( dtrpus(npiglo,npjglo,nclass), dtrpvs(npiglo,npjglo,nclass)) ALLOCATE ( dheatrpsum(nclass), dsaltrpsum(nclass) ) ALLOCATE ( dheatallegcl(nclass), dsaltallegcl(nclass) ) + IF ( l_tsfil ) THEN + ALLOCATE (zt(npiglo+1,npjglo+1), zs(npiglo+1, npjglo+1) ) + ENDIF ENDIF ! ALLOCATE ( e1v(npiglo,npjglo),e3v(npiglo,npjglo) ) @@ -479,10 +489,20 @@ PROGRAM cdftransport zu (:,:) = getvar(cf_ufil, cn_vozocrtx, jk, npiglo, npjglo, ktime=itime) zv (:,:) = getvar(cf_vfil, cn_vomecrty, jk, npiglo, npjglo, ktime=itime) IF (lheat) THEN - zut(:,:) = getvar(cf_tfil, cn_vozout, jk, npiglo, npjglo, ktime=itime) - zvt(:,:) = getvar(cf_tfil, cn_vomevt, jk, npiglo, npjglo, ktime=itime) - zus(:,:) = getvar(cf_tfil, cn_vozous, jk, npiglo, npjglo, ktime=itime) - zvs(:,:) = getvar(cf_tfil, cn_vomevs, jk, npiglo, npjglo, ktime=itime) + IF ( l_tsfil ) THEN + zt(:,:) = 0. ; zs(:,:) = 0. + zt(1:npiglo,1:npjglo) = getvar(cf_tfil, cn_votemper, jk, npiglo, npjglo, ktime=itime) + zs(1:npiglo,1:npjglo) = getvar(cf_tfil, cn_votemper, jk, npiglo, npjglo, ktime=itime) + zut(1:npiglo,1:npjglo) = zu(1:npiglo,1:npjglo) * ( zt(1:npiglo,1:npjglo) + zt(2:npiglo+1,1:npjglo)) + zus(1:npiglo,1:npjglo) = zu(1:npiglo,1:npjglo) * ( zs(1:npiglo,1:npjglo) + zs(2:npiglo+1,1:npjglo)) + zvt(1:npiglo,1:npjglo) = zv(1:npiglo,1:npjglo) * ( zt(1:npiglo,1:npjglo) + zt(1:npiglo, 1:npjglo+1)) + zvs(1:npiglo,1:npjglo) = zv(1:npiglo,1:npjglo) * ( zs(1:npiglo,1:npjglo) + zs(1:npiglo, 1:npjglo+1)) + ELSE + zut(:,:) = getvar(cf_tfil, cn_vozout, jk, npiglo, npjglo, ktime=itime) + zvt(:,:) = getvar(cf_tfil, cn_vomevt, jk, npiglo, npjglo, ktime=itime) + zus(:,:) = getvar(cf_tfil, cn_vozous, jk, npiglo, npjglo, ktime=itime) + zvs(:,:) = getvar(cf_tfil, cn_vomevs, jk, npiglo, npjglo, ktime=itime) + ENDIF ENDIF ENDIF From 4f491885d3b9401fdb87f400d07c13a7e2f8833d Mon Sep 17 00:00:00 2001 From: jmm Date: Sun, 22 Jan 2017 22:47:37 +0100 Subject: [PATCH 19/33] add -M option in cdfheatc.f90 * This option allow the use of a non standarf mask file and mask variable ( for instance polymask ) in order to limit the area where the heat content is computed. It is a generalisation of -zoom option for arbitrary masking shape * chage the precision of the output file to r8 instead of r4 --- src/cdfheatc.f90 | 32 ++++++++++++++++++++++---------- 1 file changed, 22 insertions(+), 10 deletions(-) diff --git a/src/cdfheatc.f90 b/src/cdfheatc.f90 index fdd627f..4ebe806 100644 --- a/src/cdfheatc.f90 +++ b/src/cdfheatc.f90 @@ -37,7 +37,6 @@ PROGRAM cdfheatc REAL(KIND=4), PARAMETER :: pprho0=1020. ! water density (kg/m3) REAL(KIND=4), PARAMETER :: ppcp=4000. ! calorific capacity (J/kg/m3) - REAL(KIND=4), DIMENSION(1,1) :: zdum ! working pseudo array for nc output REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: e1t, e2t ! horizontal metrics REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: e3t ! vertical metric REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: temp ! temperature @@ -52,12 +51,14 @@ PROGRAM cdfheatc REAL(KIND=8) :: dvol2d ! volume of a layer REAL(KIND=8) :: dsum2d ! weigthed sum per layer REAL(KIND=8) :: dsurf ! surface of a layer + REAL(KIND=8), DIMENSION(1,1) :: dl_dum ! working pseudo array for nc output TYPE(variable), DIMENSION(:), ALLOCATABLE :: stypvar ! structure for attributes CHARACTER(LEN=256) :: cf_tfil ! input gridT file CHARACTER(LEN=256) :: cf_out='heatc.nc' ! netcdf output file CHARACTER(LEN=256) :: cldum ! dummy character variable + CHARACTER(LEN=256) :: cv_msk='tmask' ! variable for masking LOGICAL :: lfull=.FALSE. ! flag for full step computation LOGICAL :: lchk ! flag for missing files @@ -70,6 +71,7 @@ PROGRAM cdfheatc IF ( narg == 0 ) THEN PRINT *,' usage : cdfheatc -f T-file [-mxloption option] ...' PRINT *,' [-zoom imin imax jmin jmax kmin kmax] [-full] [-o OUT-file]' + PRINT *,' [-M MSK-file VAR-mask ]' PRINT *,' ' PRINT *,' PURPOSE :' PRINT *,' Computes the heat content in the specified 3D area (Joules)' @@ -89,6 +91,10 @@ PROGRAM cdfheatc PRINT *,' option=-1 : exclude mixed layer in the computation' PRINT *,' option= 0 : [Default], do not take care of mxl.' PRINT *,' [-o OUT-file ] : specify netcdf output filename instead of ',TRIM(cf_out) + PRINT *,' [-M MSK-file VAR-mask] : Allow the use of a non standard mask file ' + PRINT *,' with VAR-mask, instead of ',TRIM(cn_fmsk),' and ',TRIM(cv_msk) + PRINT *,' This option is a usefull alternative to -zoom option, when the ' + PRINT *,' area of interest is not ''box-like'' ' PRINT *,' ' PRINT *,' REQUIRED FILES :' PRINT *,' Files ',TRIM(cn_fhgr),', ',TRIM(cn_fzgr),' and ',TRIM(cn_fmsk) @@ -99,6 +105,9 @@ PROGRAM cdfheatc PRINT *,' : heatc(dep) (Joules) ' PRINT *,' : heatc3dpervol (Joules/m3) ' PRINT *,' Standard output' + PRINT *,' ' + PRINT *,' SEE ALSO: ' + PRINT *,' cdfpolymask ' STOP ENDIF @@ -117,6 +126,9 @@ PROGRAM cdfheatc CALL getarg ( ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) ijmax CALL getarg ( ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) ikmin CALL getarg ( ijarg, cldum) ; ijarg = ijarg + 1 ; READ(cldum,*) ikmax + CASE ( '-M' ) + CALL getarg ( ijarg, cn_fmsk) ; ijarg = ijarg + 1 + CALL getarg ( ijarg, cv_msk ) ; ijarg = ijarg + 1 CASE DEFAULT PRINT *,' A single argument is considered as a T-file' CALL getarg ( ijarg, cf_tfil) ; ijarg = ijarg + 1 @@ -184,9 +196,9 @@ PROGRAM cdfheatc DO jk = 1,nvpk ik = jk + ikmin -1 - ! Get velocities v at ik + ! Get temperatures temp at ik temp( :,:) = getvar(cf_tfil, cn_votemper, ik, npiglo, npjglo, kimin=iimin, kjmin=ijmin, ktime=jt) - tmask(:,:) = getvar(cn_fmsk, 'tmask', ik, npiglo, npjglo, kimin=iimin, kjmin=ijmin ) + tmask(:,:) = getvar(cn_fmsk, cv_msk, ik, npiglo, npjglo, kimin=iimin, kjmin=ijmin ) ! get e3t at level ik ( ps...) IF ( lfull ) THEN @@ -214,17 +226,17 @@ PROGRAM cdfheatc ELSE PRINT *, ' No points in the water at level ',ik,'(',gdepw(ik),' m) ' ENDIF - zdum(1,1) = pprho0*ppcp*dsum2d - ierr = putvar(ncout, id_varout(jp_hc2d), zdum(:,:),jk, 1, 1, ktime=jt ) + dl_dum(1,1) = pprho0*ppcp*dsum2d + ierr = putvar(ncout, id_varout(jp_hc2d), dl_dum(:,:),jk, 1, 1, ktime=jt ) END DO PRINT * ,' Total Heat content : ', pprho0*ppcp*dsum ,' Joules' PRINT * ,' Total Heat content/volume : ', pprho0*ppcp*dsum/dvol ,' Joules/m3 ' - zdum(1,1)=pprho0*ppcp*dsum - ierr = putvar(ncout, id_varout(jp_hc3d), zdum(:,:),1, 1, 1, ktime=jt ) - zdum(1,1)=zdum(1,1)/dvol - ierr = putvar(ncout, id_varout(jp_hcvol), zdum(:,:),1, 1, 1, ktime=jt ) + dl_dum(1,1)=pprho0*ppcp*dsum + ierr = putvar(ncout, id_varout(jp_hc3d), dl_dum(:,:),1, 1, 1, ktime=jt ) + dl_dum(1,1)=dl_dum(1,1)/dvol + ierr = putvar(ncout, id_varout(jp_hcvol), dl_dum(:,:),1, 1, 1, ktime=jt ) END DO ierr = closeout(ncout ) CONTAINS @@ -239,7 +251,6 @@ SUBROUTINE CreateOutput ! indeed 4 scalar but that will be considered as (x,y,t) ie (1,1,t) INTEGER(KIND=4) :: ivar=3, ierr REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: zdumlon, zdumlat -! INTEGER(KIND=4), PARAMETER :: jp_hc3d=1; jp_hc2d=2 ; jp_hcvol=3 !!---------------------------------------------------------------------- ALLOCATE(stypvar(ivar) ) ALLOCATE( ipk(ivar), id_varout(ivar) ) @@ -254,6 +265,7 @@ SUBROUTINE CreateOutput stypvar%savelog10 = 0. stypvar%conline_operation = 'N/A' stypvar%caxis = 'T' + stypvar%cprecision = 'r8' stypvar(jp_hc3d)%cname = 'heatc3d' stypvar(jp_hc3d)%cunits = 'Joules' From db0e53eb9452b8350924d7d5e2e0107964c70f94 Mon Sep 17 00:00:00 2001 From: jmm Date: Sun, 22 Jan 2017 22:51:20 +0100 Subject: [PATCH 20/33] add -o and -oz option in cdfmean * These options allow the specification of the ncdf output file and the zeromean output file respectively. --- src/cdfmean.f90 | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/src/cdfmean.f90 b/src/cdfmean.f90 index d062edb..82162ab 100644 --- a/src/cdfmean.f90 +++ b/src/cdfmean.f90 @@ -93,7 +93,7 @@ PROGRAM cdfmean narg = iargc() IF ( narg == 0 ) THEN PRINT *,' usage : cdfmean IN-file IN-var T|U|V|F|W [imin imax jmin jmax kmin kmax]' - PRINT *,' ... [-full] [-var] [-zeromean] ' + PRINT *,' ... [-full] [-var] [-zeromean] [-o OUT-file] [-oz ZEROMEAN-file]' PRINT *,' ' PRINT *,' PURPOSE :' PRINT *,' Computes the mean value of the field (3D, weighted). For 3D fields,' @@ -115,6 +115,9 @@ PROGRAM cdfmean PRINT *,' partial steps.' PRINT *,' [ -var ] : also compute the spatial variance of cdfvar ' PRINT *,' [ -zeromean ] : create a file with cdfvar having a zero spatial mean.' + PRINT *,' [ -o OUT-file] : specify the name of the output file instead of ',TRIM(cf_ncout) + PRINT *,' [ -zo ZEROMEAN-file] : specify the name of the output file for option ' + PRINT *,' -zeromean, instead of ', TRIM(cf_zerom) PRINT *,' ' PRINT *,' REQUIRED FILES :' PRINT *,' Files ', TRIM(cn_fhgr),', ', TRIM(cn_fzgr),', ', TRIM(cn_fmsk) @@ -133,7 +136,7 @@ PROGRAM cdfmean ! Open standard output with recl=256 to avoid wrapping of long lines (ifort) OPEN(6,FORM='FORMATTED',RECL=256) ! ifort - ! OPEN(6,FORM='FORMATTED') ! gfortran + ! OPEN(6,FORM='FORMATTED') ! gfortran cglobal = 'Partial step computation' ijarg = 1 ; ii = 0 @@ -147,6 +150,10 @@ PROGRAM cdfmean lvar = .true. CASE ('-zeromean' ) lzeromean = .true. + CASE ('-o' ) + CALL getarg(ijarg, cf_ncout ) ; ijarg = ijarg + 1 + CASE ('-oz' ) + CALL getarg(ijarg, cf_zerom ) ; ijarg = ijarg + 1 CASE DEFAULT ii=ii+1 SELECT CASE (ii) @@ -454,4 +461,5 @@ PROGRAM cdfmean ENDIF + END PROGRAM cdfmean From 92ea1030b15a8cc9392b825b29eac172f464e513 Mon Sep 17 00:00:00 2001 From: jmm Date: Sun, 22 Jan 2017 22:54:12 +0100 Subject: [PATCH 21/33] temporary fix in cdfmktmask for _FillValue attribute change * netcdf4 prohibitis the change of the attribute _FillValue ( it gives a segmentation fault error ) * the faulty line is commented out for the moment. No problem if _FillValue is 0. * Clever fix to implement for non zero _FillValue : put masked area to the already defined _FillValue... * This latter fix may have implication of many tools. --- src/cdfmltmask.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/cdfmltmask.f90 b/src/cdfmltmask.f90 index 49d7016..d93bd49 100644 --- a/src/cdfmltmask.f90 +++ b/src/cdfmltmask.f90 @@ -236,7 +236,7 @@ PROGRAM cdfmltmask DO jvar = 1, nvar ierr = getvaratt (cf_in, cv_in(jvar), cunits, zspval, clname, csname) IF ( csname == "" ) csname=TRIM( cv_in(jvar) ) - ierr = cvaratt (cf_out, cv_in(jvar), cunits, zspv0, clname, csname) +! ierr = cvaratt (cf_out, cv_in(jvar), cunits, zspv0, clname, csname) END DO CONTAINS From 4d1cb61265ffe9ce9f3b967b95f0b89eef31cc4b Mon Sep 17 00:00:00 2001 From: jmm Date: Sun, 22 Jan 2017 22:59:41 +0100 Subject: [PATCH 22/33] add -M option in cdfsum for masking with arbitrary shape * -M option allows the use of a non standard mask file and variable * this implementation is similar to the one introduced in cdfheatc.f90 --- src/cdfsum.f90 | 18 +++++++++++++++++- 1 file changed, 17 insertions(+), 1 deletion(-) diff --git a/src/cdfsum.f90 b/src/cdfsum.f90 index f4ffadc..d490457 100644 --- a/src/cdfsum.f90 +++ b/src/cdfsum.f90 @@ -58,6 +58,7 @@ PROGRAM cdfsum CHARACTER(LEN=256) :: cv_in ! variable name CHARACTER(LEN=20) :: cv_e1, cv_e2, cv_e3 ! name of the horiz/vert metrics CHARACTER(LEN=20) :: cv_msk ! name of mask variable + CHARACTER(LEN=20) :: cl_vmsk ! name of external mask variable (-M option) CHARACTER(LEN=20) :: cvartype ! variable type CHARACTER(LEN=256) :: clunits ! attribute of output file : units CHARACTER(LEN=256) :: cllong_name ! " long name @@ -69,6 +70,7 @@ PROGRAM cdfsum LOGICAL :: lforcing ! forcing flag LOGICAL :: lchk ! flag for missing files LOGICAL :: lerror=.FALSE. ! flag for missing arguments + LOGICAL :: lfmsk=.FALSE. ! flag for using non standard mask file !!---------------------------------------------------------------------- CALL ReadCdfNames() @@ -76,6 +78,7 @@ PROGRAM cdfsum IF ( narg == 0 ) THEN PRINT *,' usage : cdfsum -f IN-file -v IN-var -p T| U | V | F | W ... ' PRINT *,' ... [-zoom imin imax jmin jmax kmin kmax] [-full ] [-o OUT-file] ' + PRINT *,' ... [-M MSK-file VAR-mask ]' PRINT *,' ' PRINT *,' PURPOSE :' PRINT *,' Computes the sum value of the field (3D, weighted)' @@ -93,9 +96,16 @@ PROGRAM cdfsum PRINT *,' if kmin=0 all k are taken' PRINT *,' [ -full : ] Use full steps instead of default partial steps' PRINT *,' [-o OUT-file ] : name of the output file instead of', TRIM(cf_out) + PRINT *,' [-M MSK-file VAR-mask] : Allow the use of a non standard mask file ' + PRINT *,' with VAR-mask, instead of ',TRIM(cn_fmsk),' and the variable' + PRINT *,' associated with the grid point set by -p argument.' + PRINT *,' This option is a usefull alternative to -zoom option, when the ' + PRINT *,' area of interest is not ''box-like'' ' PRINT *,' ' PRINT *,' REQUIRED FILES :' - PRINT *,' ', TRIM(cn_fhgr),', ',TRIM(cn_fzgr),' and ',TRIM(cn_fmsk) + PRINT *,' ', TRIM(cn_fhgr),', ',TRIM(cn_fzgr),' and ',TRIM(cn_fmsk),'. If' + PRINT *,' -M option is used, the specified mask file is required instead ' + PRINT *,' ', TRIM(cn_fmsk) PRINT *,' ' PRINT *,' OUTPUT : ' PRINT *,' Standard output.' @@ -125,6 +135,9 @@ PROGRAM cdfsum CALL getarg(ijarg, cldum ) ; ijarg=ijarg+1 ; READ(cldum,*) ijmax CALL getarg(ijarg, cldum ) ; ijarg=ijarg+1 ; READ(cldum,*) ikmin CALL getarg(ijarg, cldum ) ; ijarg=ijarg+1 ; READ(cldum,*) ikmax + CASE ( '-M' ) ; lfmsk =.TRUE. + CALL getarg(ijarg, cn_fmsk ) ; ijarg=ijarg+1 + CALL getarg(ijarg, cl_vmsk ) ; ijarg=ijarg+1 CASE DEFAULT PRINT *,' Option ', TRIM(cldum),' not understood ...' STOP @@ -228,6 +241,9 @@ PROGRAM cdfsum STOP END SELECT + ! set cv_mask to on-line specified name if -M option used + IF ( lfmsk ) cv_msk = cl_vmsk + e1(:,:) = getvar (cn_fhgr, cv_e1, 1, npiglo, npjglo, kimin=iimin, kjmin=ijmin) e2(:,:) = getvar (cn_fhgr, cv_e2, 1, npiglo, npjglo, kimin=iimin, kjmin=ijmin) gdep(:) = getvare3(cn_fzgr, cv_dep, npk ) From 5422376e92628354eebbb4d9c57c8aece2cbf67b Mon Sep 17 00:00:00 2001 From: jmm Date: Mon, 23 Jan 2017 09:23:22 +0100 Subject: [PATCH 23/33] bug fix : for -TS option, correct the computation of T/S at U/V point * add missing division by 2. * New -self option telling cdftransport that the metrics are in the input data file (needs update in cdf_xtrac_brokenline) --- src/cdftransport.f90 | 24 ++++++++++++++++++------ 1 file changed, 18 insertions(+), 6 deletions(-) diff --git a/src/cdftransport.f90 b/src/cdftransport.f90 index b4caa7d..dce6424 100644 --- a/src/cdftransport.f90 +++ b/src/cdftransport.f90 @@ -195,6 +195,7 @@ PROGRAM cdftransport LOGICAL :: l_merid = .FALSE. ! flag for meridional obc LOGICAL :: l_zonal = .FALSE. ! flag for zonal obc LOGICAL :: l_tsfil = .FALSE. ! flag for using T file instead of VT file + LOGICAL :: l_self = .FALSE. ! flag for self mesh/mask files in the input !!---------------------------------------------------------------------- CALL ReadCdfNames() @@ -203,7 +204,7 @@ PROGRAM cdftransport IF ( narg == 0 ) THEN PRINT *,' usage : cdftransport [-test u v ] [-noheat ] [-plus_minus ] [-obc] [-TS] ' PRINT *,' ... [VT-file] U-file V-file [-full] |-time jt] ...' - PRINT *,' ... [-time jt ] [-zlimit limits of level]' + PRINT *,' ... [-time jt ] [-zlimit limits of level] [-self]' PRINT *,' ' PRINT *,' PURPOSE :' PRINT *,' Compute the transports accross a section.' @@ -240,9 +241,12 @@ PROGRAM cdftransport PRINT *,' transports will be computed. If not used, the transports ' PRINT *,' are computed for the whole water column. If used, this ' PRINT *,' option must be the last on the command line.' + PRINT *,' [ -self ] : This option indicates that input files corresponds to a ' + PRINT *,' broken line, hence data files hold the metrics.' PRINT *,' ' PRINT *,' REQUIRED FILES :' PRINT *,' Files ',TRIM(cn_fhgr),', ',TRIM(cn_fzgr),' must be in the current directory.' + PRINT *,' unless -self option is used.' PRINT *,' ' PRINT *,' OUTPUT : ' PRINT *,' - Standard output ' @@ -253,7 +257,7 @@ PROGRAM cdftransport PRINT *,' from section name.' PRINT *,' ' PRINT *,' SEE ALSO :' - PRINT *,' cdfsigtrp' + PRINT *,' cdfsigtrp cdf_xtrac_brokenline' PRINT *,' ' STOP ENDIF @@ -292,6 +296,9 @@ PROGRAM cdftransport CASE ( '-TS' ) l_tsfil = .TRUE. + CASE ( '-self' ) + l_self = .TRUE. + CASE ('-zlimit' ) ! this should be the last option on the line nxtarg = ijarg - 1 nclass = narg - nxtarg + 1 @@ -310,6 +317,11 @@ PROGRAM cdftransport END SELECT END DO + IF ( l_self ) THEN + cn_fzgr = cf_vfil + cn_fhgr = cf_vfil + ENDIF + ! checking if all required files are available lchk = lchk .OR. chkfile(cn_fzgr) lchk = lchk .OR. chkfile(cn_fhgr) @@ -493,10 +505,10 @@ PROGRAM cdftransport zt(:,:) = 0. ; zs(:,:) = 0. zt(1:npiglo,1:npjglo) = getvar(cf_tfil, cn_votemper, jk, npiglo, npjglo, ktime=itime) zs(1:npiglo,1:npjglo) = getvar(cf_tfil, cn_votemper, jk, npiglo, npjglo, ktime=itime) - zut(1:npiglo,1:npjglo) = zu(1:npiglo,1:npjglo) * ( zt(1:npiglo,1:npjglo) + zt(2:npiglo+1,1:npjglo)) - zus(1:npiglo,1:npjglo) = zu(1:npiglo,1:npjglo) * ( zs(1:npiglo,1:npjglo) + zs(2:npiglo+1,1:npjglo)) - zvt(1:npiglo,1:npjglo) = zv(1:npiglo,1:npjglo) * ( zt(1:npiglo,1:npjglo) + zt(1:npiglo, 1:npjglo+1)) - zvs(1:npiglo,1:npjglo) = zv(1:npiglo,1:npjglo) * ( zs(1:npiglo,1:npjglo) + zs(1:npiglo, 1:npjglo+1)) + zut(1:npiglo,1:npjglo) = zu(1:npiglo,1:npjglo) * 0.5* ( zt(1:npiglo,1:npjglo) + zt(2:npiglo+1,1:npjglo )) + zus(1:npiglo,1:npjglo) = zu(1:npiglo,1:npjglo) * 0.5* ( zs(1:npiglo,1:npjglo) + zs(2:npiglo+1,1:npjglo )). + zvt(1:npiglo,1:npjglo) = zv(1:npiglo,1:npjglo) * 0.5* ( zt(1:npiglo,1:npjglo) + zt(1:npiglo, 2:npjglo+1)). + zvs(1:npiglo,1:npjglo) = zv(1:npiglo,1:npjglo) * 0.5* ( zs(1:npiglo,1:npjglo) + zs(1:npiglo, 2:npjglo+1)). ELSE zut(:,:) = getvar(cf_tfil, cn_vozout, jk, npiglo, npjglo, ktime=itime) zvt(:,:) = getvar(cf_tfil, cn_vomevt, jk, npiglo, npjglo, ktime=itime) From 9715b2cb6aa3bfdb29c89d42fe37e5de075bb1ba Mon Sep 17 00:00:00 2001 From: Jean-Marc Molines Date: Mon, 23 Jan 2017 09:36:50 +0100 Subject: [PATCH 24/33] fix typo in T/S at U/V point computation * extra . removed --- src/cdftransport.f90 | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/cdftransport.f90 b/src/cdftransport.f90 index dce6424..416c591 100644 --- a/src/cdftransport.f90 +++ b/src/cdftransport.f90 @@ -506,9 +506,9 @@ PROGRAM cdftransport zt(1:npiglo,1:npjglo) = getvar(cf_tfil, cn_votemper, jk, npiglo, npjglo, ktime=itime) zs(1:npiglo,1:npjglo) = getvar(cf_tfil, cn_votemper, jk, npiglo, npjglo, ktime=itime) zut(1:npiglo,1:npjglo) = zu(1:npiglo,1:npjglo) * 0.5* ( zt(1:npiglo,1:npjglo) + zt(2:npiglo+1,1:npjglo )) - zus(1:npiglo,1:npjglo) = zu(1:npiglo,1:npjglo) * 0.5* ( zs(1:npiglo,1:npjglo) + zs(2:npiglo+1,1:npjglo )). - zvt(1:npiglo,1:npjglo) = zv(1:npiglo,1:npjglo) * 0.5* ( zt(1:npiglo,1:npjglo) + zt(1:npiglo, 2:npjglo+1)). - zvs(1:npiglo,1:npjglo) = zv(1:npiglo,1:npjglo) * 0.5* ( zs(1:npiglo,1:npjglo) + zs(1:npiglo, 2:npjglo+1)). + zus(1:npiglo,1:npjglo) = zu(1:npiglo,1:npjglo) * 0.5* ( zs(1:npiglo,1:npjglo) + zs(2:npiglo+1,1:npjglo )) + zvt(1:npiglo,1:npjglo) = zv(1:npiglo,1:npjglo) * 0.5* ( zt(1:npiglo,1:npjglo) + zt(1:npiglo, 2:npjglo+1)) + zvs(1:npiglo,1:npjglo) = zv(1:npiglo,1:npjglo) * 0.5* ( zs(1:npiglo,1:npjglo) + zs(1:npiglo, 2:npjglo+1)) ELSE zut(:,:) = getvar(cf_tfil, cn_vozout, jk, npiglo, npjglo, ktime=itime) zvt(:,:) = getvar(cf_tfil, cn_vomevt, jk, npiglo, npjglo, ktime=itime) From 959b9074a86a318328ddac818d949f8b6006dcb2 Mon Sep 17 00:00:00 2001 From: jmm Date: Mon, 23 Jan 2017 19:34:15 +0100 Subject: [PATCH 25/33] Bug fixes for new option -vt in cdf_xtrac_brokenline * the new variables were defined with ipk=1 instead of ipk=npk * putvar was always called for level 1 * resulting variables were then undefined --- src/cdf_xtrac_brokenline.f90 | 38 ++++++++++++++++++------------------ 1 file changed, 19 insertions(+), 19 deletions(-) diff --git a/src/cdf_xtrac_brokenline.f90 b/src/cdf_xtrac_brokenline.f90 index 36e68e6..9a90820 100644 --- a/src/cdf_xtrac_brokenline.f90 +++ b/src/cdf_xtrac_brokenline.f90 @@ -624,19 +624,19 @@ PROGRAM cdf_xtract_brokenline END DO ! output section variable at level jk, in separated output section files - ierr = putvar (ncout(jsec), id_varout(np_tem), tempersec(:,jk), jk, npsec(jsec)-1, 1, ktime=jt ) - ierr = putvar (ncout(jsec), id_varout(np_sal), salinesec(:,jk), jk, npsec(jsec)-1, 1, ktime=jt ) - ierr = putvar (ncout(jsec), id_varout(np_una), uzonalsec(:,jk), jk, npsec(jsec)-1, 1, ktime=jt ) - ierr = putvar (ncout(jsec), id_varout(np_vna), vmeridsec(:,jk), jk, npsec(jsec)-1, 1, ktime=jt ) + ierr = putvar (ncout(jsec), id_varout(np_tem), tempersec(:,jk), jk, npsec(jsec)-1, 1, ktime=jt ) + ierr = putvar (ncout(jsec), id_varout(np_sal), salinesec(:,jk), jk, npsec(jsec)-1, 1, ktime=jt ) + ierr = putvar (ncout(jsec), id_varout(np_una), uzonalsec(:,jk), jk, npsec(jsec)-1, 1, ktime=jt ) + ierr = putvar (ncout(jsec), id_varout(np_vna), vmeridsec(:,jk), jk, npsec(jsec)-1, 1, ktime=jt ) ! along-track normal velocity, horiz. and vert. resolution, and mask zvmod(:,1)= uzonalsec(:,jk) + vmeridsec(:,jk) - ierr = putvar (ncout(jsec), id_varout(np_vmod), zvmod(:,1), jk, npsec(jsec)-1, 1, ktime=jt ) - IF (ll_ssh) ierr = putvar (ncout(jsec), id_varout(np_ssh), sshsec (:,jk), 1, npsec(jsec)-1, 1, ktime=jt ) - IF (ll_mld) ierr = putvar (ncout(jsec), id_varout(np_mld), rmldsec(:,jk), 1, npsec(jsec)-1, 1, ktime=jt ) - IF (ll_ice) ierr = putvar (ncout(jsec), id_varout(np_icethick), ricethicksec(:,jk), 1, npsec(jsec)-1, 1, ktime=jt ) - IF (ll_ice) ierr = putvar (ncout(jsec), id_varout(np_icefra), ricefrasec(:,jk), 1, npsec(jsec)-1, 1, ktime=jt ) - IF (lvt ) ierr = putvar (ncout(jsec), id_varout(np_vt ), zvmod(:,1)*tempersec(:,jk), 1, npsec(jsec)-1, 1, ktime=jt ) - IF (lvt ) ierr = putvar (ncout(jsec), id_varout(np_vs ), zvmod(:,1)*salinesec(:,jk), 1, npsec(jsec)-1, 1, ktime=jt ) + ierr = putvar (ncout(jsec), id_varout(np_vmod ), zvmod(:,1), jk, npsec(jsec)-1, 1, ktime=jt ) + IF (ll_ssh) ierr = putvar (ncout(jsec), id_varout(np_ssh ), sshsec (:,jk), 1, npsec(jsec)-1, 1, ktime=jt ) + IF (ll_mld) ierr = putvar (ncout(jsec), id_varout(np_mld ), rmldsec(:,jk), 1, npsec(jsec)-1, 1, ktime=jt ) + IF (ll_ice) ierr = putvar (ncout(jsec), id_varout(np_icethick), ricethicksec(:,jk), 1, npsec(jsec)-1, 1, ktime=jt ) + IF (ll_ice) ierr = putvar (ncout(jsec), id_varout(np_icefra ), ricefrasec(:,jk), 1, npsec(jsec)-1, 1, ktime=jt ) + IF (lvt ) ierr = putvar (ncout(jsec), id_varout(np_vt ), zvmod(:,1)*tempersec(:,jk),jk, npsec(jsec)-1, 1, ktime=jt ) + IF (lvt ) ierr = putvar (ncout(jsec), id_varout(np_vs ), zvmod(:,1)*salinesec(:,jk),jk, npsec(jsec)-1, 1, ktime=jt ) IF ( jt == 1 ) THEN ! output of time independent variables at first time step only ! save a mask of the section @@ -883,7 +883,7 @@ SUBROUTINE CreateOutputFile(ksec) stypvar(ivar)%clong_name = 'icethick along '//TRIM(csection(ksec))//' section' stypvar(ivar)%cshort_name = cn_iicethic stypvar(ivar)%caxis = 'TX' - ipk(ivar) = 1 + ipk(ivar) = 1 ivar = ivar + 1 np_icefra = ivar @@ -902,23 +902,23 @@ SUBROUTINE CreateOutputFile(ksec) np_vt = ivar stypvar(ivar)%cname = cn_vomevt stypvar(ivar)%cunits = 'C.m/s' - stypvar(ivar)%valid_min = -10000. + stypvar(ivar)%valid_min = -1000000. stypvar(ivar)%valid_max = 1000000. stypvar(ivar)%clong_name = 'VT product along '//TRIM(csection(ksec))//' section' stypvar(ivar)%cshort_name = cn_vomevt - stypvar(ivar)%caxis = 'TX' - ipk(ivar) = 1 + stypvar(ivar)%caxis = 'TZX' + ipk(ivar) = npk ivar = ivar + 1 np_vs = ivar stypvar(ivar)%cname = cn_vomevs - stypvar(ivar)%cunits = 'C.m/s' - stypvar(ivar)%valid_min = -10000. + stypvar(ivar)%cunits = 'PSU.m/s' + stypvar(ivar)%valid_min = -1000000. stypvar(ivar)%valid_max = 1000000. stypvar(ivar)%clong_name = 'VS product along '//TRIM(csection(ksec))//' section' stypvar(ivar)%cshort_name = cn_vomevs - stypvar(ivar)%caxis = 'TX' - ipk(ivar) = 1 + stypvar(ivar)%caxis = 'TZX' + ipk(ivar) = npk ivar = ivar + 1 ENDIF From 420fc3959f5d16bc8a366f45db202148642f96c0 Mon Sep 17 00:00:00 2001 From: jmm Date: Mon, 23 Jan 2017 22:55:38 +0100 Subject: [PATCH 26/33] Finalize -self option on cdftransport.f90 * -self option is used with broken line files, where the relevant metrics is saved in the data file * With -self, no need to provide mesh/mask files. The broken line is considered as a pseudo zonal section, and only the relevant metrics is required. Not used metrics is just set to dummy values. --- src/cdftransport.f90 | 48 ++++++++++++++++++++++++++++++++++---------- 1 file changed, 37 insertions(+), 11 deletions(-) diff --git a/src/cdftransport.f90 b/src/cdftransport.f90 index 416c591..cd9424f 100644 --- a/src/cdftransport.f90 +++ b/src/cdftransport.f90 @@ -426,13 +426,25 @@ PROGRAM cdftransport ! ! read metrics and grid position e1v(:,:) = getvar(cn_fhgr, cn_ve1v, 1, npiglo, npjglo) - e2u(:,:) = getvar(cn_fhgr, cn_ve2u, 1, npiglo, npjglo) + IF ( l_self ) THEN + e2u(:,:) = 1. ! dummy value, not used + glamf(:,:) = 1. + gphif(:,:) = 1. + ! use e31d for temporary calculation + e31d(:) = getvar1d(cf_tfil, cn_vdeptht, npk) + gdepw(1) = 0. + gdepw(2:npk) = 0.5 * (e31d(1:npk-1) + e31d(2:npk)) ! This is just a proxy for gdepw + ! max error ~ 1m for 46 lev + e31d(:) = 1. ! set dummy value for e31d + ELSE + e2u(:,:) = getvar(cn_fhgr, cn_ve2u, 1, npiglo, npjglo) - glamf(:,:) = getvar(cn_fhgr, cn_glamf, 1,npiglo, npjglo) - gphif(:,:) = getvar(cn_fhgr, cn_gphif, 1,npiglo, npjglo) + glamf(:,:) = getvar(cn_fhgr, cn_glamf, 1,npiglo, npjglo) + gphif(:,:) = getvar(cn_fhgr, cn_gphif, 1,npiglo, npjglo) - gdepw(:) = getvare3(cn_fzgr, cn_gdepw, npk) - e31d(:) = getvare3(cn_fzgr, cn_ve3t, npk) ! used only for full step + gdepw(:) = getvare3(cn_fzgr, cn_gdepw, npk) + e31d(:) = getvare3(cn_fzgr, cn_ve3t, npk) ! used only for full step + ENDIF ! look for nearest level to imeter and setup ilev0 and ilev1 (t-index of class limit) ik = 1 @@ -498,21 +510,30 @@ PROGRAM cdftransport ELSE IF ( l_merid ) THEN ; zu(1,:)=zuobc(:,jk) ; zv(1,:)=zvobc(:,jk) ENDIF ELSE - zu (:,:) = getvar(cf_ufil, cn_vozocrtx, jk, npiglo, npjglo, ktime=itime) + IF ( l_self ) THEN + zu(:,:) = 0. + ELSE + zu (:,:) = getvar(cf_ufil, cn_vozocrtx, jk, npiglo, npjglo, ktime=itime) + ENDIF zv (:,:) = getvar(cf_vfil, cn_vomecrty, jk, npiglo, npjglo, ktime=itime) IF (lheat) THEN IF ( l_tsfil ) THEN zt(:,:) = 0. ; zs(:,:) = 0. zt(1:npiglo,1:npjglo) = getvar(cf_tfil, cn_votemper, jk, npiglo, npjglo, ktime=itime) - zs(1:npiglo,1:npjglo) = getvar(cf_tfil, cn_votemper, jk, npiglo, npjglo, ktime=itime) + zs(1:npiglo,1:npjglo) = getvar(cf_tfil, cn_vosaline, jk, npiglo, npjglo, ktime=itime) zut(1:npiglo,1:npjglo) = zu(1:npiglo,1:npjglo) * 0.5* ( zt(1:npiglo,1:npjglo) + zt(2:npiglo+1,1:npjglo )) zus(1:npiglo,1:npjglo) = zu(1:npiglo,1:npjglo) * 0.5* ( zs(1:npiglo,1:npjglo) + zs(2:npiglo+1,1:npjglo )) zvt(1:npiglo,1:npjglo) = zv(1:npiglo,1:npjglo) * 0.5* ( zt(1:npiglo,1:npjglo) + zt(1:npiglo, 2:npjglo+1)) zvs(1:npiglo,1:npjglo) = zv(1:npiglo,1:npjglo) * 0.5* ( zs(1:npiglo,1:npjglo) + zs(1:npiglo, 2:npjglo+1)) ELSE - zut(:,:) = getvar(cf_tfil, cn_vozout, jk, npiglo, npjglo, ktime=itime) + IF ( l_self ) THEN + zut(:,:) = 0. + zus(:,:) = 0. + ELSE + zut(:,:) = getvar(cf_tfil, cn_vozout, jk, npiglo, npjglo, ktime=itime) + zus(:,:) = getvar(cf_tfil, cn_vozous, jk, npiglo, npjglo, ktime=itime) + ENDIF zvt(:,:) = getvar(cf_tfil, cn_vomevt, jk, npiglo, npjglo, ktime=itime) - zus(:,:) = getvar(cf_tfil, cn_vozous, jk, npiglo, npjglo, ktime=itime) zvs(:,:) = getvar(cf_tfil, cn_vomevs, jk, npiglo, npjglo, ktime=itime) ENDIF ENDIF @@ -523,8 +544,13 @@ PROGRAM cdftransport e3v(:,:) = e31d(jk) e3u(:,:) = e31d(jk) ELSE - e3v(:,:) = getvar(cn_fzgr, 'e3v_ps', jk, npiglo, npjglo, ldiom=.TRUE.) - e3u(:,:) = getvar(cn_fzgr, 'e3u_ps', jk, npiglo, npjglo, ldiom=.TRUE.) + IF ( l_self) THEN + e3u(:,:) = 1. !dummy value + e3v(:,:) = getvar(cn_fzgr, 'e3v_ps', jk, npiglo, npjglo, ldiom=.FALSE.) ! In broken line name is e3v_ps + ELSE + e3u(:,:) = getvar(cn_fzgr, 'e3u_ps', jk, npiglo, npjglo, ldiom=.TRUE.) + e3v(:,:) = getvar(cn_fzgr, 'e3v_ps', jk, npiglo, npjglo, ldiom=.TRUE.) + ENDIF ENDIF dwku (:,:) = zu (:,:)*e2u(:,:)*e3u(:,:)*1.d0 From baf8c72e3d8033042889b181d85103815eb65638 Mon Sep 17 00:00:00 2001 From: Javier Vegas-Regidor Date: Wed, 25 Jan 2017 12:21:31 +0100 Subject: [PATCH 27/33] Added -ov and -ot to cdfmean --- src/cdfmean.f90 | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/src/cdfmean.f90 b/src/cdfmean.f90 index 82162ab..564bbd7 100644 --- a/src/cdfmean.f90 +++ b/src/cdfmean.f90 @@ -116,8 +116,12 @@ PROGRAM cdfmean PRINT *,' [ -var ] : also compute the spatial variance of cdfvar ' PRINT *,' [ -zeromean ] : create a file with cdfvar having a zero spatial mean.' PRINT *,' [ -o OUT-file] : specify the name of the output file instead of ',TRIM(cf_ncout) - PRINT *,' [ -zo ZEROMEAN-file] : specify the name of the output file for option ' + PRINT *,' [ -ot OUTASCII-file] : specify the name of the output ASCII file instead ' + PRINT *,' of ',TRIM(cf_out) + PRINT *,' [ -oz ZEROMEAN-file] : specify the name of the output file for option ' PRINT *,' -zeromean, instead of ', TRIM(cf_zerom) + PRINT *,' [ -ov VAR-file] : specify the name of the output file for option ' + PRINT *,' -var, instead of ', TRIM(cf_var) PRINT *,' ' PRINT *,' REQUIRED FILES :' PRINT *,' Files ', TRIM(cn_fhgr),', ', TRIM(cn_fzgr),', ', TRIM(cn_fmsk) @@ -154,6 +158,10 @@ PROGRAM cdfmean CALL getarg(ijarg, cf_ncout ) ; ijarg = ijarg + 1 CASE ('-oz' ) CALL getarg(ijarg, cf_zerom ) ; ijarg = ijarg + 1 + CASE ('-ov' ) + CALL getarg(ijarg, cf_var ) ; ijarg = ijarg + 1 + CASE ('-ot' ) + CALL getarg(ijarg, cf_out ) ; ijarg = ijarg + 1 CASE DEFAULT ii=ii+1 SELECT CASE (ii) From be8f19b4e6ae235232ac60484155789865889fa6 Mon Sep 17 00:00:00 2001 From: Javier Vegas-Regidor Date: Wed, 25 Jan 2017 16:51:18 +0100 Subject: [PATCH 28/33] Added customizable mask feature for cdfmean --- src/cdfmean.f90 | 21 ++++++++++++++------- 1 file changed, 14 insertions(+), 7 deletions(-) diff --git a/src/cdfmean.f90 b/src/cdfmean.f90 index 564bbd7..e9aec06 100644 --- a/src/cdfmean.f90 +++ b/src/cdfmean.f90 @@ -64,7 +64,7 @@ PROGRAM cdfmean CHARACTER(LEN=256) :: cv_dep ! deptht name CHARACTER(LEN=20) :: cv_e1, cv_e2 ! horizontal metrics names CHARACTER(LEN=20) :: cv_e3, cv_e31d ! vertical metrics names - CHARACTER(LEN=20) :: cv_msk ! mask variable name + CHARACTER(LEN=20) :: cv_msk = '' ! mask variable name CHARACTER(LEN=256) :: cf_in ! input file name CHARACTER(LEN=256) :: cf_out = 'cdfmean.txt' ! ASCII output file for mean CHARACTER(LEN=256) :: cf_var = 'cdfvar.txt' ! ASCII output file for variance @@ -111,6 +111,10 @@ PROGRAM cdfmean PRINT *,' if imin = 0 then ALL i are taken' PRINT *,' if jmin = 0 then ALL j are taken' PRINT *,' if kmin = 0 then ALL k are taken' + PRINT *,' [-M MSK-file VAR-mask] : Allow the use of a non standard mask file ' + PRINT *,' with VAR-mask, instead of ',TRIM(cn_fmsk),' and ',TRIM(cv_msk) + PRINT *,' This option is a usefull alternative to the previous options, when the ' + PRINT *,' area of interest is not ''box-like''' PRINT *,' [ -full ] : compute the mean for full steps, instead of default ' PRINT *,' partial steps.' PRINT *,' [ -var ] : also compute the spatial variance of cdfvar ' @@ -162,6 +166,9 @@ PROGRAM cdfmean CALL getarg(ijarg, cf_var ) ; ijarg = ijarg + 1 CASE ('-ot' ) CALL getarg(ijarg, cf_out ) ; ijarg = ijarg + 1 + CASE ( '-M' ) + CALL getarg ( ijarg, cn_fmsk) ; ijarg = ijarg + 1 + CALL getarg ( ijarg, cv_msk ) ; ijarg = ijarg + 1 CASE DEFAULT ii=ii+1 SELECT CASE (ii) @@ -241,35 +248,35 @@ PROGRAM cdfmean cv_e2 = cn_ve2t cv_e3 = 'e3t_ps' cv_e31d = cn_ve3t - cv_msk = 'tmask' + IF (cv_msk == '' ) THEN ; cv_msk = 'tmask' ; ENDIF cv_dep = cn_gdept CASE ( 'U' ) cv_e1 = cn_ve1u cv_e2 = cn_ve2u cv_e3 = 'e3t_ps' cv_e31d = cn_ve3t - cv_msk = 'umask' + IF (cv_msk == '' ) THEN ; cv_msk = 'umask' ; ENDIF cv_dep = cn_gdept CASE ( 'V' ) cv_e1 = cn_ve1v cv_e2 = cn_ve2v cv_e3 = 'e3t_ps' cv_e31d = cn_ve3t - cv_msk = 'vmask' + IF (cv_msk == '' ) THEN ; cv_msk = 'vmask' ; ENDIF cv_dep = cn_gdept CASE ( 'F' ) cv_e1 = cn_ve1f cv_e2 = cn_ve2f cv_e3 = 'e3t_ps' cv_e31d = cn_ve3t - cv_msk = 'fmask' + IF (cv_msk == '' ) THEN ; cv_msk = 'fmask' ; ENDIF cv_dep = cn_gdept CASE ( 'W' ) cv_e1 = cn_ve1t cv_e2 = cn_ve2t cv_e3 = 'e3w_ps' cv_e31d = cn_ve3w - cv_msk = 'tmask' + IF (cv_msk == '' ) THEN ; cv_msk = 'tmask' ; ENDIF cv_dep = cn_gdepw CASE DEFAULT PRINT *, 'this type of variable is not known :', TRIM(ctype) @@ -362,7 +369,7 @@ PROGRAM cdfmean ELSE e3(:,:) = getvar(cn_fzgr, cv_e3, ik, npiglo, npjglo, kimin=iimin, kjmin=ijmin, ldiom=.TRUE.) ENDIF - ! + ! dsurf = SUM(DBLE( e1 * e2 * zmask)) dvol2d = SUM(DBLE( e1 * e2 * e3 * zmask)) dvol = dvol + dvol2d From 305acdd52c9ce6eebdf858070229a0ddba63ae5e Mon Sep 17 00:00:00 2001 From: jmm Date: Mon, 6 Feb 2017 22:11:13 +0100 Subject: [PATCH 29/33] Improve functions GetNcfile etc.. not used yet. * This function is developped for a more robust determination of the caracteristics of the fileset. --- src/cdfio.F90 | 36 ++++++++++++++++++++++++++++++++++-- 1 file changed, 34 insertions(+), 2 deletions(-) diff --git a/src/cdfio.F90 b/src/cdfio.F90 index 28c268e..35d6053 100644 --- a/src/cdfio.F90 +++ b/src/cdfio.F90 @@ -114,15 +114,18 @@ MODULE cdfio INTEGER(KIND=4) :: idz ! z dimid INTEGER(KIND=4) :: idt ! t dimid INTEGER(KIND=4) :: idb ! time-bound dimid + INTEGER(KIND=4), DIMENSION(:), ALLOCATABLE :: ideflat ! deflate level (nvar) INTEGER(KIND=4), DIMENSION(:), ALLOCATABLE :: nvatt ! number of att of each variable (var) INTEGER(KIND=4), DIMENSION(:), ALLOCATABLE :: nvid ! varid of each variable (var) INTEGER(KIND=4), DIMENSION(:), ALLOCATABLE :: nvdim ! dimension of each variable (var) INTEGER(KIND=4), DIMENSION(:), ALLOCATABLE :: itype ! type of each variable (var) INTEGER(KIND=4), DIMENSION(:), ALLOCATABLE :: nlen ! len of each dimension ( ndims) + INTEGER(KIND=4), DIMENSION(:,:), ALLOCATABLE :: ichunk ! size of chunk (nvar, ndims) INTEGER(KIND=4), DIMENSION(:,:), ALLOCATABLE :: idimids ! dimids of each variable (nvar, ndims) CHARACTER(LEN=255) :: c_fnam ! name of working file CHARACTER(LEN=80 ), DIMENSION(:), ALLOCATABLE :: c_vnam ! name of each variable (var) CHARACTER(LEN=80 ), DIMENSION(:), ALLOCATABLE :: c_dnam ! name of each dimension (ndims) + LOGICAL, DIMENSION(:), ALLOCATABLE :: lconti ! contiguous flag (nvar) ! extra information for global attribute INTEGER(KIND=4) :: number_total ! DOMAIN_number_total INTEGER(KIND=4) :: number ! DOMAIN_number @@ -3007,18 +3010,47 @@ FUNCTION GetNcFile (cd_file) ALLOCATE (GetNcFile%c_vnam (GetNcFile%nvars) ) ALLOCATE (GetNcFile%nvatt (GetNcFile%nvars) ) ALLOCATE (GetNcFile%itype (GetNcFile%nvars) ) - ALLOCATE (GetNcFile%c_dnam(GetNcFile%ndims) ) + ALLOCATE (GetNcFile%c_dnam (GetNcFile%ndims) ) ALLOCATE (GetNcFile%nlen (GetNcFile%ndims) ) ALLOCATE (GetNcFile%idimids (GetNcFile%nvars,GetNcFile%ndims) ) + ! Look for dimensions + DO jdim = 1, GetNcFile%ndims + ierr = NF90_INQUIRE_DIMENSION(GetNcFile%ncid,jdim, & + & name = GetNcFile%c_dnam(jdim), & + & len = GetNcFile%nlen (jdim) ) + ENDDO + ! Look for variables DO jvar = 1, GetNcFile%nvars ierr = NF90_INQUIRE_VARIABLE (GetNcFile%ncid, jvar, & & name = GetNcFile%c_vnam(jvar), & & xtype = GetNcFile%itype(jvar), & & ndims = GetNcFile%nvdim(jvar), & & dimids = GetNcFile%idimids(jvar,:), & - & nAtts = GetNcFile%nvatt(jvar) ) + & nAtts = GetNcFile%nvatt(jvar), & + & contiguous = GetNcFile%lconti(jvar), & + & chunksizes = GetNcFile%ichunk(jvar,:), & + & deflate_level = GetNcFile%ideflat(jvar) ) END DO + ! Look for attributes + ierr = NF90_GET_ATT (GetNcFile%ncid, NF90_GLOBAL, 'DOMAIN_number_total' , GetNcFile%number_total ) + ierr = NF90_GET_ATT (GetNcFile%ncid, NF90_GLOBAL, 'DOMAIN_number ' , GetNcFile%number ) + ierr = NF90_GET_ATT (GetNcFile%ncid, NF90_GLOBAL, 'DOMAIN_dimensions_ids' , GetNcFile%idimensions_ids(:) ) + ierr = NF90_GET_ATT (GetNcFile%ncid, NF90_GLOBAL, 'DOMAIN_size_global' , GetNcFile%isize_global(:) ) + ierr = NF90_GET_ATT (GetNcFile%ncid, NF90_GLOBAL, 'DOMAIN_size_local' , GetNcFile%isize_local(:) ) + ierr = NF90_GET_ATT (GetNcFile%ncid, NF90_GLOBAL, 'DOMAIN_position_first' , GetNcFile%iposition_first(:) ) + ierr = NF90_GET_ATT (GetNcFile%ncid, NF90_GLOBAL, 'DOMAIN_position_last' , GetNcFile%iposition_last(:) ) + ierr = NF90_GET_ATT (GetNcFile%ncid, NF90_GLOBAL, 'DOMAIN_halo_size_start', GetNcFile%ihalo_size_start(:)) + ierr = NF90_GET_ATT (GetNcFile%ncid, NF90_GLOBAL, 'DOMAIN_halo_size_end' , GetNcFile%ihalo_size_end(:) ) + ierr = NF90_GET_ATT (GetNcFile%ncid, NF90_GLOBAL, 'DOMAIN_type' , GetNcFile%c_type ) + + ! NOTE : for recombined files, no more DOMAIN attributes !!! + ! DOMAIN_dimensions_ids gives ids for x, y + idx = GetNcFile%idimensions_ids(1) + idy = GetNcFile%idimensions_ids(2) + ! time is unlimited dim + idt = GetNcFile%iunlim + ! try to infer size of the domain assuming some basis: ! (1) 2D var are (x,y) ! (2) time dim is unlimited From 6b699f1defd9df51e13a8c722e8b915f24f853cb Mon Sep 17 00:00:00 2001 From: Javier Vegas-Regidor Date: Tue, 7 Feb 2017 16:05:40 +0000 Subject: [PATCH 30/33] Added info about the new options to the synopsis --- src/cdfmean.f90 | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/cdfmean.f90 b/src/cdfmean.f90 index e9aec06..1aa01eb 100644 --- a/src/cdfmean.f90 +++ b/src/cdfmean.f90 @@ -93,7 +93,9 @@ PROGRAM cdfmean narg = iargc() IF ( narg == 0 ) THEN PRINT *,' usage : cdfmean IN-file IN-var T|U|V|F|W [imin imax jmin jmax kmin kmax]' - PRINT *,' ... [-full] [-var] [-zeromean] [-o OUT-file] [-oz ZEROMEAN-file]' + PRINT *,' ... [-full] [-var] [-zeromean] [-M MSK-file VAR-mask ] + PRINT *,' ... [-o OUT-file] [ -ot OUTASCII-file] [-oz ZEROMEAN-file]' + PRINT *,' ... [ -ov VAR-file] PRINT *,' ' PRINT *,' PURPOSE :' PRINT *,' Computes the mean value of the field (3D, weighted). For 3D fields,' From 1d74ade0b7c513ee82b763037af91deceefcde9e Mon Sep 17 00:00:00 2001 From: jmm Date: Tue, 7 Feb 2017 17:21:43 +0100 Subject: [PATCH 31/33] Allow more 3rd dimension names in cdfmoy * this is mainly for lim3 and ICB files * still some work to do for ICB as it may have 2 'vertical' axis in the same files --- src/cdfmoy.f90 | 32 +++++++++++++------------------- 1 file changed, 13 insertions(+), 19 deletions(-) diff --git a/src/cdfmoy.f90 b/src/cdfmoy.f90 index d8e5686..e48faf4 100644 --- a/src/cdfmoy.f90 +++ b/src/cdfmoy.f90 @@ -36,6 +36,7 @@ PROGRAM cdfmoy INTEGER(KIND=4) :: jk, jfil ! dummy loop index INTEGER(KIND=4) :: jvar, jv, jt ! dummy loop index INTEGER(KIND=4) :: ierr ! working integer + INTEGER(KIND=4) :: idep, idep_max ! possible depth index, maximum INTEGER(KIND=4) :: narg, iargc, ijarg ! browsing command line INTEGER(KIND=4) :: nfil ! number of files to average INTEGER(KIND=4) :: npiglo, npjglo ! size of the domain @@ -84,6 +85,7 @@ PROGRAM cdfmoy CHARACTER(LEN=256), DIMENSION(:), ALLOCATABLE :: cv_nam2 ! array of var2 name for output CHARACTER(LEN=256), DIMENSION(:), ALLOCATABLE :: cv_nam3 ! array of var3 name for output CHARACTER(LEN=256), DIMENSION(:), ALLOCATABLE :: cv_nam4 ! array of var3 name for output + CHARACTER(LEN=256), DIMENSION(:), ALLOCATABLE :: clv_dep ! array of possible depth name (or 3rd dimension) TYPE (variable), DIMENSION(:), ALLOCATABLE :: stypvar ! attributes for average values TYPE (variable), DIMENSION(:), ALLOCATABLE :: stypvar2 ! attributes for square averaged values @@ -214,28 +216,20 @@ PROGRAM cdfmoy npiglo = getdim (cf_in, cn_x) npjglo = getdim (cf_in, cn_y) - npk = getdim (cf_in, cn_z, cdtrue=cv_dep, kstatus=ierr) - - IF (ierr /= 0 ) THEN - npk = getdim (cf_in, 'z',cdtrue=cv_dep,kstatus=ierr) - IF (ierr /= 0 ) THEN - npk = getdim (cf_in,'sigma',cdtrue=cv_dep,kstatus=ierr) - IF ( ierr /= 0 ) THEN - npk = getdim (cf_in,'nav_lev',cdtrue=cv_dep,kstatus=ierr) - IF ( ierr /= 0 ) THEN - npk = getdim (cf_in,'levels',cdtrue=cv_dep,kstatus=ierr) - IF ( ierr /= 0 ) THEN - PRINT *,' assume file with no depth' - npk=0 - ENDIF - ENDIF - ENDIF - ENDIF - ENDIF + + ! looking for npk among various possible name + idep_max=8 + ALLOCATE ( clv_dep(idep_max) ) + clv_dep(:) = (/cn_z,'z','sigma','nav_lev','levels','ncatice','icbcla','icbsect'/) + idep=1 ; ierr=1000 + DO WHILE ( ierr /= 0 .AND. idep <= idep_max ) + npk = getdim (cf_in, clv_dep(idep), cdtrue=cv_dep, kstatus=ierr) + idep = idep + 1 + ENDDO PRINT *, 'npiglo = ', npiglo PRINT *, 'npjglo = ', npjglo - PRINT *, 'npk = ', npk + PRINT *, 'npk = ', npk , 'Dep name :' , TRIM(cv_dep) ALLOCATE( dtab(npiglo,npjglo), dtab2(npiglo,npjglo), v2d(npiglo,npjglo),rmask2d(npiglo,npjglo)) ! [from SL] ALLOCATE( rmean(npiglo,npjglo), rmean2(npiglo,npjglo) ) From ed4089352cc646e842b956878e6ddb79bca39c3c Mon Sep 17 00:00:00 2001 From: jmm Date: Tue, 7 Feb 2017 22:00:01 +0100 Subject: [PATCH 32/33] Fix a typo in cdfmean usage message * missing ending quotes --- src/cdfmean.f90 | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/cdfmean.f90 b/src/cdfmean.f90 index 1aa01eb..a9dd24a 100644 --- a/src/cdfmean.f90 +++ b/src/cdfmean.f90 @@ -93,9 +93,9 @@ PROGRAM cdfmean narg = iargc() IF ( narg == 0 ) THEN PRINT *,' usage : cdfmean IN-file IN-var T|U|V|F|W [imin imax jmin jmax kmin kmax]' - PRINT *,' ... [-full] [-var] [-zeromean] [-M MSK-file VAR-mask ] + PRINT *,' ... [-full] [-var] [-zeromean] [-M MSK-file VAR-mask ]' PRINT *,' ... [-o OUT-file] [ -ot OUTASCII-file] [-oz ZEROMEAN-file]' - PRINT *,' ... [ -ov VAR-file] + PRINT *,' ... [ -ov VAR-file]' PRINT *,' ' PRINT *,' PURPOSE :' PRINT *,' Computes the mean value of the field (3D, weighted). For 3D fields,' From 87e0d166977fb2473c5b1a6c117a771666c9a6f8 Mon Sep 17 00:00:00 2001 From: jmm Date: Tue, 7 Feb 2017 22:01:10 +0100 Subject: [PATCH 33/33] Update DOC/cdftools.html --- DOC/cdftools.html | 94 +++++++++++++++++++++++++++++++++++------------ 1 file changed, 71 insertions(+), 23 deletions(-) diff --git a/DOC/cdftools.html b/DOC/cdftools.html index d29accb..bb52194 100644 --- a/DOC/cdftools.html +++ b/DOC/cdftools.html @@ -1484,6 +1484,7 @@

    cdfheatc

      usage :  cdfheatc  -f T-file [-mxloption option] ...
           [-zoom imin imax jmin jmax kmin kmax] [-full] [-o OUT-file]
    +      [-M MSK-file VAR-mask ]
            
           PURPOSE :
              Computes the heat content in the specified 3D area (Joules)
    @@ -1503,6 +1504,10 @@ 

    cdfheatc

    option=-1 : exclude mixed layer in the computation option= 0 : [Default], do not take care of mxl. [-o OUT-file ] : specify netcdf output filename instead of heatc.nc + [-M MSK-file VAR-mask] : Allow the use of a non standard mask file + with VAR-mask, instead of mask.nc and tmask + This option is a usefull alternative to -zoom option, when the + area of interest is not 'box-like' REQUIRED FILES : Files mesh_hgr.nc, mesh_zgr.nc and mask.nc @@ -1512,7 +1517,10 @@

    cdfheatc

    variables: heatc3d (Joules) : heatc(dep) (Joules) : heatc3dpervol (Joules/m3) - Standard output
    + Standard output + + SEE ALSO: + cdfpolymask

    cdfhflx

    @@ -2022,7 +2030,9 @@

    cdfmaxmoc

    cdfmean

      usage : cdfmean  IN-file IN-var T|U|V|F|W [imin imax jmin jmax kmin kmax]
    -        ... [-full] [-var] [-zeromean] 
    +        ... [-full] [-var] [-zeromean] [-M MSK-file VAR-mask ]
    +        ... [-o OUT-file] [ -ot OUTASCII-file] [-oz ZEROMEAN-file]
    +        ... [ -ov VAR-file]
            
           PURPOSE :
              Computes the mean value of the field (3D, weighted). For 3D fields,
    @@ -2040,10 +2050,24 @@ 

    cdfmean

    if imin = 0 then ALL i are taken if jmin = 0 then ALL j are taken if kmin = 0 then ALL k are taken + [-M MSK-file VAR-mask] : Allow the use of a non standard mask file + with VAR-mask, instead of mask.nc and + This option is a usefull alternative to the previous options, whe + n the + area of interest is not 'box-like' [ -full ] : compute the mean for full steps, instead of default partial steps. [ -var ] : also compute the spatial variance of cdfvar [ -zeromean ] : create a file with cdfvar having a zero spatial mean. + [ -o OUT-file] : specify the name of the output file instead of + cdfmean.nc + [ -ot OUTASCII-file] : specify the name of the output ASCII file instead + + of cdfmean.txt + [ -oz ZEROMEAN-file] : specify the name of the output file for option + -zeromean, instead of zeromean.nc + [ -ov VAR-file] : specify the name of the output file for option + -var, instead of cdfvar.txt REQUIRED FILES : Files mesh_hgr.nc, mesh_zgr.nc, mask.nc @@ -2061,7 +2085,7 @@

    cdfmean

    cdfmhst

      usage : cdfmhst  VT-file | (V-file T-file [S-file])  [MST] [-full] ...
    -               ...  [-Zdim] 
    +               ...  [-Zdim] [-o OUT-file]
            
           PURPOSE :
             Compute the meridional heat/salt transport as a function of 
    @@ -2080,6 +2104,7 @@ 

    cdfmhst

    If not specified, only the MHT is output. [-full ] : to be set for full step case. [-Zdim ] : to be set to output vertical structure of Heat/salt transport + [-o OUT-file ] : change name of the output file. Default:mhst.nc REQUIRED FILES : mesh_hgr.nc, mesh_zgr.nc and mask.nc @@ -2089,7 +2114,7 @@

    cdfmhst

    OUTPUT : ASCII files : zonal_heat_trp.dat : Meridional Heat Transport zonal_salt_trp.dat : Meridional Salt Transport - netcdf file : mhst.nc + netcdf file : mhst.nc unless -o option is used. variables : ( [... ] : MST option ) zomht_glo : Meridional Heat Transport (global) [ zomst_glo : Meridional Salt Transport (global) ] @@ -2835,7 +2860,7 @@

    cdfpendep

    cdfpolymask

    -
      usage : cdfpolymask POLY-file REF-file [ -r]
    +
      usage : cdfpolymask -p POLY-file -ref REF-file [ -r] [-o OUT_file]
            
           PURPOSE :
             Create a maskfile with polymask variable having 1
    @@ -2843,18 +2868,22 @@ 

    cdfpolymask

    the behaviour (0 inside, 1 outside). ARGUMENTS : - POLY-file : input ASCII file describing a polyline in I J grid. + -p POLY-file : input ASCII file describing a polyline in I J grid. This file is structured by block, one block corresponding to a polygon: 1rst line of the block gives a polygon name 2nd line gives the number of vertices (nvert) and a dummy 0 the block finishes with nvert pairs of (I,J) describing the polygon vertices. - REF-file : reference netcdf file for header of polymask file. + -ref REF-file : reference netcdf file for header of polymask file. + This file will be used to look for domain dimensions, and + in order to build the output file (nav_lon, nav_lat etc ...) OPTIONS : [ -r ] : revert option. When used, 0 is inside the polygon, 1 outside. + [ -o OUT-file ] : spefify the name of the output mask file instead + of polymask.nc REQUIRED FILES : none @@ -3744,31 +3773,45 @@

    cdfstrconv

    cdfsum

    -
      usage : cdfsum IN-file IN-var T| U | V | F | W  ... 
    -              ... [imin imax jmin jmax kmin kmax] [-full ] 
    +
      usage : cdfsum -f IN-file -v IN-var -p T| U | V | F | W  ... 
    +           ... [-zoom imin imax jmin jmax kmin kmax] [-full ] [-o OUT-file] 
    +           ... [-M MSK-file VAR-mask ]
            
           PURPOSE :
             Computes the sum value of the field (3D, weighted)
    -        This sum can be optionally limited to a sub-area.
    +        This sum can be optionally limited to a 3D sub-area.
            
           ARGUMENTS :
    -        IN-file : netcdf input file.
    -        IN-var  : netcdf variable to work with.
    -        T| U | V | F | W : C-grid point where IN-var is located.
    +        -f IN-file : netcdf input file.
    +        -v IN-var  : netcdf variable to work with.
    +        -p T| U | V | F | W : C-grid point where IN-var is located.
            
           OPTIONS :
    -        [imin imax jmin jmax kmin kmax] : limit of the sub area to work with.
    +        [-zoom imin imax jmin jmax kmin kmax] : limit of the 3D sub area. 
                    if imin=0 all i are taken
                    if jmin=0 all j are taken
                    if kmin=0 all k are taken
    +        [ -full : ] Use full steps instead of default partial steps
    +        [-o OUT-file ] : name of the output file instead ofcdfsum.nc
    +        [-M MSK-file VAR-mask] : Allow the use of a non standard mask file 
    +               with VAR-mask, instead of mask.nc and the variable
    +               associated with the grid point set by -p argument.
    +               This option is a usefull alternative to -zoom option, when the 
    +               area of interest is not 'box-like' 
            
           REQUIRED FILES :
    -       mesh_hgr.nc, mesh_zgr.nc and mask.nc
    +       mesh_hgr.nc, mesh_zgr.nc and mask.nc. If
    +          -M option is used, the specified mask file is required instead 
    +          mask.nc
            
           OUTPUT : 
             Standard output.
    -        netcdf file : cdfsum.nc with 2 variables : vertical profile of sum
    -                      and 3D sum.
    + netcdf file : cdfsum.nc unless modified with -o option. + - 2 variables : vertical profile of sum and 3D sum. + names are sum_<varname> and sum3D_<varname>. + + SEE ALSO: + cdfmean

    cdftempvol-full

    @@ -3784,9 +3827,9 @@

    cdftempvol-full

    cdftransport

    -
      usage : cdftransport [-test  u v ] [-noheat ] [-plus_minus ] [-obc]...
    +
      usage : cdftransport [-test  u v ] [-noheat ] [-plus_minus ] [-obc] [-TS] 
                        ... [VT-file] U-file V-file [-full] |-time jt] ...
    -                   ... [-time jt ] [-zlimit limits of level]
    +                   ... [-time jt ] [-zlimit limits of level] [-self]
            
          PURPOSE :
            Compute the transports accross a section.
    @@ -3812,18 +3855,23 @@ 

    cdftransport

    the volume transport. This option implicitly set -noheat, and must be used before the file names. [-obc ] : indicates that input files are obc files (vertical slices) - Take care that for this case, mesh files must be adapted. - This option implicitly set -noheat, and must be used before - the file names. + Take care that for this case, mesh files must be adapted. + This option implicitly set -noheat, and must be used before + the file names. + [ -TS ] : Indicate that UT VT US VS will be recomputed from T U V + files. T-file is passed as the first file instead of VT [-full ] : use for full step configurations. [-time jt ]: compute transports for time index jt. Default is 1. [-zlimit list of depth] : Specify depths limits defining layers where the transports will be computed. If not used, the transports are computed for the whole water column. If used, this option must be the last on the command line. + [ -self ] : This option indicates that input files corresponds to a + broken line, hence data files hold the metrics. REQUIRED FILES : Files mesh_hgr.nc, mesh_zgr.nc must be in the current directory. + unless -self option is used. OUTPUT : - Standard output @@ -3834,7 +3882,7 @@

    cdftransport

    from section name. SEE ALSO : - cdfsigtrp + cdfsigtrp cdf_xtrac_brokenline

    cdfuv