!copyright (C) 2001  MSC-RPN COMM  %%%RPNPHY%%%
*** S/P BLWEIGHT2
*
#include "phy_macros_f.h"

      SUBROUTINE BLWEIGHT2 (W, S, PS, N, NK) 1
*
#include "impnone.cdk"
*
*
      INTEGER N, NK
      REAL W(N,NK), S(N,NK)
      REAL PS(N)
*
*Author
*          J. Mailhot and B. Bilodeau (Dec 2001)
*
*
*Revision
*001       A-M. Leduc and S. Belair (Jun 2003) - ps as argument
*                   blweight ---> blweight2. Change weighting
*                   profile from sigma to pressure dependent.
*
*Object
*          Compute a weighting profile to be used with the moist 
*          turbulence scheme.
*
*Arguments
*
*          - Output -
* W        weighting profile
*
*          - Input -
* S        sigma levels
* PS       surface pressure (in Pa)
* N        horizontal dimension
* NK       vertical dimension
*
*
*Notes
*          The profile is set to:
*            1 in the lower part of the atmosphere (S .ge. SMAX) if pres .ge. pmax
*            0 in the upper part of the atmosphere (S .le. SMIN) if pres .le. pmin
*            (with a linear interpolation in-between)
*
*
*
*******************************************************
*     AUTOMATIC ARRAYS
*******************************************************
*
      AUTOMATIC ( PRES     , REAL , (N,NK   ) )
*
*******************************************************


      INTEGER J, K
*
*      REAL SMIN, SMAX
*      SAVE SMIN, SMAX
       REAL PMIN, PMAX
       SAVE PMIN, PMAX
*
************************************************************
*
*      DATA SMIN , SMAX / 0.45 , 0.55 /
       DATA PMIN , PMAX / 45000, 55000 /
*
*
      DO K=1,NK
      DO J=1,N
*        W(J,K) = 1.0
**
*        IF (S(J,K).LE.SMIN) THEN
*           W(J,K) = 0.0
*        ELSE IF (S(J,K).LE.SMAX.AND.S(J,K).GT.SMIN) THEN
*           W(J,K) = (1. - (SMAX - S(J,K)) / (SMAX-SMIN) )
*        ENDIF

         PRES(J,K)=S(J,K)*PS(J)
         W(J,K)=(1- (PMAX-PRES(J,K))/(PMAX-PMIN) )
         W(J,K)=MIN ( MAX ( W(J,K), 0.), 1.)
       

      END DO
      END DO
*
*
      RETURN
      END