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/histo_o500_pctau.F90

    r1988 r1992  
    1 !
     1
    22! $Header$
    3 !
    4       SUBROUTINE histo_o500_pctau(nbreg,pct_ocean,w,histo,histoW,nhisto)
    5       USE dimphy
    6       IMPLICIT none
    73
    8       INTEGER :: ij, k, l, nw
    9       INTEGER :: nreg, nbreg
    10 cym#include "dimensions.h"
    11 cym#include "dimphy.h"
    12       INTEGER, PARAMETER :: kmax=8, lmax=8
    13       INTEGER, PARAMETER :: kmaxm1=kmax-1, lmaxm1=lmax-1
    14       INTEGER, PARAMETER :: iwmax=40
     4SUBROUTINE histo_o500_pctau(nbreg, pct_ocean, w, histo, histow, nhisto)
     5  USE dimphy
     6  IMPLICIT NONE
    157
    16       INTEGER, dimension(klon) :: iw
    17       REAL, dimension(klon) :: w
    18       REAL, PARAMETER :: wmin=-200., pas_w=10.
    19       REAL, dimension(kmaxm1,lmaxm1,iwmax,nbreg) :: histoW, nhisto
    20       REAL, dimension(klon,kmaxm1,lmaxm1) :: histo
     8  INTEGER :: ij, k, l, nw
     9  INTEGER :: nreg, nbreg
     10  ! ym#include "dimensions.h"
     11  ! ym#include "dimphy.h"
     12  INTEGER, PARAMETER :: kmax = 8, lmax = 8
     13  INTEGER, PARAMETER :: kmaxm1 = kmax - 1, lmaxm1 = lmax - 1
     14  INTEGER, PARAMETER :: iwmax = 40
    2115
    22 !     LOGICAL, dimension(klon,nbreg) :: pct_ocean
    23       INTEGER, dimension(klon,nbreg) :: pct_ocean
     16  INTEGER, DIMENSION (klon) :: iw
     17  REAL, DIMENSION (klon) :: w
     18  REAL, PARAMETER :: wmin = -200., pas_w = 10.
     19  REAL, DIMENSION (kmaxm1, lmaxm1, iwmax, nbreg) :: histow, nhisto
     20  REAL, DIMENSION (klon, kmaxm1, lmaxm1) :: histo
    2421
    25 ! initialisation
    26       histoW(:,:,:,:)=0.     
    27       nhisto(:,:,:,:)=0.   
    28 !   
    29 !calcul de l'histogramme de chaque regime dynamique
    30       DO nreg=1, nbreg
    31        DO ij=1, klon
    32         iw(ij) = int((w(ij)-wmin)/pas_w) +1
    33 c       IF(pct_ocean(ij,nreg)) THEN
    34 c       IF(pct_ocean(ij,nreg).EQ.1) THEN
    35          IF(iw(ij).GE.1.AND.iw(ij).LE.iwmax) THEN
    36           DO l=1, lmaxm1
    37            DO k=1, kmaxm1
    38             IF(histo(ij,k,l).GT.0.) THEN
    39              histoW(k,l,iw(ij),nreg) = histoW(k,l,iw(ij),nreg)
    40      &       + histo(ij,k,l)*pct_ocean(ij,nreg)
    41              nhisto(k,l,iw(ij),nreg)= nhisto(k,l,iw(ij),nreg) +
    42      &       pct_ocean(ij,nreg)
    43             ENDIF
    44            ENDDO !k
    45           ENDDO !l
    46 c        ELSE IF (iw(ij).LE.0.OR.iw(ij).GT.iwmax) THEN !iw
    47 c         PRINT*,'ij,iw=',ij,iw(ij)
    48          ENDIF !iw
    49 c       ENDIF !pct_ocean
    50        ENDDO !ij
    51 !normalisation
    52        DO nw=1, iwmax
    53         DO l=1, lmaxm1
    54          DO k=1, kmaxm1
    55           IF(nhisto(k,l,nw,nreg).NE.0.) THEN
    56            histoW(k,l,nw,nreg) = 100.*histoW(k,l,nw,nreg)
    57      &     /nhisto(k,l,nw,nreg)
    58 c          PRINT*,'k,l,nw,nreg,histoW',k,l,nw,nreg,
    59 c    &     histoW(k,l,nw,nreg)
    60           ENDIF
    61          ENDDO !k
    62         ENDDO !l
    63        ENDDO !nw
    64       ENDDO !nreg
     22  ! LOGICAL, dimension(klon,nbreg) :: pct_ocean
     23  INTEGER, DIMENSION (klon, nbreg) :: pct_ocean
    6524
    66       RETURN
    67       END
     25  ! initialisation
     26  histow(:, :, :, :) = 0.
     27  nhisto(:, :, :, :) = 0.
     28
     29  ! calcul de l'histogramme de chaque regime dynamique
     30  DO nreg = 1, nbreg
     31    DO ij = 1, klon
     32      iw(ij) = int((w(ij)-wmin)/pas_w) + 1
     33      ! IF(pct_ocean(ij,nreg)) THEN
     34      ! IF(pct_ocean(ij,nreg).EQ.1) THEN
     35      IF (iw(ij)>=1 .AND. iw(ij)<=iwmax) THEN
     36        DO l = 1, lmaxm1
     37          DO k = 1, kmaxm1
     38            IF (histo(ij,k,l)>0.) THEN
     39              histow(k, l, iw(ij), nreg) = histow(k, l, iw(ij), nreg) + &
     40                histo(ij, k, l)*pct_ocean(ij, nreg)
     41              nhisto(k, l, iw(ij), nreg) = nhisto(k, l, iw(ij), nreg) + &
     42                pct_ocean(ij, nreg)
     43            END IF
     44          END DO !k
     45        END DO !l
     46        ! ELSE IF (iw(ij).LE.0.OR.iw(ij).GT.iwmax) THEN !iw
     47        ! PRINT*,'ij,iw=',ij,iw(ij)
     48      END IF !iw
     49      ! ENDIF !pct_ocean
     50    END DO !ij
     51    ! normalisation
     52    DO nw = 1, iwmax
     53      DO l = 1, lmaxm1
     54        DO k = 1, kmaxm1
     55          IF (nhisto(k,l,nw,nreg)/=0.) THEN
     56            histow(k, l, nw, nreg) = 100.*histow(k, l, nw, nreg)/ &
     57              nhisto(k, l, nw, nreg)
     58            ! PRINT*,'k,l,nw,nreg,histoW',k,l,nw,nreg,
     59            ! &     histoW(k,l,nw,nreg)
     60          END IF
     61        END DO !k
     62      END DO !l
     63    END DO !nw
     64  END DO !nreg
     65
     66  RETURN
     67END SUBROUTINE histo_o500_pctau
Note: See TracChangeset for help on using the changeset viewer.