source: LMDZ6/branches/Ocean_skin/libf/phylmd/histo_o500_pctau.F90 @ 3627

Last change on this file since 3627 was 2346, checked in by Ehouarn Millour, 9 years ago

Physics/dynamics separation:

  • remove all references to dimensions.h from physics. nbp_lon (==iim) , nbp_lat (==jjm+1) and nbp_lev (==llm) from mod_grid_phy_lmdz should be used instead.
  • added module regular_lonlat_mod in phy_common to store information about the global (lon-lat) grid cell boundaries and centers.

EM

  • 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.9 KB
Line 
1
2! $Header$
3
4SUBROUTINE histo_o500_pctau(nbreg, pct_ocean, w, histo, histow, nhisto)
5  USE dimphy
6  IMPLICIT NONE
7
8  INTEGER :: ij, k, l, nw
9  INTEGER :: nreg, nbreg
10  INTEGER, PARAMETER :: kmax = 8, lmax = 8
11  INTEGER, PARAMETER :: kmaxm1 = kmax - 1, lmaxm1 = lmax - 1
12  INTEGER, PARAMETER :: iwmax = 40
13
14  INTEGER, DIMENSION (klon) :: iw
15  REAL, DIMENSION (klon) :: w
16  REAL, PARAMETER :: wmin = -200., pas_w = 10.
17  REAL, DIMENSION (kmaxm1, lmaxm1, iwmax, nbreg) :: histow, nhisto
18  REAL, DIMENSION (klon, kmaxm1, lmaxm1) :: histo
19
20  ! LOGICAL, dimension(klon,nbreg) :: pct_ocean
21  INTEGER, DIMENSION (klon, nbreg) :: pct_ocean
22
23  ! initialisation
24  histow(:, :, :, :) = 0.
25  nhisto(:, :, :, :) = 0.
26
27  ! calcul de l'histogramme de chaque regime dynamique
28  DO nreg = 1, nbreg
29    DO ij = 1, klon
30      iw(ij) = int((w(ij)-wmin)/pas_w) + 1
31      ! IF(pct_ocean(ij,nreg)) THEN
32      ! IF(pct_ocean(ij,nreg).EQ.1) THEN
33      IF (iw(ij)>=1 .AND. iw(ij)<=iwmax) THEN
34        DO l = 1, lmaxm1
35          DO k = 1, kmaxm1
36            IF (histo(ij,k,l)>0.) THEN
37              histow(k, l, iw(ij), nreg) = histow(k, l, iw(ij), nreg) + &
38                histo(ij, k, l)*pct_ocean(ij, nreg)
39              nhisto(k, l, iw(ij), nreg) = nhisto(k, l, iw(ij), nreg) + &
40                pct_ocean(ij, nreg)
41            END IF
42          END DO !k
43        END DO !l
44        ! ELSE IF (iw(ij).LE.0.OR.iw(ij).GT.iwmax) THEN !iw
45        ! PRINT*,'ij,iw=',ij,iw(ij)
46      END IF !iw
47      ! ENDIF !pct_ocean
48    END DO !ij
49    ! normalisation
50    DO nw = 1, iwmax
51      DO l = 1, lmaxm1
52        DO k = 1, kmaxm1
53          IF (nhisto(k,l,nw,nreg)/=0.) THEN
54            histow(k, l, nw, nreg) = 100.*histow(k, l, nw, nreg)/ &
55              nhisto(k, l, nw, nreg)
56            ! PRINT*,'k,l,nw,nreg,histoW',k,l,nw,nreg,
57            ! &     histoW(k,l,nw,nreg)
58          END IF
59        END DO !k
60      END DO !l
61    END DO !nw
62  END DO !nreg
63
64  RETURN
65END SUBROUTINE histo_o500_pctau
Note: See TracBrowser for help on using the repository browser.