Ignore:
Timestamp:
Jan 27, 2016, 10:42:32 AM (8 years ago)
Author:
idelkadi
Message:

Mise a jour du simulateur COSP (passage de la version v3.2 a la version v1.4) :

  • mise a jour des sources pour ISCCP, CALIPSO et PARASOL
  • prise en compte des changements de phases pour les nuages (Calipso)
  • rajout de plusieurs diagnostiques (fraction nuageuse en fonction de la temperature, ...)

http://lmdz.lmd.jussieu.fr/Members/aidelkadi/cosp

File:
1 edited

Legend:

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

    r1907 r2428  
    11! (c) British Crown Copyright 2008, the Met Office.
    22! All rights reserved.
     3! $Revision: 88 $, $Date: 2013-11-13 15:08:38 +0100 (mer. 13 nov. 2013) $
     4! $URL: http://cfmip-obs-sim.googlecode.com/svn/stable/v1.4.0/cosp_lidar.F90 $
    35!
    46! Redistribution and use in source and binary forms, with or without modification, are permitted
     
    2931!                               Call lidar_simulator changed (lsca, gbx%cca and depol removed;
    3032!                               frac_out changed in sgx%frac_out)
     33! Jun 2011 - G. Cesana        - Added betaperp_tot argument
    3134!
    3235!
     
    4346!%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    4447SUBROUTINE COSP_LIDAR(gbx,sgx,sghydro,y)
    45  
     48
    4649  ! Arguments
    4750  type(cosp_gridbox),intent(in) :: gbx  ! Gridbox info
     
    4952  type(cosp_sghydro),intent(in) :: sghydro  ! Subgrid info for hydrometeors
    5053  type(cosp_sglidar),intent(inout) :: y ! Subgrid output
    51  
     54
    5255  ! Local variables
    5356  integer :: i
    5457  real :: presf(sgx%Npoints, sgx%Nlevels + 1)
    55   real :: frac_out(sgx%Npoints, sgx%Nlevels)
    5658  real,dimension(sgx%Npoints, sgx%Nlevels) :: lsca,mr_ll,mr_li,mr_cl,mr_ci
    5759  real,dimension(sgx%Npoints, sgx%Nlevels) :: beta_tot,tau_tot
     60  real,dimension(sgx%Npoints, sgx%Nlevels) :: betaperp_tot
    5861  real,dimension(sgx%Npoints, PARASOL_NREFL)  :: refle
    59  
    60  
     62
    6163  presf(:,1:sgx%Nlevels) = gbx%ph
    6264  presf(:,sgx%Nlevels + 1) = 0.0
    63 !   presf(:,sgx%Nlevels + 1) = gbx%p(:,sgx%Nlevels) - (presf(:,sgx%Nlevels) - gbx%p(:,sgx%Nlevels))
    6465  lsca = gbx%tca-gbx%cca
    6566  do i=1,sgx%Ncolumns
     
    6970      mr_cl(:,:) = sghydro%mr_hydro(:,i,:,I_CVCLIQ)
    7071      mr_ci(:,:) = sghydro%mr_hydro(:,i,:,I_CVCICE)
    71       frac_out(:,:) = sgx%frac_out(:,i,:)   
    72       call lidar_simulator(sgx%Npoints, sgx%Nlevels, 4 &
    73                  , PARASOL_NREFL, LIDAR_UNDEF  &
    74                  , gbx%p, presf, gbx%T &
    75                  , mr_ll, mr_li, mr_cl, mr_ci &
    76                  , gbx%Reff(:,:,I_LSCLIQ), gbx%Reff(:,:,I_LSCICE), gbx%Reff(:,:,I_CVCLIQ), gbx%Reff(:,:,I_CVCICE) &
    77                  , frac_out, gbx%lidar_ice_type, y%beta_mol, beta_tot, tau_tot  &
    78                  , refle ) ! reflectance
    79      
     72      call lidar_simulator(sgx%Npoints, sgx%Nlevels, 4, PARASOL_NREFL, LIDAR_UNDEF  &
     73                 , gbx%p, presf, gbx%T, mr_ll, mr_li, mr_cl, mr_ci &
     74                 , gbx%Reff(:,:,I_LSCLIQ), gbx%Reff(:,:,I_LSCICE) &
     75                 , gbx%Reff(:,:,I_CVCLIQ), gbx%Reff(:,:,I_CVCICE) &
     76                 , gbx%lidar_ice_type, y%beta_mol, beta_tot &
     77                 , betaperp_tot, tau_tot, refle )
     78
     79      y%betaperp_tot(:,i,:) = betaperp_tot(:,:)
    8080      y%beta_tot(:,i,:) = beta_tot(:,:)
    8181      y%tau_tot(:,i,:)  = tau_tot(:,:)
Note: See TracChangeset for help on using the changeset viewer.