1 | PROGRAM testhist1 |
---|
2 | !- |
---|
3 | !$Id$ |
---|
4 | !--------------------------------------------------------------------- |
---|
5 | !- This program provide a an example of the basic usage of HIST. |
---|
6 | !- No secial features are used but just the basics. |
---|
7 | !--------------------------------------------------------------------- |
---|
8 | USE ioipsl |
---|
9 | ! |
---|
10 | IMPLICIT NONE |
---|
11 | ! |
---|
12 | INTEGER,PARAMETER :: iim=96, jjm=96, llm=12, nbreg=200 |
---|
13 | ! |
---|
14 | REAL :: champ1(iim,jjm), champ2(iim,jjm,llm), champ3(iim,jjm) |
---|
15 | REAL :: lon(iim,jjm),lat(iim,jjm), lev(llm) |
---|
16 | REAL :: lon_test(iim),lat_test(jjm) |
---|
17 | REAL :: x |
---|
18 | ! |
---|
19 | INTEGER :: i, j, l, id, it, ij, sig_id, hori_id |
---|
20 | INTEGER :: day=15, month=2, year=1997 |
---|
21 | INTEGER :: itau=0, index(nbreg), start |
---|
22 | ! |
---|
23 | REAL :: julday |
---|
24 | REAL :: deltat=60., dt_wrt, dt_op |
---|
25 | CHARACTER(LEN=20) :: histname |
---|
26 | ! |
---|
27 | REAL :: pi=3.1415 |
---|
28 | !--------------------------------------------------------------------- |
---|
29 | !- |
---|
30 | ! 1.0 Define a few variables we will need. These are the coordinates |
---|
31 | ! the file name and the date. |
---|
32 | !- |
---|
33 | DO i=1,iim |
---|
34 | DO j=1,jjm |
---|
35 | lon(i,j) = ((float(iim/2)+0.5)-float(i))*pi/float(iim/2) & |
---|
36 | & *(-1.)*180./pi |
---|
37 | lat(i,j) = 180./pi*ASIN(((float(jjm/2)+0.5)-float(j)) & |
---|
38 | & /float(jjm/2)) |
---|
39 | ENDDO |
---|
40 | ENDDO |
---|
41 | !- |
---|
42 | lon_test(:) = lon(:,1) |
---|
43 | lat_test(:) = lat(1,:) |
---|
44 | !- |
---|
45 | DO l=1,llm |
---|
46 | lev(l) = REAL(l)/llm |
---|
47 | ENDDO |
---|
48 | ! |
---|
49 | histname = 'testhist1.nc' |
---|
50 | !- |
---|
51 | ! 1.1 The chosen date is 15 Feb. 1997 as stated above. |
---|
52 | ! It has to be transformed into julian days using |
---|
53 | ! the calendar provided by IOIPSL. |
---|
54 | !- |
---|
55 | CALL ymds2ju(year, month, day, 0.,julday) |
---|
56 | dt_wrt = 3*deltat |
---|
57 | dt_op = 3*deltat |
---|
58 | !- |
---|
59 | ! 2.0 Do all the declarations for hist. That is define the file, |
---|
60 | ! the vertical coordinate and the variables in the file. |
---|
61 | !- |
---|
62 | CALL ioconf_modname('testhist1 produced this file') |
---|
63 | !- |
---|
64 | CALL histbeg (histname,iim,lon_test,jjm,lat_test, & |
---|
65 | & 1,iim,1,jjm,itau,julday,deltat,hori_id,id) |
---|
66 | !- |
---|
67 | CALL histvert (id,"sigma","Sigma levels","-",llm,lev,sig_id) |
---|
68 | !- |
---|
69 | CALL histdef (id,"champ1","Some field","m", & |
---|
70 | & iim,jjm,hori_id,1,1,1,-99,32,"inst(scatter(x))", & |
---|
71 | & dt_op,dt_wrt,var_range=(/1.,-1./)) |
---|
72 | !- |
---|
73 | CALL histdef (id,"champ2","Another field","m", & |
---|
74 | & iim,jjm,hori_id,llm,1,llm,sig_id,32,"t_max(max(x,1.0)*2)", & |
---|
75 | & deltat,dt_wrt,var_range=(/0.,90./)) |
---|
76 | !- |
---|
77 | CALL histdef (id,"champ3","A field without time","m", & |
---|
78 | & iim,jjm,hori_id,1,1,1,-99, 32,"once", & |
---|
79 | & deltat,dt_wrt) |
---|
80 | !- |
---|
81 | CALL histend (id) |
---|
82 | !- |
---|
83 | ! 2.1 The filed we are going to write are computes |
---|
84 | !- |
---|
85 | x = 10. |
---|
86 | CALL RANDOM_NUMBER(HARVEST=x) |
---|
87 | CALL RANDOM_NUMBER(champ1) |
---|
88 | champ3 = champ1 |
---|
89 | DO l=1,llm |
---|
90 | champ2(:,:,l) = champ1*l |
---|
91 | ENDDO |
---|
92 | !- |
---|
93 | ! 3.0 Start the time steping and write the data as we go along. |
---|
94 | !- |
---|
95 | start = 1 |
---|
96 | !- |
---|
97 | DO it=1,12 |
---|
98 | !--- |
---|
99 | ! 3.1 In the 2D filed we will have a set of random numbers |
---|
100 | ! which move through the map. |
---|
101 | !--- |
---|
102 | ij = 0 |
---|
103 | DO j=1,nbreg/10 |
---|
104 | DO i=1,10 |
---|
105 | ij = ij+1 |
---|
106 | index(ij) = iim*(j+20)+(i+start) |
---|
107 | ENDDO |
---|
108 | ENDDO |
---|
109 | !--- |
---|
110 | IF (start < iim-10) THEN |
---|
111 | start = start+10 |
---|
112 | ELSE |
---|
113 | start = 1 |
---|
114 | ENDIF |
---|
115 | !--- |
---|
116 | itau = itau + 1 |
---|
117 | !--- |
---|
118 | ! 3.2 Pass the data to HIST for operation and writing. |
---|
119 | !--- |
---|
120 | CALL histwrite (id,"champ1",itau,champ1,nbreg,index) |
---|
121 | CALL histwrite (id,"champ2",itau,champ2,iim*jjm*llm,index) |
---|
122 | CALL histwrite (id,"champ3",itau,champ3,iim*jjm,index) |
---|
123 | champ1 = champ1+1 |
---|
124 | champ2 = champ2+2 |
---|
125 | ENDDO |
---|
126 | !- |
---|
127 | ! 4.0 The HIST routines are ended and netCDF is closed |
---|
128 | !- |
---|
129 | ! CALL histclo |
---|
130 | ! This line should work but there seems to be a bug |
---|
131 | ! in the optional argument on SUN ! |
---|
132 | !- |
---|
133 | CALL histclo(id) |
---|
134 | !-------------------- |
---|
135 | END PROGRAM testhist1 |
---|