[cdftools] 52/228: RD : add netcdf output in cdfprofile and computation between two levels in cdfhdy

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


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

mckinstry pushed a commit to branch master
in repository cdftools.

commit b000bc80b5cce848dc661cb485ef50d4b3ca8a30
Author: dussin <dussin at 1055176f-818a-41d9-83e1-73fbe5b947c5>
Date:   Fri Jun 4 09:29:07 2010 +0000

    RD : add netcdf output in cdfprofile and computation between two levels in cdfhdy
    
    
    git-svn-id: http://servforge.legi.grenoble-inp.fr/svn/CDFTOOLS/trunk@328 1055176f-818a-41d9-83e1-73fbe5b947c5
---
 cdfhdy.f90     | 30 ++++++++++++++---------------
 cdfprofile.f90 | 60 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++--
 2 files changed, 73 insertions(+), 17 deletions(-)

diff --git a/cdfhdy.f90 b/cdfhdy.f90
index 3e37c71..b891314 100644
--- a/cdfhdy.f90
+++ b/cdfhdy.f90
@@ -26,7 +26,7 @@ PROGRAM cdfhdy
   INTEGER   :: npiglo,npjglo, npk, npt             !: size of the domain
   INTEGER, DIMENSION(1) ::  ipk, &                 !: outptut variables : number of levels,
        &                    id_varout              !: ncdf varid's
-  real(KIND=4) , DIMENSION (:,:), ALLOCATABLE :: ztemp, zsal ,&   !: Array to read a layer of data
+  real(KIND=8) , DIMENSION (:,:), ALLOCATABLE :: ztemp, zsal ,&   !: Array to read a layer of data
        &                                         ztemp0, zsal0 ,&   !: reference density
        &                                         zsig0 , &        !: potential density (sig-0)
        &                                         zsig  , &        !: potential density (sig-0)
@@ -178,25 +178,25 @@ SUBROUTINE eos_insitu( ptem, psal, pdepth, jpiglo, jpjglo, prd )
      !! References :   Jackett and McDougall, J. Atmos. Ocean. Tech., 1994
      !!----------------------------------------------------------------------
      INTEGER, INTENT(in   )                           ::   jpiglo, jpjglo
-     REAL(4), DIMENSION(jpiglo,jpjglo), INTENT(in   ) ::   ptem   ! potential temperature  [Celcius]
-     REAL(4), DIMENSION(jpiglo,jpjglo), INTENT(in   ) ::   psal   ! salinity               [psu]
-     REAL(4), DIMENSION(jpiglo,jpjglo), INTENT(in   ) ::   pdepth ! depth                  [m]
-     REAL(4), DIMENSION(jpiglo,jpjglo), INTENT(  out) ::   prd    ! in situ density 
+     REAL(8), DIMENSION(jpiglo,jpjglo), INTENT(in   ) ::   ptem   ! potential temperature  [Celcius]
+     REAL(8), DIMENSION(jpiglo,jpjglo), INTENT(in   ) ::   psal   ! salinity               [psu]
+     REAL(8), DIMENSION(jpiglo,jpjglo), INTENT(in   ) ::   pdepth ! depth                  [m]
+     REAL(8), DIMENSION(jpiglo,jpjglo), INTENT(  out) ::   prd    ! in situ density 
      !!
      INTEGER  ::   ji, jj, jk           ! dummy loop indices
      INTEGER  ::   jpkm1
-     REAL(4) ::   zt , zs , zh , zsr   ! temporary scalars
-     REAL(4) ::   zr1, zr2, zr3, zr4   !    -         -
-     REAL(4) ::   zrhop, ze, zbw, zb   !    -         -
-     REAL(4) ::   zd , zc , zaw, za    !    -         -
-     REAL(4) ::   zb1, za1, zkw, zk0   !    -         -
-     REAL(4) ::   zrau0r               !    -         -
-     REAL(4), DIMENSION(jpiglo,jpjglo) ::   zws   ! temporary workspace
+     REAL(8) ::   zt , zs , zh , zsr   ! temporary scalars
+     REAL(8) ::   zr1, zr2, zr3, zr4   !    -         -
+     REAL(8) ::   zrhop, ze, zbw, zb   !    -         -
+     REAL(8) ::   zd , zc , zaw, za    !    -         -
+     REAL(8) ::   zb1, za1, zkw, zk0   !    -         -
+     REAL(8) ::   zrau0r               !    -         -
+     REAL(8), DIMENSION(jpiglo,jpjglo) ::   zws   ! temporary workspace
      INTEGER  ::   nn_eos   = 0        !: = 0/1/2 type of eq. of state and Brunt-Vaisala frequ.
-     REAL(4) ::   rn_alpha = 2.0e-4   !: thermal expension coeff. (linear equation of state)
-     REAL(4) ::   rn_beta  = 7.7e-4   !: saline  expension coeff. (linear equation of state)
+     REAL(8) ::   rn_alpha = 2.0e-4   !: thermal expension coeff. (linear equation of state)
+     REAL(8) ::   rn_beta  = 7.7e-4   !: saline  expension coeff. (linear equation of state)
 
-     REAL(4) ::   ralpbet           !: alpha / beta ratio
+     REAL(8) ::   ralpbet           !: alpha / beta ratio
       !!----------------------------------------------------------------------
 
      zrau0r = 1.e0 / rau0
diff --git a/cdfprofile.f90 b/cdfprofile.f90
index 4050728..8000f9b 100644
--- a/cdfprofile.f90
+++ b/cdfprofile.f90
@@ -25,17 +25,31 @@ PROGRAM cdfprofile
   INTEGER :: jk
   INTEGER :: ilook, jlook
   INTEGER :: npiglo, npjglo, npk
+  ! added to write in netcdf
+  INTEGER :: kx=1, ky=1, kz            ! dims of netcdf output file
+  INTEGER :: jj, nboutput=1                ! number of values to write in cdf output
+  INTEGER :: ncout, ierr               ! for netcdf output
+  INTEGER, DIMENSION(:), ALLOCATABLE ::  ipk, id_varout
 
-  REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: v2d
+  REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE :: v2d, lon, lat
   REAL(KIND=4), DIMENSION(:), ALLOCATABLE :: depth, profile
+  ! added to write in netcdf
+  REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE ::  dumlon, dumlat
+  REAL(KIND=4), DIMENSION (1)               ::  tim ! time counter
+  REAL(KIND=4), DIMENSION (1,1)             ::  dummymean 
+  TYPE(variable), DIMENSION(:), ALLOCATABLE :: typvar  ! structure of output
+
 
   CHARACTER(LEN=256) :: cdum, cfile, cvar, cdep
+  ! added to write in netcdf
+  CHARACTER(LEN=256) :: cfileoutnc='profile.nc'
+
 
   !!  Read command line and output usage message if not compliant.
   narg= iargc()
   IF ( narg /= 4  ) THEN
      PRINT *,' Usage : cdfprofile  I J file varname '
-     PRINT *,' Output on standard output'
+     PRINT *,' Output on standard output and netcdf'
      STOP
   ENDIF
 
@@ -53,12 +67,51 @@ PROGRAM cdfprofile
 
   ! Allocate arrays
   ALLOCATE( v2d (npiglo,npjglo), depth(npk) ,profile(npk) )
+  ALLOCATE ( typvar(nboutput), ipk(nboutput), id_varout(nboutput) )
+  ALLOCATE (dumlon(1,1) , dumlat(1,1) ,lon(npiglo,npjglo), lat(npiglo,npjglo))
+
+  lon(:,:)= getvar(cfile, 'nav_lon',  1 ,npiglo,npjglo)
+  lat(:,:)= getvar(cfile, 'nav_lat',  1 ,npiglo,npjglo)
+
+  dumlon(:,:)=lon(ilook,jlook)
+  dumlat(:,:)=lat(ilook,jlook)
+
+  DO jj=1,nboutput
+     ipk(jj)=npk
+  ENDDO
+
+  ! define new variables for output 
+  typvar(1)%name=TRIM(cvar)
+  typvar(1)%units='Sverdrup'
+  typvar%missing_value=99999.
+  typvar(1)%valid_min= -1000.
+  typvar(1)%valid_max= 1000.
+  typvar%scale_factor= 1.
+  typvar%add_offset= 0.
+  typvar%savelog10= 0.
+  !typvar(1)%long_name=
+  typvar(1)%short_name=TRIM(cvar)
+  typvar%online_operation='N/A'
+  typvar%axis='TZ'
 
   depth(:) = getvar1d(cfile,cdep,npk,istatus)
+  kz=npk
+
+  ! create output fileset
+  ncout =create(cfileoutnc,'none',kx,ky,npk,cdep='depth')
+  ierr= createvar(ncout,typvar,nboutput,ipk,id_varout )
+  ierr= putheadervar(ncout, cfile,kx, &
+       ky,kz,pnavlon=dumlon,pnavlat=dumlat,pdep=depth)
+  tim=getvar1d(cfile,'time_counter',1)
+  ierr=putvar1d(ncout,tim,1,'T')
 
   DO jk=1,npk
      v2d (:,:)= getvar(cfile, cvar,  jk ,npiglo,npjglo)
      profile(jk) = v2d(ilook,jlook)
+     ! netcdf output 
+     dummymean(1,1)=profile(jk)
+     ierr = putvar(ncout, id_varout(1), dummymean, jk, kx, ky )
+
   END DO
   PRINT *, "FILE : ", TRIM(cfile)
   PRINT *, "    ", TRIM(cdep),"         ", TRIM(cvar),"(",ilook,",",jlook,")"
@@ -66,4 +119,7 @@ PROGRAM cdfprofile
      PRINT *, depth(jk), profile(jk)
   END DO
 
+  ierr = closeout(ncout)
+
+
 END PROGRAM cdfprofile

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



More information about the debian-science-commits mailing list