New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
testhist1.f90 in branches/DEV_r1879_FCM/NEMOGCM/EXTERNAL/IOIPSL/example – NEMO

source: branches/DEV_r1879_FCM/NEMOGCM/EXTERNAL/IOIPSL/example/testhist1.f90 @ 1993

Last change on this file since 1993 was 1993, checked in by smasson, 14 years ago

merging IOIPSL/v2_2_1 into the EXTERNAL deposit

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