source: LMDZ6/trunk/libf/dyn3d_common/inigrads.f90 @ 5248

Last change on this file since 5248 was 5246, checked in by abarral, 23 hours ago

Convert fixed-form to free-form sources .F -> .{f,F}90
(WIP: some .F remain, will be handled in subsequent commits)

  • 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 1.7 KB
RevLine 
[524]1!
2! $Header$
3!
[5246]4subroutine inigrads(if,im &
5        ,x,fx,xmin,xmax,jm,y,ymin,ymax,fy,lm,z,fz &
6        ,dt,file,titlel)
[524]7
8
[5246]9  implicit none
[524]10
[5246]11  integer :: if,im,jm,lm,i,j,l
12  real :: x(im),y(jm),z(lm),fx,fy,fz,dt
13  real :: xmin,xmax,ymin,ymax
[524]14
[5246]15  character(len=*),intent(in) :: file
16  character(len=*),intent(in) :: titlel
[524]17
[5246]18  INCLUDE "gradsdef.h"
[524]19
[5246]20  ! data unit/66,32,34,36,38,40,42,44,46,48/
21  integer :: nf
22  save nf
23  data nf/0/
[524]24
[5246]25  unit(1)=66
26  unit(2)=32
27  unit(3)=34
28  unit(4)=36
29  unit(5)=38
30  unit(6)=40
31  unit(7)=42
32  unit(8)=44
33  unit(9)=46
[524]34
[5246]35  if (if.le.nf) stop 'verifier les appels a inigrads'
[524]36
[5246]37  print*,'Entree dans inigrads'
[524]38
[5246]39  nf=if
40  title(if)=titlel
41  ivar(if)=0
[524]42
[5246]43  fichier(if)=trim(file)
[524]44
[5246]45  firsttime(if)=.true.
46  dtime(if)=dt
[524]47
[5246]48  iid(if)=1
49  ifd(if)=im
50  imd(if)=im
51  do i=1,im
52     xd(i,if)=x(i)*fx
53     if(xd(i,if).lt.xmin) iid(if)=i+1
54     if(xd(i,if).le.xmax) ifd(if)=i
55  enddo
56  print*,'On stoke du point ',iid(if),'  a ',ifd(if),' en x'
[524]57
[5246]58  jid(if)=1
59  jfd(if)=jm
60  jmd(if)=jm
61  do j=1,jm
62     yd(j,if)=y(j)*fy
63     if(yd(j,if).gt.ymax) jid(if)=j+1
64     if(yd(j,if).ge.ymin) jfd(if)=j
65  enddo
66  print*,'On stoke du point ',jid(if),'  a ',jfd(if),' en y'
[524]67
[5246]68  print*,'Open de dat'
69  print*,'file=',file
70  print*,'fichier(if)=',fichier(if)
[524]71
[5246]72  print*,4*(ifd(if)-iid(if))*(jfd(if)-jid(if))
73  print*,trim(file)//'.dat'
[524]74
[5246]75  OPEN (unit(if)+1,FILE=trim(file)//'.dat' &
76        ,FORM='unformatted', &
77        ACCESS='direct' &
78        ,RECL=4*(ifd(if)-iid(if)+1)*(jfd(if)-jid(if)+1))
[524]79
[5246]80  print*,'Open de dat ok'
[524]81
[5246]82  lmd(if)=lm
83  do l=1,lm
84     zd(l,if)=z(l)*fz
85  enddo
[524]86
[5246]87  irec(if)=0
[524]88
[5246]89  print*,if,imd(if),jmd(if),lmd(if)
90  print*,'if,imd(if),jmd(if),lmd(if)'
[524]91
[5246]92  return
93end subroutine inigrads
Note: See TracBrowser for help on using the repository browser.