source: LMDZ6/branches/Amaury_dev/libf/misc/formcoord.f90 @ 5114

Last change on this file since 5114 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 986 bytes
Line 
1
2! $Header$
3
4SUBROUTINE formcoord(unit,n,x,a,rev,text)
5  IMPLICIT NONE
6  integer :: n,unit,ndec
7  logical :: rev
8  real :: x(n),a
9  character(len=4) :: text
10
11  integer :: i,id,i1,i2,in
12  real :: dx,dxmin
13
14  if(rev) then
15     id=-1
16     i1=n
17     i2=n-1
18     in=1
19     write(unit,3000) text(1:1)
20  else
21     id=1
22     i1=1
23     i2=2
24     in=n
25  endif
26
27  if (n<2) then
28     ndec=1
29     write(unit,1000) text,n,x(1)*a
30  else
31     dxmin=abs(x(2)-x(1))
32     do i=2,n-1
33        dx=abs(x(i+1)-x(i))
34        if (dx<dxmin) dxmin=dx
35     enddo
36
37     ndec=-log10(dxmin)+2
38     if(mod(n,6)==1) then
39        write(unit,1000) text,n,x(i1)*a
40        write(unit,2000) (x(i)*a,i=i2,in,id)
41     else
42        write(unit,1000) text,n
43        write(unit,2000) (x(i)*a,i=i1,in,id)
44     endif
45  endif
46
471000   format(a4,2x,i4,' LEVELS',43x,f12.2)
482000   format(6f12.2)
49  !1000  format(a4,2x,i4,' LEVELS',43x,f12.<ndec>)
50  !2000  format(6f12.<ndec>)
513000   format('FORMAT ',a1,'REV')
52
53
54end subroutine formcoord
Note: See TracBrowser for help on using the repository browser.