source: LMDZ6/trunk/libf/dyn3d_common/dump2d.f90 @ 5246

Last change on this file since 5246 was 5246, checked in by abarral, 25 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: 743 bytes
RevLine 
[524]1!
[1279]2! $Id: dump2d.f90 5246 2024-10-21 12:58:45Z abarral $
[524]3!
[5246]4SUBROUTINE dump2d(im,jm,z,nom_z)
5  IMPLICIT NONE
6  INTEGER :: im,jm
7  REAL :: z(im,jm)
8  CHARACTER (len=*) :: nom_z
[524]9
[5246]10  INTEGER :: i,j,imin,illm,jmin,jllm
11  REAL :: zmin,zllm
[524]12
[5246]13  WRITE(*,*) "dump2d: ",trim(nom_z)
[524]14
[5246]15  zmin=z(1,1)
16  zllm=z(1,1)
17  imin=1
18  illm=1
19  jmin=1
20  jllm=1
[524]21
[5246]22  DO j=1,jm
23     DO i=1,im
24        IF(z(i,j).GT.zllm) THEN
25           illm=i
26           jllm=j
27           zllm=z(i,j)
28        ENDIF
29        IF(z(i,j).LT.zmin) THEN
30           imin=i
31           jmin=j
32           zmin=z(i,j)
33        ENDIF
34     ENDDO
35  ENDDO
[524]36
[5246]37  PRINT*,'MIN: ',zmin
38  PRINT*,'MAX: ',zllm
[524]39
[5246]40  IF(zllm.GT.zmin) THEN
41   DO j=1,jm
42    WRITE(*,'(600i1)') (NINT(10.*(z(i,j)-zmin)/(zllm-zmin)),i=1,im)
43   ENDDO
44  ENDIF
45  RETURN
46END SUBROUTINE dump2d
Note: See TracBrowser for help on using the repository browser.