Ignore:
Timestamp:
Mar 5, 2014, 2:19:12 PM (11 years ago)
Author:
lguez
Message:

Converted to free source form files in libf/phylmd which were still in
fixed source form. The conversion was done using the polish mode of
the NAG Fortran Compiler.

In addition to converting to free source form, the processing of the
files also:

-- indented the code (including comments);

-- set Fortran keywords to uppercase, and set all other identifiers
to lower case;

-- added qualifiers to end statements (for example "end subroutine
conflx", instead of "end");

-- changed the terminating statements of all DO loops so that each
loop ends with an ENDDO statement (instead of a labeled continue).

-- replaced #include by include.

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/ecrireg.F90

    r1988 r1992  
    1 !
     1
    22! $Header$
    3 !
    4       SUBROUTINE ecriregs(unit,pz)
    5       use dimphy
    6       IMPLICIT none
    7 c-----------------------------------------------------------------------
    8 #include "dimensions.h"
    9 cccc#include "dimphy.h"
    10 #include "paramet.h"
    11 #include "comgeom.h"
    12 #include "comvert.h"
    13 #include "regdim.h"
    14 c
    15 c   arguments:
    16 c   ----------
    17       INTEGER unit
    18       REAL pz(klon)
    19 c
    20 c   local:
    21 c   ------
    22       INTEGER i,j, ig
    23       REAL zz(iim,jjm+1)
    24       INTEGER nleng
    25       PARAMETER (nleng=(i2_fin-i2_deb+1+i1_fin-i1_deb+1)
    26      .                *(j_fin-j_deb+1))
    27       REAL zzz(nleng)
    28 c
    29 c-----------------------------------------------------------------------
    30 c   passage a la grille dynamique:
    31 c   ------------------------------
    32          DO i=1,iim
    33             zz(i,1)=pz(1)
    34             zz(i,jjm+1)=pz(klon)
    35          ENDDO
    36 c
    37 c   traitement des point normaux
    38          DO j=2,jjm
    39             ig=2+(j-2)*iim
    40             CALL SCOPY(iim,pz(ig),1,zz(1,j),1)
    41          ENDDO
    42 c-----------------------------------------------------------------------
    43       ig = 0
    44       DO j = j_deb, j_fin
    45          DO i=i1_deb,i1_fin
    46             ig = ig + 1
    47             zzz(ig) = zz(i,j)
    48          ENDDO
    49          DO i=i2_deb,i2_fin
    50             ig = ig + 1
    51             zzz(ig) = zz(i,j)
    52          ENDDO
    53       ENDDO
     3
     4SUBROUTINE ecriregs(unit, pz)
     5  USE dimphy
     6  IMPLICIT NONE
     7  ! -----------------------------------------------------------------------
     8  include "dimensions.h"
     9  ! ccc#include "dimphy.h"
     10  include "paramet.h"
     11  include "comgeom.h"
     12  include "comvert.h"
     13  include "regdim.h"
     14
     15  ! arguments:
     16  ! ----------
     17  INTEGER unit
     18  REAL pz(klon)
     19
     20  ! local:
     21  ! ------
     22  INTEGER i, j, ig
     23  REAL zz(iim, jjm+1)
     24  INTEGER nleng
     25  PARAMETER (nleng=(i2_fin-i2_deb+1+i1_fin-i1_deb+1)*(j_fin-j_deb+1))
     26  REAL zzz(nleng)
     27
     28  ! -----------------------------------------------------------------------
     29  ! passage a la grille dynamique:
     30  ! ------------------------------
     31  DO i = 1, iim
     32    zz(i, 1) = pz(1)
     33    zz(i, jjm+1) = pz(klon)
     34  END DO
     35
     36  ! traitement des point normaux
     37  DO j = 2, jjm
     38    ig = 2 + (j-2)*iim
     39    CALL scopy(iim, pz(ig), 1, zz(1,j), 1)
     40  END DO
     41  ! -----------------------------------------------------------------------
     42  ig = 0
     43  DO j = j_deb, j_fin
     44    DO i = i1_deb, i1_fin
     45      ig = ig + 1
     46      zzz(ig) = zz(i, j)
     47    END DO
     48    DO i = i2_deb, i2_fin
     49      ig = ig + 1
     50      zzz(ig) = zz(i, j)
     51    END DO
     52  END DO
    5453#ifdef VPP
    55       CALL ecriture(unit,zzz,nleng)
     54  CALL ecriture(unit, zzz, nleng)
    5655#else
    57       WRITE(unit) zzz
     56  WRITE (unit) zzz
    5857#endif
    59       RETURN
    60       END
    61       SUBROUTINE ecrirega(unit,pz)
    62       USE dimphy
    63       IMPLICIT none
    64 c-----------------------------------------------------------------------
    65 #include "dimensions.h"
    66 cccc#include "dimphy.h"
    67 #include "paramet.h"
    68 #include "comgeom.h"
    69 #include "comvert.h"
    70 #include "regdim.h"
    71 c
    72 c   arguments:
    73 c   ----------
    74       INTEGER unit
    75       REAL pz(klon,klev)
    76 c
    77 c   local:
    78 c   ------
    79       INTEGER i,j,ilay,ig
    80       REAL zz(iim,jjm+1,llm)
    81       INTEGER nleng
    82       PARAMETER (nleng=(i2_fin-i2_deb+1+i1_fin-i1_deb+1)
    83      .                *(j_fin-j_deb+1))
    84       REAL zzz(nleng)
    85 c-----------------------------------------------------------------------
    86 c   passage a la grille dynamique:
    87 c   ------------------------------
    88       DO ilay=1,llm
    89 c   traitement des poles
    90          DO i=1,iim
    91             zz(i,1,ilay)=pz(1,ilay)
    92             zz(i,jjm+1,ilay)=pz(klon,ilay)
    93          ENDDO
    94 c   traitement des point normaux
    95          DO j=2,jjm
    96             ig=2+(j-2)*iim
    97             CALL SCOPY(iim,pz(ig,ilay),1,zz(1,j,ilay),1)
    98          ENDDO
    99       ENDDO
    100 c-----------------------------------------------------------------------
    101       DO ilay = 1, llm
    102       ig = 0
    103       DO j = j_deb, j_fin
    104          DO i=i1_deb,i1_fin
    105             ig = ig + 1
    106             zzz(ig) = zz(i,j,ilay)
    107          ENDDO
    108          DO i=i2_deb,i2_fin
    109             ig = ig + 1
    110             zzz(ig) = zz(i,j,ilay)
    111          ENDDO
    112       ENDDO
     58  RETURN
     59END SUBROUTINE ecriregs
     60SUBROUTINE ecrirega(unit, pz)
     61  USE dimphy
     62  IMPLICIT NONE
     63  ! -----------------------------------------------------------------------
     64  include "dimensions.h"
     65  ! ccc#include "dimphy.h"
     66  include "paramet.h"
     67  include "comgeom.h"
     68  include "comvert.h"
     69  include "regdim.h"
     70
     71  ! arguments:
     72  ! ----------
     73  INTEGER unit
     74  REAL pz(klon, klev)
     75
     76  ! local:
     77  ! ------
     78  INTEGER i, j, ilay, ig
     79  REAL zz(iim, jjm+1, llm)
     80  INTEGER nleng
     81  PARAMETER (nleng=(i2_fin-i2_deb+1+i1_fin-i1_deb+1)*(j_fin-j_deb+1))
     82  REAL zzz(nleng)
     83  ! -----------------------------------------------------------------------
     84  ! passage a la grille dynamique:
     85  ! ------------------------------
     86  DO ilay = 1, llm
     87    ! traitement des poles
     88    DO i = 1, iim
     89      zz(i, 1, ilay) = pz(1, ilay)
     90      zz(i, jjm+1, ilay) = pz(klon, ilay)
     91    END DO
     92    ! traitement des point normaux
     93    DO j = 2, jjm
     94      ig = 2 + (j-2)*iim
     95      CALL scopy(iim, pz(ig,ilay), 1, zz(1,j,ilay), 1)
     96    END DO
     97  END DO
     98  ! -----------------------------------------------------------------------
     99  DO ilay = 1, llm
     100    ig = 0
     101    DO j = j_deb, j_fin
     102      DO i = i1_deb, i1_fin
     103        ig = ig + 1
     104        zzz(ig) = zz(i, j, ilay)
     105      END DO
     106      DO i = i2_deb, i2_fin
     107        ig = ig + 1
     108        zzz(ig) = zz(i, j, ilay)
     109      END DO
     110    END DO
    113111#ifdef VPP
    114       CALL ecriture(unit,zzz,nleng)
     112    CALL ecriture(unit, zzz, nleng)
    115113#else
    116       WRITE(unit) zzz
     114    WRITE (unit) zzz
    117115#endif
    118       ENDDO
     116  END DO
    119117
    120       RETURN
    121       END
     118  RETURN
     119END SUBROUTINE ecrirega
Note: See TracChangeset for help on using the changeset viewer.