source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/wrgrads.f90 @ 5113

Last change on this file since 5113 was 5113, checked in by abarral, 2 months ago

Rename modules in misc from *_mod > lmdz_*
Put cbrt.f90, ch*.f90, pch*.f90 in new lmdz_libmath_pch.f90

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 3.5 KB
Line 
1! $Header$
2
3SUBROUTINE 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  character(len = 10) :: name, file
19  character(len = 10) :: titlevar
20
21  !   local
22
23  integer :: im, jm, lm, i, j, l, iv, iii, iji, iif, ijf
24
25  logical :: writectl
26
27  writectl = .FALSE.
28
29  PRINT*, if, iid(if), jid(if), ifd(if), jfd(if)
30  iii = iid(if)
31  iji = jid(if)
32  iif = ifd(if)
33  ijf = jfd(if)
34  im = iif - iii + 1
35  jm = ijf - iji + 1
36  lm = lmd(if)
37
38  PRINT*, 'im,jm,lm,name,firsttime(if)'
39  PRINT*, im, jm, lm, name, firsttime(if)
40
41  if(firsttime(if)) then
42    if(name==var(1, if)) then
43      firsttime(if) = .FALSE.
44      ivar(if) = 1
45      PRINT*, 'fin de l initialiation de l ecriture du fichier'
46      PRINT*, file
47      PRINT*, 'fichier no: ', if
48      PRINT*, 'unit ', unit(if)
49      PRINT*, 'nvar  ', nvar(if)
50      PRINT*, 'vars ', (var(iv, if), iv = 1, nvar(if))
51    else
52      ivar(if) = ivar(if) + 1
53      nvar(if) = ivar(if)
54      var(ivar(if), if) = name
55      tvar(ivar(if), if) = trim(titlevar)
56      nld(ivar(if), if) = nl
57      PRINT*, 'initialisation ecriture de ', var(ivar(if), if)
58      PRINT*, 'if ivar(if) nld ', if, ivar(if), nld(ivar(if), if)
59    endif
60    writectl = .TRUE.
61    itime(if) = 1
62  else
63    ivar(if) = mod(ivar(if), nvar(if)) + 1
64    if (ivar(if)==nvar(if)) then
65      writectl = .TRUE.
66      itime(if) = itime(if) + 1
67    endif
68
69    if(var(ivar(if), if)/=name) then
70      PRINT*, 'Il faut stoker la meme succession de champs a chaque'
71      PRINT*, 'pas de temps'
72      PRINT*, 'fichier no: ', if
73      PRINT*, 'unit ', unit(if)
74      PRINT*, 'nvar  ', nvar(if)
75      PRINT*, 'vars ', (var(iv, if), iv = 1, nvar(if))
76      CALL abort_gcm("wrgrads", "problem", 1)
77    endif
78  endif
79
80  PRINT*, 'ivar(if),nvar(if),var(ivar(if),if),writectl'
81  PRINT*, ivar(if), nvar(if), var(ivar(if), if), writectl
82  do l = 1, nl
83    irec(if) = irec(if) + 1
84    ! PRINT*,'Ecrit rec=',irec(if),iii,iif,iji,ijf,
85    !    s (l-1)*imd(if)*jmd(if)+(iji-1)*imd(if)+iii
86    !    s ,(l-1)*imd(if)*jmd(if)+(ijf-1)*imd(if)+iif
87    write(unit(if) + 1, rec = irec(if)) &
88            ((field((l - 1) * imd(if) * jmd(if) + (j - 1) * imd(if) + i) &
89                    , i = iii, iif), j = iji, ijf)
90  enddo
91  if (writectl) then
92
93    file = fichier(if)
94    !   WARNING! on reecrase le fichier .ctl a chaque ecriture
95    open(unit(if), file = trim(file) // '.ctl' &
96            , form = 'formatted', status = 'unknown')
97    write(unit(if), '(a5,1x,a40)') &
98            'DSET ', '^' // trim(file) // '.dat'
99
100    write(unit(if), '(a12)') 'UNDEF 1.0E30'
101    write(unit(if), '(a5,1x,a40)') 'TITLE ', title(if)
102    CALL formcoord(unit(if), im, xd(iii, if), 1., .FALSE., 'XDEF')
103    CALL formcoord(unit(if), jm, yd(iji, if), 1., .TRUE., 'YDEF')
104    CALL formcoord(unit(if), lm, zd(1, if), 1., .FALSE., 'ZDEF')
105    write(unit(if), '(a4,i10,a30)') &
106            'TDEF ', itime(if), ' LINEAR 02JAN1987 1MO '
107    write(unit(if), '(a4,2x,i5)') 'VARS', nvar(if)
108    do iv = 1, nvar(if)
109      ! PRINT*,'if,var(iv,if),nld(iv,if),nld(iv,if)-1/nld(iv,if)'
110      ! PRINT*,if,var(iv,if),nld(iv,if),nld(iv,if)-1/nld(iv,if)
111      write(unit(if), 1000) var(iv, if), nld(iv, if) - 1 / nld(iv, if) &
112              , 99, tvar(iv, if)
113    enddo
114    write(unit(if), '(a7)') 'ENDVARS'
115    !
116    1000   format(a5, 3x, i4, i3, 1x, a39)
117
118    close(unit(if))
119
120  endif ! writectl
121
122
123
124END SUBROUTINE wrgrads
125
Note: See TracBrowser for help on using the repository browser.