source: LMDZ6/trunk/libf/dyn3dmem/wrgrads.f90 @ 5300

Last change on this file since 5300 was 5297, checked in by abarral, 2 days ago

Turn gradsdef.h coefils.h into a module

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