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_simulator.F90

    r1907 r2428  
    11! (c) British Crown Copyright 2008, the Met Office.
    2 
    32! 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_simulator.F90 $
    45!
    56! Redistribution and use in source and binary forms, with or without modification, are permitted
     
    2728! History:
    2829! Jul 2007 - A. Bodas-Salcedo - Initial version
     30! Jan 2013 - G. Cesana - Add new variables linked to the lidar cloud phase
    2931!
    30 !
    31 
     32
     33#include "cosp_defs.h"
    3234MODULE MOD_COSP_SIMULATOR
     35  USE MOD_COSP_CONSTANTS, ONLY: I_RADAR, I_LIDAR, I_ISCCP, I_MISR, I_MODIS, &
     36                                I_RTTOV, I_STATS, tsim
    3337  USE MOD_COSP_TYPES
    3438  USE MOD_COSP_RADAR
    3539  USE MOD_COSP_LIDAR
    3640  USE MOD_COSP_ISCCP_SIMULATOR
     41  USE MOD_COSP_MODIS_SIMULATOR
    3742  USE MOD_COSP_MISR_SIMULATOR
     43!#ifdef RTTOV
     44!  USE MOD_COSP_RTTOV_SIMULATOR
     45!#endif
    3846  USE MOD_COSP_STATS
    3947  IMPLICIT NONE
     
    4553!--------------------- SUBROUTINE COSP_SIMULATOR ------------------
    4654!%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    47 SUBROUTINE COSP_SIMULATOR(gbx,sgx,sghydro,cfg,vgrid,sgradar,sglidar,isccp,misr,stradar,stlidar)
     55!#ifdef RTTOV
     56!SUBROUTINE COSP_SIMULATOR(gbx,sgx,sghydro,cfg,vgrid,sgradar,sglidar,isccp,misr,modis,rttov,stradar,stlidar)
     57!#else
     58SUBROUTINE COSP_SIMULATOR(gbx,sgx,sghydro,cfg,vgrid,sgradar,sglidar,isccp,misr,modis,stradar,stlidar)
     59!#endif
    4860
    4961  ! Arguments
    50   type(cosp_gridbox),intent(in) :: gbx      ! Grid-box inputs
     62  type(cosp_gridbox),intent(inout) :: gbx      ! Grid-box inputs
    5163  type(cosp_subgrid),intent(in) :: sgx      ! Subgrid inputs
    5264  type(cosp_sghydro),intent(in) :: sghydro  ! Subgrid info for hydrometeors
    53   type(cosp_config),intent(in) :: cfg       ! Configuration options
     65  type(cosp_config),intent(in)  :: cfg      ! Configuration options
    5466  type(cosp_vgrid),intent(in)   :: vgrid    ! Information on vertical grid of stats
    5567  type(cosp_sgradar),intent(inout) :: sgradar ! Output from radar simulator
     
    5769  type(cosp_isccp),intent(inout)   :: isccp   ! Output from ISCCP simulator
    5870  type(cosp_misr),intent(inout)    :: misr    ! Output from MISR simulator
     71  type(cosp_modis),intent(inout)   :: modis   ! Output from MODIS simulator
     72!#ifdef RTTOV
     73!  type(cosp_rttov),intent(inout)    :: rttov    ! Output from RTTOV
     74!#endif
    5975  type(cosp_radarstats),intent(inout) :: stradar ! Summary statistics from radar simulator
    6076  type(cosp_lidarstats),intent(inout) :: stlidar ! Summary statistics from lidar simulator
    6177  ! Local variables
    62   ! ***Timing variables (to be deleted in final version)
    63   integer :: t0,t1,count_rate,count_max
    64 
    65   !+++++++++ Radar model ++++++++++ 
     78  integer :: i,j,k,isim
     79  logical :: inconsistent
     80  ! Timing variables
     81  integer :: t0,t1
     82
     83  t0 = 0
     84  t1 = 0
     85
     86  inconsistent=.false.
     87!   do k=1,gbx%Nhydro
     88!   do j=1,gbx%Nlevels
     89!   do i=1,gbx%Npoints
     90!     if ((gbx%mr_hydro(i,j,k)>0.0).and.(gbx%Reff(i,j,k)<=0.0)) inconsistent=.true.
     91!   enddo
     92!   enddo
     93!   enddo
     94!  if (inconsistent)  print *, '%%%% COSP_SIMULATOR: inconsistency in mr_hydro and Reff'
     95
     96
     97  !+++++++++ Radar model ++++++++++
     98  isim = I_RADAR
    6699  if (cfg%Lradar_sim) then
     100    call system_clock(t0)
    67101    call cosp_radar(gbx,sgx,sghydro,sgradar)
    68   endif
    69  
     102    call system_clock(t1)
     103    tsim(isim) = tsim(isim) + (t1 -t0)
     104  endif
     105
    70106  !+++++++++ Lidar model ++++++++++
     107  isim = I_LIDAR
    71108  if (cfg%Llidar_sim) then
     109    call system_clock(t0)
    72110    call cosp_lidar(gbx,sgx,sghydro,sglidar)
    73   endif
    74 
    75  
     111    call system_clock(t1)
     112    tsim(isim) = tsim(isim) + (t1 -t0)
     113  endif
     114
    76115  !+++++++++ ISCCP simulator ++++++++++
     116  isim = I_ISCCP
    77117  if (cfg%Lisccp_sim) then
     118    call system_clock(t0)
    78119    call cosp_isccp_simulator(gbx,sgx,isccp)
    79   endif
    80  
     120    call system_clock(t1)
     121    tsim(isim) = tsim(isim) + (t1 -t0)
     122  endif
     123
    81124  !+++++++++ MISR simulator ++++++++++
     125  isim = I_MISR
    82126  if (cfg%Lmisr_sim) then
     127    call system_clock(t0)
    83128    call cosp_misr_simulator(gbx,sgx,misr)
    84   endif
    85  
     129    call system_clock(t1)
     130    tsim(isim) = tsim(isim) + (t1 -t0)
     131  endif
     132
     133  !+++++++++ MODIS simulator ++++++++++
     134  isim = I_MODIS
     135  if (cfg%Lmodis_sim) then
     136    call system_clock(t0)
     137    call cosp_modis_simulator(gbx,sgx,sghydro,isccp, modis)
     138    call system_clock(t1)
     139    tsim(isim) = tsim(isim) + (t1 -t0)
     140  endif
     141
     142  !+++++++++ RTTOV ++++++++++
     143  isim = I_RTTOV
     144!#ifdef RTTOV
     145!  if (cfg%Lrttov_sim) then
     146!    call system_clock(t0)
     147!    call cosp_rttov_simulator(gbx,rttov)
     148!    call system_clock(t1)
     149!    tsim(isim) = tsim(isim) + (t1 -t0)
     150!  endif
     151!#endif
    86152
    87153  !+++++++++++ Summary statistics +++++++++++
     154  isim = I_STATS
    88155  if (cfg%Lstats) then
     156    call system_clock(t0)
    89157    call cosp_stats(gbx,sgx,cfg,sgradar,sglidar,vgrid,stradar,stlidar)
    90 !    print *, '%%%%%%  Stats:', (t1-t0)*1.0/count_rate, ' s'
    91   endif
    92 
    93  
     158    call system_clock(t1)
     159    tsim(isim) = tsim(isim) + (t1 -t0)
     160  endif
     161
     162  !+++++++++++ Change of units after computation of statistics +++++++++++
     163  ! This avoids using UDUNITS in CMOR
     164
     165  ! Cloud fractions from 1 to %
     166  if (cfg%Lclcalipso) then
     167    where(stlidar%lidarcld /= R_UNDEF) stlidar%lidarcld = stlidar%lidarcld*100.0
     168  endif
     169  if (cfg%Lcltcalipso.OR.cfg%Lcllcalipso.OR.cfg%Lclmcalipso.OR.cfg%Lclhcalipso) then
     170    where(stlidar%cldlayer /= R_UNDEF) stlidar%cldlayer = stlidar%cldlayer*100.0
     171  endif
     172  if (cfg%Lclcalipso2) then
     173    where(stradar%lidar_only_freq_cloud /= R_UNDEF) stradar%lidar_only_freq_cloud = stradar%lidar_only_freq_cloud*100.0
     174  endif
     175
     176  if (cfg%Lcltcalipsoliq.OR.cfg%Lcllcalipsoliq.OR.cfg%Lclmcalipsoliq.OR.cfg%Lclhcalipsoliq.OR. &
     177      cfg%Lcltcalipsoice.OR.cfg%Lcllcalipsoice.OR.cfg%Lclmcalipsoice.OR.cfg%Lclhcalipsoice.OR. &
     178      cfg%Lcltcalipsoun.OR.cfg%Lcllcalipsoun.OR.cfg%Lclmcalipsoun.OR.cfg%Lclhcalipsoun ) then
     179    where(stlidar%cldlayerphase /= R_UNDEF) stlidar%cldlayerphase = stlidar%cldlayerphase*100.0
     180  endif
     181  if (cfg%Lclcalipsoliq.OR.cfg%Lclcalipsoice.OR.cfg%Lclcalipsoun) then
     182    where(stlidar%lidarcldphase /= R_UNDEF) stlidar%lidarcldphase = stlidar%lidarcldphase*100.0
     183  endif
     184  if (cfg%Lclcalipsotmp.OR.cfg%Lclcalipsotmpliq.OR.cfg%Lclcalipsotmpice.OR.cfg%Lclcalipsotmpun) then
     185    where(stlidar%lidarcldtmp /= R_UNDEF) stlidar%lidarcldtmp = stlidar%lidarcldtmp*100.0
     186  endif
     187
     188  if (cfg%Lcltisccp) then
     189     where(isccp%totalcldarea /= R_UNDEF) isccp%totalcldarea = isccp%totalcldarea*100.0
     190! Test
     191!     where(isccp%totalcldarea == R_UNDEF) isccp%totalcldarea = 0.
     192  endif 
     193  if (cfg%Lclisccp) then
     194    where(isccp%fq_isccp /= R_UNDEF) isccp%fq_isccp = isccp%fq_isccp*100.0
     195  endif
     196
     197  if (cfg%LclMISR) then
     198    where(misr%fq_MISR /= R_UNDEF) misr%fq_MISR = misr%fq_MISR*100.0
     199  endif
     200
     201  if (cfg%Lcltlidarradar) then
     202    where(stradar%radar_lidar_tcc /= R_UNDEF) stradar%radar_lidar_tcc = stradar%radar_lidar_tcc*100.0
     203  endif
     204
     205  if (cfg%Lclmodis) then
     206    where(modis%Optical_Thickness_vs_Cloud_Top_Pressure /= R_UNDEF) modis%Optical_Thickness_vs_Cloud_Top_Pressure = &
     207                                                      modis%Optical_Thickness_vs_Cloud_Top_Pressure*100.0
     208  endif
     209  if (cfg%Lcltmodis) then
     210     where(modis%Cloud_Fraction_Total_Mean /= R_UNDEF) modis%Cloud_Fraction_Total_Mean = modis%Cloud_Fraction_Total_Mean*100.0
     211  endif
     212  if (cfg%Lclwmodis) then
     213     where(modis%Cloud_Fraction_Water_Mean /= R_UNDEF) modis%Cloud_Fraction_Water_Mean = modis%Cloud_Fraction_Water_Mean*100.0
     214  endif
     215  if (cfg%Lclimodis) then
     216     where(modis%Cloud_Fraction_Ice_Mean /= R_UNDEF) modis%Cloud_Fraction_Ice_Mean = modis%Cloud_Fraction_Ice_Mean*100.0
     217  endif
     218
     219  if (cfg%Lclhmodis) then
     220     where(modis%Cloud_Fraction_High_Mean /= R_UNDEF) modis%Cloud_Fraction_High_Mean = modis%Cloud_Fraction_High_Mean*100.0
     221  endif
     222  if (cfg%Lclmmodis) then
     223     where(modis%Cloud_Fraction_Mid_Mean /= R_UNDEF) modis%Cloud_Fraction_Mid_Mean = modis%Cloud_Fraction_Mid_Mean*100.0
     224  endif
     225  if (cfg%Lcllmodis) then
     226     where(modis%Cloud_Fraction_Low_Mean /= R_UNDEF) modis%Cloud_Fraction_Low_Mean = modis%Cloud_Fraction_Low_Mean*100.0
     227  endif
     228
     229  ! Change pressure from hPa to Pa.
     230  if (cfg%Lboxptopisccp) then
     231    where(isccp%boxptop /= R_UNDEF) isccp%boxptop = isccp%boxptop*100.0
     232  endif
     233  if (cfg%Lpctisccp) then
     234    where(isccp%meanptop /= R_UNDEF) isccp%meanptop = isccp%meanptop*100.0
     235  endif
     236
     237
    94238END SUBROUTINE COSP_SIMULATOR
    95239
Note: See TracChangeset for help on using the changeset viewer.