~ubuntu-branches/ubuntu/vivid/cdftools/vivid

« back to all changes in this revision

Viewing changes to cdfdifmask.f90

  • Committer: Package Import Robot
  • Author(s): Alastair McKinstry
  • Date: 2013-11-14 19:04:43 UTC
  • Revision ID: package-import@ubuntu.com-20131114190443-ymhovvnzvr5kd02l
Tags: upstream-3.0
ImportĀ upstreamĀ versionĀ 3.0

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
PROGRAM cdfdifmask
 
2
  !!======================================================================
 
3
  !!                     ***  PROGRAM  cdfdifmask  ***
 
4
  !!=====================================================================
 
5
  !!  ** Purpose : Build the difference between 2 mask files
 
6
  !!
 
7
  !!
 
8
  !! History : 2.1  : ??????   : ???          : Original code
 
9
  !!           3.0  : 12/2010  : J.M. Molines : Doctor norm + Lic.
 
10
  !!----------------------------------------------------------------------
 
11
  USE cdfio
 
12
  USE modcdfnames
 
13
  !!----------------------------------------------------------------------
 
14
  !! CDFTOOLS_3.0 , MEOM 2011
 
15
  !! $Id$
 
16
  !! Copyright (c) 2010, J.-M. Molines
 
17
  !! Software governed by the CeCILL licence (Licence/CDFTOOLSCeCILL.txt)
 
18
  !!----------------------------------------------------------------------
 
19
  IMPLICIT NONE
 
20
 
 
21
  INTEGER(KIND=4)                            :: jk, jvar               ! dummy loop index
 
22
  INTEGER(KIND=4)                            :: ierr                   ! working integer
 
23
  INTEGER(KIND=4)                            :: narg, iargc            ! browsing command line
 
24
  INTEGER(KIND=4)                            :: npiglo, npjglo, npk    ! size of the domain
 
25
  INTEGER(KIND=4)                            :: ncout                  ! ncid of output file
 
26
  INTEGER(KIND=4), DIMENSION(4)              :: ipk                    ! outptut variables : levels,
 
27
  INTEGER(KIND=4), DIMENSION(4)              :: id_varout              ! ncdf varid's
 
28
 
 
29
  REAL(KIND=4), DIMENSION (:,:), ALLOCATABLE :: zmask, zmask2          ! 2D mask at current level
 
30
  REAL(KIND=4), DIMENSION(:),    ALLOCATABLE :: tim                    ! dummy time variable
 
31
 
 
32
  CHARACTER(LEN=256)                         :: cf_out='mask_diff.nc'  ! Output file name
 
33
  CHARACTER(LEN=256)                         :: cf_msk1, cf_msk2       ! name of input files
 
34
  CHARACTER(LEN=256)                         :: cv_in                  ! variable name
 
35
 
 
36
  TYPE(variable), DIMENSION(4)               :: stypvar                ! data structure
 
37
 
 
38
  LOGICAL                                    :: lchk                   ! checking file existence
 
39
  !!----------------------------------------------------------------------
 
40
  CALL ReadCdfNames()
 
41
 
 
42
  narg = iargc()
 
43
  IF ( narg == 0 ) THEN
 
44
     PRINT *,' usage : cdfdifmask  mask1 mask2'
 
45
     PRINT *,'     PURPOSE :'
 
46
     PRINT *,'       Compute the difference between 2 mask files.' 
 
47
     PRINT *,'      '
 
48
     PRINT *,'     ARGUMENTS :'
 
49
     PRINT *,'       mask1, mask2 : model files to be compared.' 
 
50
     PRINT *,'      '
 
51
     PRINT *,'     REQUIRED FILES :'
 
52
     PRINT *,'        none'
 
53
     PRINT *,'      '
 
54
     PRINT *,'     OUTPUT : '
 
55
     PRINT *,'       netcdf file : ', TRIM(cf_out) 
 
56
     PRINT *,'       variables : tmask, umask, vmask, fmask'
 
57
     STOP
 
58
  ENDIF
 
59
  CALL getarg (1, cf_msk1)
 
60
  CALL getarg (2, cf_msk2)
 
61
 
 
62
  lchk =           chkfile ( cf_msk1 )
 
63
  lchk = lchk .OR. chkfile ( cf_msk2 )
 
64
  IF ( lchk ) STOP ! missing file
 
65
 
 
66
  npiglo = getdim (cf_msk1, cn_x)
 
67
  npjglo = getdim (cf_msk1, cn_y)
 
68
  npk    = getdim (cf_msk1, 'z' )  ! mask file have a z depth dim instead of depth ...
 
69
 
 
70
  ipk(:) = npk
 
71
  stypvar(:)%cunits            = '1/0'
 
72
  stypvar(:)%rmissing_value    = 9999.
 
73
  stypvar(:)%valid_min         = 0.
 
74
  stypvar(:)%valid_max         = 1.
 
75
  stypvar(:)%conline_operation = 'N/A'
 
76
  stypvar(:)%caxis             = 'TZYX'
 
77
  stypvar(:)%cprecision        = 'by'
 
78
 
 
79
  stypvar(1)%cname='tmask' ;  stypvar(1)%clong_name='tmask' ;  stypvar(1)%cshort_name='tmask'
 
80
  stypvar(2)%cname='umask' ;  stypvar(2)%clong_name='umask' ;  stypvar(2)%cshort_name='umask'
 
81
  stypvar(3)%cname='vmask' ;  stypvar(3)%clong_name='vmask' ;  stypvar(3)%cshort_name='vmask'
 
82
  stypvar(4)%cname='fmask' ;  stypvar(4)%clong_name='fmask' ;  stypvar(4)%cshort_name='fmask'
 
83
 
 
84
  ncout = create      (cf_out, cf_msk1, npiglo, npjglo, npk,      cdep='z', cdepvar='nav_lev')
 
85
  ierr  = createvar   (ncout,  stypvar, 4,      ipk,    id_varout                            )
 
86
  ierr  = putheadervar(ncout,  cf_msk1, npiglo, npjglo, npk,      cdep='nav_lev'             )
 
87
 
 
88
  ALLOCATE (zmask(npiglo,npjglo), zmask2(npiglo,npjglo))
 
89
 
 
90
  DO jvar=1,4
 
91
     cv_in = stypvar(jvar)%cname
 
92
     PRINT *, ' making difference for ', TRIM(cv_in)
 
93
     DO jk=1, npk
 
94
        PRINT * ,'jk = ', jk
 
95
        zmask(:,:)  = getvar(cf_msk1, cv_in, jk, npiglo, npjglo)
 
96
        zmask2(:,:) = getvar(cf_msk2, cv_in, jk, npiglo, npjglo)
 
97
        zmask(:,:)  = zmask2(:,:) - zmask(:,:)
 
98
        ierr        = putvar(ncout, id_varout(jvar), zmask, jk, npiglo, npjglo)
 
99
     END DO  ! loop to next level
 
100
  END DO
 
101
 
 
102
  tim(:) = 0.
 
103
  ierr   = putvar1d(ncout, tim, 1, 'T')
 
104
  ierr   = closeout(ncout)
 
105
 
 
106
END PROGRAM cdfdifmask