Ignore:
Timestamp:
Jan 27, 2016, 10:42:32 AM (9 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_utils.F90

    r1907 r2428  
    11! (c) British Crown Copyright 2008, the Met Office.
    22! All rights reserved.
     3! $Revision: 23 $, $Date: 2011-03-31 15:41:37 +0200 (jeu. 31 mars 2011) $
     4! $URL: http://cfmip-obs-sim.googlecode.com/svn/stable/v1.4.0/cosp_utils.F90 $
    35!
    46! Redistribution and use in source and binary forms, with or without modification, are permitted
     
    4547!%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    4648SUBROUTINE COSP_PRECIP_MXRATIO(Npoints,Nlevels,Ncolumns,p,T,prec_frac,prec_type, &
    47                           n_ax,n_bx,alpha_x,c_x,d_x,g_x,a_x,b_x,gamma1,gamma2, &
    48                           flux,mxratio)
     49                          n_ax,n_bx,alpha_x,c_x,d_x,g_x,a_x,b_x,gamma1,gamma2,gamma3,gamma4, &
     50                          flux,mxratio,reff)
    4951
    5052    ! Input arguments, (IN)
     
    5254    real,intent(in),dimension(Npoints,Nlevels) :: p,T,flux
    5355    real,intent(in),dimension(Npoints,Ncolumns,Nlevels) :: prec_frac
    54     real,intent(in) :: n_ax,n_bx,alpha_x,c_x,d_x,g_x,a_x,b_x,gamma1,gamma2,prec_type
     56    real,intent(in) :: n_ax,n_bx,alpha_x,c_x,d_x,g_x,a_x,b_x,gamma1,gamma2,gamma3,gamma4,prec_type
    5557    ! Input arguments, (OUT)
    5658    real,intent(out),dimension(Npoints,Ncolumns,Nlevels) :: mxratio
     59    real,intent(inout),dimension(Npoints,Ncolumns,Nlevels) :: reff
    5760    ! Local variables
    5861    integer :: i,j,k
    59     real :: sigma,one_over_xip1,xi,rho0,rho
     62    real :: sigma,one_over_xip1,xi,rho0,rho,lambda_x,gamma_4_3_2,delta
    6063   
    6164    mxratio = 0.0
    6265
    6366    if (n_ax >= 0.0) then ! N_ax is used to control which hydrometeors need to be computed
    64         !gamma1  = gamma(alpha_x + b_x + d_x + 1.0)
    65         !gamma2  = gamma(alpha_x + b_x + 1.0)
    6667        xi      = d_x/(alpha_x + b_x - n_bx + 1.0)
    6768        rho0    = 1.29
    6869        sigma   = (gamma2/(gamma1*c_x))*(n_ax*a_x*gamma2)**xi
    6970        one_over_xip1 = 1.0/(xi + 1.0)
     71        gamma_4_3_2 = 0.5*gamma4/gamma3
     72        delta = (alpha_x + b_x + d_x - n_bx + 1.0)
    7073       
    7174        do k=1,Nlevels
     
    7679                        mxratio(i,j,k)=(flux(i,k)*((rho/rho0)**g_x)*sigma)**one_over_xip1
    7780                        mxratio(i,j,k)=mxratio(i,j,k)/rho
     81                        ! Compute effective radius
     82                        if ((reff(i,j,k) <= 0.0).and.(flux(i,k) /= 0.0)) then
     83                           lambda_x = (a_x*c_x*((rho0/rho)**g_x)*n_ax*gamma1/flux(i,k))**(1./delta)
     84                           reff(i,j,k) = gamma_4_3_2/lambda_x
     85                        endif
    7886                    endif
    7987                enddo
Note: See TracChangeset for help on using the changeset viewer.