/[MITgcm]/MITgcm_contrib/ocean_inversion_project/region_mask/read_mask.f
ViewVC logotype

Contents of /MITgcm_contrib/ocean_inversion_project/region_mask/read_mask.f

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.1 - (show annotations) (download)
Tue Sep 23 04:34:24 2003 UTC (20 years, 7 months ago) by dimitri
Branch: MAIN
CVS Tags: HEAD
o Mods and bug fixes to pkg/cal and pkg/exf needed for computation
  of tracer Green's fucntions for ocean inversion project.

1 !
2 ! $Id: read_mask.f v 1. 2003/07/24 fletcher Exp $
3 !
4 !_ ---------------------------------------------------------------------
5 !_ $Log: read_mask.f $
6 !_ Revision 1. 24/07/2003 Sara Fletcher
7 !_ Started Coding
8 !_
9 !***********************************************************************
10 !
11 ! NAME: READ_MASK.F
12 !
13 ! DESCRIPTION: This program demonstrates how to read a 3-D netCDF region mask
14 ! file.
15 !
16 ! COMPILING:
17 !
18 ! f77 -o read_mask.x read_mask.f libnetcdf.a
19 !
20 ! VARIABLES:
21 ! imt, jmt: indices of the region mask in the input file
22 ! filename = Name of Net CDF file
23 ! ndyetrac = Number of dye regions (30 or 16)
24 ! region_index = 2-D array containing a region index which assigns each
25 ! ocean region to a different index value
26 ! region_mask = 3-D (i,j,ndyetrac) array. Gridboxes included in each
27 ! model region are set to 1 and those not included are set
28 ! to 0.
29 !
30 !***********************************************************************
31
32 PROGRAM read_mask
33
34 ! No implicit declarations
35 IMPLICIT NONE
36 INCLUDE 'netcdf.inc'
37
38 ! define variables
39 CHARACTER*256 string256,filename
40 INTEGER ndyetrac,imt,jmt, i,j,n
41 PARAMETER (ndyetrac=30) !Equals 30 or 16
42 PARAMETER (imt= 96, jmt=40)
43 REAL*4 lon(imt)
44 REAL*4 lat(jmt)
45 CHARACTER*30, reg_name(ndyetrac)
46 CHARACTER*1, string1
47 CHARACTER*2, string2
48 INTEGER region_index(imt,jmt)
49 INTEGER mask_temp(imt,jmt), region_mask(imt,jmt,ndyetrac)
50
51
52 INTEGER*4 NC_ID, STATUS
53 INTEGER*4 idlon, idlat, idtrac, idindex, idmask(ndyetrac)
54
55
56
57 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
58 ! Generate region names
59 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
60
61 do i=1,ndyetrac
62 if (i.lt.10) then
63 write(string1,'(I1.1)') i
64 reg_name(i)='region'//string1
65 else
66 write(string2,'(I2.2)') i
67 reg_name(i)='region'//string2
68 endif
69 enddo
70
71
72 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
73 ! NetCDF filename
74 ! Either 30reg_regionmask.cdf or 16reg_regionmask.cdf
75 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
76
77 if (ndyetrac.eq.30) then
78 filename='30reg_regionmask.cdf'
79 else if (ndyetrac.eq.16) then
80 filename='16reg_regionmask.cdf'
81 endif
82
83 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
84 ! Open the NetCDF file
85 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
86 STATUS=NF_OPEN(filename,NF_NOWRITE,NC_ID)
87 IF (STATUS.NE.NF_NOERR) CALL HANDLE_ERRORS(STATUS)
88
89 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
90 ! Get the netCDF variable dimensions
91 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
92
93 STATUS=NF_INQ_DIMID(NC_ID,'tlon',idlon)
94 IF (STATUS.NE.NF_NOERR) CALL HANDLE_ERRORS(STATUS)
95
96 STATUS=NF_INQ_DIMID(NC_ID,'tlat',idlat)
97 IF (STATUS.NE.NF_NOERR) CALL HANDLE_ERRORS(STATUS)
98
99 STATUS=NF_INQ_VARID(NC_ID,'reg_indx',idindex)
100 IF (STATUS.NE.NF_NOERR) CALL HANDLE_ERRORS(STATUS)
101
102 do i=1,ndyetrac
103 STATUS=NF_INQ_VARID(NC_ID,reg_name(i),idmask(i))
104 IF (STATUS.NE.NF_NOERR) CALL HANDLE_ERRORS(STATUS)
105 enddo
106
107 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
108 ! READ the netCDF DATA
109 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
110
111 STATUS=NF_GET_VAR_REAL(NC_ID,idlon, lon)
112 IF (STATUS.NE.NF_NOERR) CALL HANDLE_ERRORS(STATUS)
113
114 STATUS=NF_GET_VAR_REAL(NC_ID,idlat,lat)
115 IF (STATUS.NE.NF_NOERR) CALL HANDLE_ERRORS(STATUS)
116
117 STATUS=NF_GET_VAR_INT(NC_ID,idindex,region_index)
118 IF (STATUS.NE.NF_NOERR) CALL HANDLE_ERRORS(STATUS)
119
120 do n=1,ndyetrac
121 STATUS=NF_GET_VAR_INT(NC_ID,idmask(n),mask_temp)
122 IF (STATUS.NE.NF_NOERR) CALL HANDLE_ERRORS(STATUS)
123 do i=1,imt
124 do j=1,jmt
125 region_mask(i,j,n)=0
126 if(mask_temp(i,j).eq.1)region_mask(i,j,n)=1
127 write(10,*),i,j,lon(i),lat(j),n,region_mask(i,j,n)
128 enddo
129 enddo
130 enddo
131
132
133 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
134 ! Close the NetCDF file
135 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
136 STATUS=NF_CLOSE(NC_ID)
137 IF (STATUS.NE.NF_NOERR) CALL HANDLE_ERRORS(STATUS)
138
139 END
140
141
142 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
143 ! Error handling subroutine
144 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
145 SUBROUTINE HANDLE_ERRORS(STATUS)
146
147 INCLUDE 'netcdf.inc'
148 INTEGER*4 STATUS
149
150 IF (STATUS .NE. nf_noerr) THEN
151 PRINT *, nf_strerror(STATUS)
152 STOP 'stopped'
153 ENDIF
154
155 END
156
157 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
158

  ViewVC Help
Powered by ViewVC 1.1.22