source: IOIPSL/trunk/example/testhist2.f90 @ 363

Last change on this file since 363 was 363, checked in by bellier, 16 years ago

Updating for more compliance with CF Metadata Convention.

  • Property svn:keywords set to Id
File size: 3.7 KB
Line 
1PROGRAM testhist2
2!-
3!$Id$
4!---------------------------------------------------------------------
5!- This program provide a an example of the basic usage of HIST.
6!- Here the test the time sampling and averaging. Thus a long
7!- time-series is produced and sampled in different ways.
8!---------------------------------------------------------------------
9  USE ioipsl
10!
11  IMPLICIT NONE
12!
13  INTEGER,PARAMETER :: iim=12,jjm=10,llm=2
14!
15  REAL :: champ1(iim,jjm), champ(iim,jjm), champ2(iim,jjm)
16  REAL :: lon(iim,jjm),lat(iim,jjm), lev(llm)
17  REAL :: x
18!
19  INTEGER :: i, j, l, id, id2, sig_id, hori_id, it
20  INTEGER :: day=1, month=1, year=1997
21  INTEGER :: itau=0, start, index(1)
22!
23  REAL :: julday, un_mois, un_an
24  REAL :: deltat=86400, dt_wrt, dt_op, dt_wrt2, dt_op2
25  CHARACTER(LEN=20) :: histname
26!
27  REAL :: pi=3.1415
28!---------------------------------------------------------------------
29!-
30! 0.0 Choose a 360 days calendar
31!-
32  CALL ioconf_calendar('gregorian')
33!-
34! 1.0 Define a few variables we will need.
35!     These are the coordinates the file name and the date.
36!-
37  DO i=1,iim
38    DO j=1,jjm
39      lon(i,j) = ((float(iim/2)+0.5)-float(i))*pi/float(iim/2) &
40 &              *(-1.)*180./pi
41      lat(i,j) = 180./pi * ASIN(((float(jjm/2)+0.5)-float(j)) &
42 &              /float(jjm/2))
43    ENDDO
44  ENDDO
45!-
46  DO l=1,llm
47    lev(l) = float(l)/llm
48  ENDDO
49!-
50  histname = 'testhist2.nc'
51!-
52! 1.1 The chosen date is 15 Feb. 1997 as stated above.
53!     It has to be transformed into julian days using
54!     the calendar provided by IOIPSL.
55!-
56  CALL ymds2ju(year, month, day, 0.,julday)
57  CALL ioget_calendar(un_an)
58  un_mois = un_an/12.
59  dt_wrt = un_mois*deltat
60  dt_op = deltat
61  dt_wrt2 = -1.
62  dt_op2 = deltat
63!-
64! 2.0 Do all the declarations for hist. That is define the file,
65!     the vertical coordinate and the variables in the file.
66!     Monthly means are written to test this feature
67!-
68  CALL ioconf_modname ('testhist2 produced this file')
69!-
70  CALL histbeg (histname,iim,lon,jjm,lat, &
71 &       1,iim,1,jjm,itau,julday,deltat,hori_id,id)
72!-
73  CALL histvert (id,"sigma","Sigma levels"," ",llm,lev,sig_id,pdirect="up")
74!-
75  CALL histdef (id,"champ1","Some field","m", &
76 &       iim,jjm,hori_id,1,1,1,-99,32,"t_sum",dt_op,dt_wrt)
77!-
78  CALL histdef (id,"champ2","summed field","m", &
79 &       iim,jjm,hori_id,1,1,1,-99,32,"t_sum",dt_op,dt_wrt)
80!-
81  CALL histend (id)
82!-
83! Open a second file which will do monthly means using the -1 notation.
84!-
85  histname = 'testhist2_bis.nc'
86  CALL histbeg (histname,iim,lon,jjm,lat, &
87 &       1,iim,1,jjm,itau,julday,deltat,hori_id,id2)
88!-
89  CALL histvert (id2,"sigma","Sigma levels"," ",llm,lev,sig_id,pdirect="up")
90!-
91  CALL histdef (id2,"champ1","Some field","m", &
92 &       iim,jjm,hori_id,1,1,1,-99,32,"t_sum",dt_op2,dt_wrt2)
93!-
94  CALL histdef (id2,"champ2","summed field","m", &
95 &       iim,jjm,hori_id,1,1,1,-99,32,"t_sum",dt_op2,dt_wrt2)
96!-
97  CALL histend (id2)
98!-
99! 2.1 The filed we are going to write are computes
100!-
101  CALL RANDOM_NUMBER(HARVEST=x)
102  CALL RANDOM_NUMBER(champ)
103  champ = champ*2*pi
104  champ1 = sin(champ)
105  champ2(:,:) = 1.
106!-
107! 3.0 Start the time steping and write the data as we go along.
108!-
109  start = 1
110!-
111  DO it=1,730
112!---
113!   3.1 In the 2D filed we will have a set of random numbers
114!       which move through the map.
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,iim*jjm,index)
121    CALL histwrite (id2,"champ1",itau,champ1,iim*jjm,index)
122    CALL histwrite (id, "champ2",itau,champ2,iim*jjm,index)
123    CALL histwrite (id2,"champ2",itau,champ2,iim*jjm,index)
124!---
125    champ1 = sin((it+1)*champ)
126  ENDDO
127!-
128! 4.0 The HIST routines are ended and netCDF is closed
129!-
130  CALL histclo ()
131!--------------------
132END PROGRAM testhist2
Note: See TracBrowser for help on using the repository browser.