1 | ! $Header$ |
---|
2 | |
---|
3 | subroutine wrgrads(if, nl, field, name, titlevar) |
---|
4 | IMPLICIT NONE |
---|
5 | |
---|
6 | ! Declarations |
---|
7 | ! if indice du fichier |
---|
8 | ! nl nombre de couches |
---|
9 | ! field champ |
---|
10 | ! name petit nom |
---|
11 | ! titlevar Titre |
---|
12 | |
---|
13 | include "gradsdef.h" |
---|
14 | |
---|
15 | ! arguments |
---|
16 | integer :: if, nl |
---|
17 | real :: field(imx * jmx * lmx) |
---|
18 | |
---|
19 | integer, parameter :: wp = selected_real_kind(p = 6, r = 36) |
---|
20 | real(wp) field4(imx * jmx * lmx) |
---|
21 | |
---|
22 | character(len = 10) :: name, file |
---|
23 | character(len = 10) :: titlevar |
---|
24 | |
---|
25 | ! local |
---|
26 | |
---|
27 | integer :: im, jm, lm, i, j, l, iv, iii, iji, iif, ijf |
---|
28 | |
---|
29 | logical :: writectl |
---|
30 | |
---|
31 | writectl = .false. |
---|
32 | |
---|
33 | ! print*,if,iid(if),jid(if),ifd(if),jfd(if) |
---|
34 | iii = iid(if) |
---|
35 | iji = jid(if) |
---|
36 | iif = ifd(if) |
---|
37 | ijf = jfd(if) |
---|
38 | im = iif - iii + 1 |
---|
39 | jm = ijf - iji + 1 |
---|
40 | lm = lmd(if) |
---|
41 | |
---|
42 | ! print*,'im,jm,lm,name,firsttime(if)' |
---|
43 | ! print*,im,jm,lm,name,firsttime(if) |
---|
44 | |
---|
45 | if(firsttime(if)) then |
---|
46 | if(name==var(1, if)) then |
---|
47 | firsttime(if) = .false. |
---|
48 | ivar(if) = 1 |
---|
49 | print*, 'fin de l initialiation de l ecriture du fichier' |
---|
50 | print*, file |
---|
51 | print*, 'fichier no: ', if |
---|
52 | print*, 'unit ', unit(if) |
---|
53 | print*, 'nvar ', nvar(if) |
---|
54 | print*, 'vars ', (var(iv, if), iv = 1, nvar(if)) |
---|
55 | else |
---|
56 | ivar(if) = ivar(if) + 1 |
---|
57 | nvar(if) = ivar(if) |
---|
58 | var(ivar(if), if) = name |
---|
59 | tvar(ivar(if), if) = trim(titlevar) |
---|
60 | nld(ivar(if), if) = nl |
---|
61 | ! print*,'initialisation ecriture de ',var(ivar(if),if) |
---|
62 | ! print*,'if ivar(if) nld ',if,ivar(if),nld(ivar(if),if) |
---|
63 | endif |
---|
64 | writectl = .true. |
---|
65 | itime(if) = 1 |
---|
66 | else |
---|
67 | ivar(if) = mod(ivar(if), nvar(if)) + 1 |
---|
68 | if (ivar(if)==nvar(if)) then |
---|
69 | writectl = .true. |
---|
70 | itime(if) = itime(if) + 1 |
---|
71 | endif |
---|
72 | |
---|
73 | if(var(ivar(if), if)/=name) then |
---|
74 | print*, 'Il faut stoker la meme succession de champs a chaque' |
---|
75 | print*, 'pas de temps' |
---|
76 | print*, 'fichier no: ', if |
---|
77 | print*, 'unit ', unit(if) |
---|
78 | print*, 'nvar ', nvar(if) |
---|
79 | print*, 'vars ', (var(iv, if), iv = 1, nvar(if)) |
---|
80 | CALL abort_gcm("wrgrads", "problem", 1) |
---|
81 | endif |
---|
82 | endif |
---|
83 | |
---|
84 | ! print*,'ivar(if),nvar(if),var(ivar(if),if),writectl' |
---|
85 | ! print*,ivar(if),nvar(if),var(ivar(if),if),writectl |
---|
86 | field4(1:imd(if) * jmd(if) * nl) = field(1:imd(if) * jmd(if) * nl) |
---|
87 | do l = 1, nl |
---|
88 | irec(if) = irec(if) + 1 |
---|
89 | ! print*,'Ecrit rec=',irec(if),iii,iif,iji,ijf, |
---|
90 | ! s (l-1)*imd(if)*jmd(if)+(iji-1)*imd(if)+iii |
---|
91 | ! s ,(l-1)*imd(if)*jmd(if)+(ijf-1)*imd(if)+iif |
---|
92 | write(unit(if) + 1, rec = irec(if)) & |
---|
93 | ((field4((l - 1) * imd(if) * jmd(if) + (j - 1) * imd(if) + i) & |
---|
94 | , i = iii, iif), j = iji, ijf) |
---|
95 | enddo |
---|
96 | if (writectl) then |
---|
97 | |
---|
98 | file = fichier(if) |
---|
99 | ! WARNING! on reecrase le fichier .ctl a chaque ecriture |
---|
100 | open(unit(if), file = trim(file) // '.ctl' & |
---|
101 | , form = 'formatted', status = 'unknown') |
---|
102 | write(unit(if), '(a5,1x,a40)') & |
---|
103 | 'DSET ', '^' // trim(file) // '.dat' |
---|
104 | |
---|
105 | write(unit(if), '(a12)') 'UNDEF 1.0E30' |
---|
106 | write(unit(if), '(a5,1x,a40)') 'TITLE ', title(if) |
---|
107 | CALL formcoord(unit(if), im, xd(iii, if), 1., .false., 'XDEF') |
---|
108 | CALL formcoord(unit(if), jm, yd(iji, if), 1., .true., 'YDEF') |
---|
109 | CALL formcoord(unit(if), lm, zd(1, if), 1., .false., 'ZDEF') |
---|
110 | write(unit(if), '(a4,i10,a30)') & |
---|
111 | 'TDEF ', itime(if), ' LINEAR 02JAN1987 1MO ' |
---|
112 | write(unit(if), '(a4,2x,i5)') 'VARS', nvar(if) |
---|
113 | do iv = 1, nvar(if) |
---|
114 | ! print*,'if,var(iv,if),nld(iv,if),nld(iv,if)-1/nld(iv,if)' |
---|
115 | ! print*,if,var(iv,if),nld(iv,if),nld(iv,if)-1/nld(iv,if) |
---|
116 | write(unit(if), 1000) var(iv, if), nld(iv, if) - 1 / nld(iv, if) & |
---|
117 | , 99, tvar(iv, if) |
---|
118 | enddo |
---|
119 | write(unit(if), '(a7)') 'ENDVARS' |
---|
120 | ! |
---|
121 | 1000 format(a5, 3x, i4, i3, 1x, a39) |
---|
122 | |
---|
123 | close(unit(if)) |
---|
124 | |
---|
125 | endif ! writectl |
---|
126 | |
---|
127 | |
---|
128 | |
---|
129 | END SUBROUTINE wrgrads |
---|
130 | |
---|