Ignore:
Timestamp:
Jul 17, 2017, 5:52:31 PM (7 years ago)
Author:
musat
Message:

Ajout modifs de Rodrigo Guzman et Marine Bonazolla dans la version COSP/CMIP6
IM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/cosp/lmd_ipsl_stats.F90

    r2428 r2955  
    3636      SUBROUTINE diag_lidar(npoints,ncol,llm,max_bin,nrefl &
    3737                  ,tmp,pnorm,pnorm_perp,pmol,refl,land,pplay,undef,ok_lidar_cfad &
    38                   ,cfad2,srbval,ncat,lidarcld,lidarcldphase,cldlayer,cldlayerphase &
    39                   ,lidarcldtmp,parasolrefl)
     38                  ,cfad2,srbval,ncat,ntype,lidarcld,lidarcldtype,lidarcldphase,cldlayer & !OPAQ
     39                  ,cldtype,cldlayerphase,lidarcldtmp,parasolrefl,vgrid_z,profSR)          !OPAQ !TIBO
    4040!
    4141! -----------------------------------------------------------------------------------
     
    8282      integer max_bin               ! nb of bins for SR CFADs
    8383      integer ncat                  ! nb of cloud layer types (low,mid,high,total)
     84      integer ntype                 ! nb of OPAQ products (opaque and thin clouds, z_opaque) !OPAQ
    8485      integer nrefl                 ! nb of solar zenith angles for parasol reflectances
    8586
     
    9394      real tmp(npoints,llm)         ! temp at each levels
    9495      real pnorm_perp(npoints,ncol,llm)  ! lidar perpendicular ATB
     96      real vgrid_z(llm)             ! mid-level altitude of the output vertical grid         !OPAQ
    9597
    9698! c outputs :
    9799      real lidarcld(npoints,llm)     ! 3D "lidar" cloud fraction
     100      real lidarcldtype(npoints,llm,ntype+1)   ! 3D "lidar" OPAQ type fraction + opacity     !OPAQ
    98101      real sub(npoints,llm)     ! 3D "lidar" indice
    99102      real cldlayer(npoints,ncat)    ! "lidar" cloud layer fraction (low, mid, high, total)
     103      real cldtype(npoints,ntype)  ! "lidar" OPAQ type covers (opaque/thin cloud + z_opaque) !OPAQ
    100104
    101105      real cfad2(npoints,max_bin,llm) ! CFADs of SR
    102106      real srbval(max_bin)           ! SR bins in CFADs
    103107      real parasolrefl(npoints,nrefl)! grid-averaged parasol reflectance
     108!     real profSR(npoints,ncol,llm)  ! tableau avec les subcolumns SR !TIBO
     109      real profSR(npoints,llm,ncol)  ! tableau avec les subcolumns SR !TIBO2
    104110
    105111! c threshold for cloud detection :
     
    110116      real S_att
    111117      parameter (S_att = 0.01)
     118!      parameter (S_att = 0.06)  !OPAQ ! Threshold for "surface detection" equivalent
    112119
    113120! c local variables :
     
    147154        end where
    148155         x3d(:,ic,:) = x3d_c
     156!       profSR(:,ic,:) = x3d(:,ic,:) !TIBO
     157        profSR(:,:,ic) = x3d(:,ic,:) !TIBO2
    149158      enddo
    150159
     
    157166              tmp,x3d,pnorm,pnorm_perp,pplay, S_att,S_cld,S_cld_att,undef,lidarcld, &
    158167              cldlayer,lidarcldphase,sub,cldlayerphase,lidarcldtmp)
     168
     169    CALL COSP_OPAQ(npoints,ncol,llm,ntype,x3d,S_cld,undef,lidarcldtype,            & !OPAQ
     170                   cldtype,vgrid_z)                                                  !OPAQ
    159171
    160172! c -------------------------------------------------------
     
    983995! ---------------------------------------------------------------
    984996
     997! BEGINNING OF OPAQ CHANGES
     998    ! ####################################################################################
     999    ! SUBROUTINE cosp_opaq
     1000    ! Conventions: Ntype must be equal to 3 (opaque cloud, thin cloud, z_opaque)
     1001    ! ####################################################################################
     1002    SUBROUTINE COSP_OPAQ(Npoints,Ncolumns,Nlevels,Ntype,x,S_cld,undef,lidarcldtype,   &
     1003                         cldtype,vgrid_z)
     1004
     1005      IMPLICIT NONE
     1006! Input arguments
     1007      integer Npoints,Ncolumns,Nlevels,Ntype
     1008      real x(Npoints,Ncolumns,Nlevels)
     1009      real S_cld
     1010      real undef
     1011      real vgrid_z(Nlevels)
     1012! Output :
     1013      real lidarcldtype(Npoints,Nlevels,Ntype+1) ! 3D "lidar" OPAQ type + opacity fraction
     1014      real cldtype(Npoints,Ntype)              ! opaque and thin cloud covers, z_opaque
     1015! Local variables
     1016      integer ip, k, iz, ic, zopac
     1017      real p1
     1018      real cldy(Npoints,Ncolumns,Nlevels)
     1019      real cldyopaq(Npoints,Ncolumns,Nlevels)
     1020      real srok(Npoints,Ncolumns,Nlevels)
     1021      real srokopaq(Npoints,Ncolumns,Nlevels)
     1022      real cldlay(Npoints,Ncolumns,Ntype+1)  ! opaque, thin, z_opaque and all cloud cover
     1023      real nsublay(Npoints,Ncolumns,Ntype+1) ! opaque, thin, z_opaque and all cloud cover
     1024      real nsublayer(Npoints,Ntype)
     1025      real nsub(Npoints,Nlevels)
     1026      real nsubopaq(Npoints,Nlevels)
     1027      real S_att_opaq
     1028      real S_att
     1029 
     1030    ! ####################################################################################
     1031        ! 1) Initialize   
     1032    ! ####################################################################################
     1033    cldtype               = 0.0
     1034    lidarcldtype          = 0.0
     1035    nsub                  = 0.0
     1036    nsubopaq              = 0.0
     1037    cldlay                = 0.0
     1038    nsublay               = 0.0
     1039    nsublayer             = 0.0
     1040    S_att_opaq            = 0.06 ! Fully Attenuated threshold, from Guzman et al. 2017, JGR-A
     1041    S_att                 = 0.01
     1042
     1043    ! ####################################################################################
     1044    ! 2) Cloud detection and Fully attenuated layer detection
     1045    ! ####################################################################################
     1046    do k=1,Nlevels
     1047       ! Cloud detection at subgrid-scale:
     1048       where ( (x(:,:,k) .gt. S_cld) .and. (x(:,:,k) .ne. undef) )
     1049          cldy(:,:,k)=1.0
     1050       elsewhere
     1051          cldy(:,:,k)=0.0
     1052       endwhere
     1053       ! Fully attenuated layer detection at subgrid-scale:
     1054       where ( (x(:,:,k) .gt. 0.0) .and. (x(:,:,k) .lt. S_att_opaq) .and. (x(:,:,k) .ne. undef) )
     1055          cldyopaq(:,:,k)=1.0
     1056       elsewhere
     1057          cldyopaq(:,:,k)=0.0
     1058       endwhere
     1059
     1060       ! Number of useful sub-column layers:
     1061       where ( (x(:,:,k) .gt. S_att) .and. (x(:,:,k) .ne. undef) )
     1062          srok(:,:,k)=1.0
     1063       elsewhere
     1064          srok(:,:,k)=0.0
     1065       endwhere
     1066       ! Number of useful sub-columns layers for z_opaque 3D fraction:
     1067       where ( (x(:,:,k) .gt. 0.0) .and. (x(:,:,k) .ne. undef) )
     1068          srokopaq(:,:,k)=1.0
     1069       elsewhere
     1070          srokopaq(:,:,k)=0.0
     1071       endwhere
     1072    enddo
     1073
     1074    ! ####################################################################################
     1075    ! 3) Grid-box 3D OPAQ product fraction and cloud type cover (opaque/thin) + mean z_opaque
     1076    ! ####################################################################################
     1077
     1078    do k= Nlevels,1,-1
     1079       do ic = 1, Ncolumns
     1080          do ip = 1, Npoints
     1081
     1082             cldlay(ip,ic,1)   = MAX(cldlay(ip,ic,1),cldyopaq(ip,ic,k)) ! Opaque clouds
     1083             cldlay(ip,ic,4)   = MAX(cldlay(ip,ic,4),cldy(ip,ic,k))     ! All clouds
     1084
     1085             nsublay(ip,ic,1)  = MAX(nsublay(ip,ic,1),srok(ip,ic,k))
     1086             nsublay(ip,ic,2)  = MAX(nsublay(ip,ic,2),srok(ip,ic,k))
     1087!             nsublay(ip,ic,4)  = MAX(nsublay(ip,ic,4),srok(ip,ic,k))
     1088             nsub(ip,k)        = nsub(ip,k) + srok(ip,ic,k)
     1089             nsubopaq(ip,k)    = nsubopaq(ip,k) + srokopaq(ip,ic,k)
     1090
     1091          enddo
     1092       enddo
     1093    enddo   
     1094
     1095! OPAQ variables
     1096     do ic = 1, Ncolumns
     1097        do ip = 1, Npoints
     1098
     1099     ! Declaring non-opaque cloudy profiles as thin cloud profiles
     1100           if ( (cldlay(ip,ic,4) .eq. 1.0) .and. (cldlay(ip,ic,1) .eq. 0.0) ) then
     1101              cldlay(ip,ic,2)  =  1.0
     1102           endif
     1103
     1104     ! Filling in 3D and 2D variables
     1105
     1106     ! Opaque cloud profiles
     1107           if ( cldlay(ip,ic,1) .eq. 1.0 ) then
     1108              zopac = 0.0
     1109              do k=2,Nlevels
     1110     ! Declaring opaque cloud fraction and z_opaque altitude for 3D and 2D variables
     1111                 if ( (cldy(ip,ic,k) .eq. 1.0) .and. (zopac .eq. 0.0) ) then
     1112                    lidarcldtype(ip,k-1,3) = lidarcldtype(ip,k-1,3) + 1.0
     1113                    cldlay(ip,ic,3)        = vgrid_z(k-1) !z_opaque altitude
     1114                    nsublay(ip,ic,3)       = 1.0
     1115                    zopac = 1.0
     1116                 endif
     1117                 if ( cldy(ip,ic,k) .eq. 1.0 ) then
     1118                    lidarcldtype(ip,k,1)   = lidarcldtype(ip,k,1) + 1.0
     1119                 endif
     1120              enddo
     1121           endif
     1122
     1123     ! Thin cloud profiles
     1124           if ( cldlay(ip,ic,2) .eq. 1.0 ) then
     1125              do k=1,Nlevels
     1126     ! Declaring thin cloud fraction for 3D variable
     1127                 if ( cldy(ip,ic,k) .eq. 1.0 ) then
     1128                    lidarcldtype(ip,k,2) = lidarcldtype(ip,k,2) + 1.0
     1129                 endif
     1130              enddo
     1131           endif
     1132
     1133       enddo
     1134    enddo   
     1135
     1136    ! 3D cloud types fraction (opaque=1 and thin=2)
     1137    where ( nsub(:,:) .gt. 0.0 )
     1138       lidarcldtype(:,:,1) = lidarcldtype(:,:,1)/nsub(:,:)
     1139       lidarcldtype(:,:,2) = lidarcldtype(:,:,2)/nsub(:,:)
     1140    elsewhere
     1141       lidarcldtype(:,:,1) = undef
     1142       lidarcldtype(:,:,2) = undef
     1143    endwhere
     1144    ! 3D z_opaque fraction (=3)
     1145    where ( nsubopaq(:,:) .gt. 0.0 )
     1146       lidarcldtype(:,:,3) = lidarcldtype(:,:,3)/nsubopaq(:,:)
     1147    elsewhere
     1148       lidarcldtype(:,:,3) = undef
     1149    endwhere
     1150    ! 3D opacity fraction (=4) !Summing z_opaque fraction from TOA(k=Nlevels) to SFC(k=1)
     1151       lidarcldtype(:,Nlevels,4) = lidarcldtype(:,Nlevels,3)
     1152    do ip = 1, Npoints
     1153        do k = Nlevels-1, 1, -1
     1154           if ( lidarcldtype(ip,k,3) .ne. undef ) then
     1155              lidarcldtype(ip,k,4) = lidarcldtype(ip,k+1,4) + lidarcldtype(ip,k,3)
     1156           endif
     1157        enddo
     1158    enddo
     1159    where ( nsubopaq(:,:) .eq. 0.0 )
     1160       lidarcldtype(:,:,4) = undef
     1161    endwhere
     1162
     1163    ! Layered cloud types (opaque, thin and z_opaque 2D variables)
     1164
     1165    do iz = 1, Ntype
     1166       do ic = 1, Ncolumns
     1167          cldtype(:,iz)   = cldtype(:,iz)   + cldlay(:,ic,iz)
     1168          nsublayer(:,iz) = nsublayer(:,iz) + nsublay(:,ic,iz)
     1169       enddo
     1170    enddo
     1171    where (nsublayer(:,:) .gt. 0.0)
     1172       cldtype(:,:) = cldtype(:,:)/nsublayer(:,:)
     1173    elsewhere
     1174       cldtype(:,:) = undef
     1175    endwhere
     1176
     1177  END SUBROUTINE COSP_OPAQ
     1178! END OF OPAQ CHANGES
     1179
    9851180
    9861181END MODULE MOD_LMD_IPSL_STATS
Note: See TracChangeset for help on using the changeset viewer.