16   use variable_precision, 
ONLY: wp
 
   17   use initialize, 
only: mphys_init
 
   18   use mphys_switches, 
only: set_mphys_switches,  &
 
   20      nq_l, nq_r, nq_i, nq_s, nq_g,               &
 
   21      l_2mc, l_2mr, l_2mi, l_2ms, l_2mg,          &
 
   22      l_3mr, l_3ms, l_3mg,                        &
 
   23      soluble_modes, active_cloud, active_rain,   &
 
   24      insoluble_modes, active_ice, active_number, &
 
   25      isol, iinsol, option, aerosol_option,        &
 
   26      iopt_act, option, aerosol_option        &
 
   29      , l_aaut, l_aacc, l_aevp, l_ased, l_warm            &
 
   30      , l_inuc, iopt_rcrit, iopt_inuc, l_iaut, l_iacw                &
 
   31      , l_rain, l_boussinesq, diag_mu_option   &
 
   32      , l_sed_3mdiff, l_cons, l_abelshipway, l_sed_icecloud_as_1m         &
 
   33      , l_active_inarg2000, process_level, l_separate_rain, l_idep    &
 
   34      , max_step_length, max_sed_length, l_sg, l_g, l_passive        &
 
   35      , l_passive3m, l_limit_psd, l_override_checks &
 
   36      , max_mu, fix_mu, l_raci_g, l_onlycollect, l_inhom_revp &
 
   37      , l_tidy_conserve_e , l_tidy_conserve_q & 
 
   79   use micro_main, 
only: shipway_microphysics
 
   80   use generic_diagnostic_variables, 
ONLY: casdiags, allocate_diagnostic_space, &
 
   81        deallocate_diagnostic_space
 
   92      z_half(:,:,:), 
z_centre(:,:,:), 
dz(:,:,:), 
qv(:,:,:),
qc(:,:,:) &
 
   93      , 
nc(:,:,:), 
qr(:,:,:), 
nr(:,:,:), 
m3r(:,:,:),
rho(:,:,:) &
 
   95      , 
qi(:,:,:), 
ni(:,:,:), 
qs(:,:,:), 
ns(:,:,:), 
m3s(:,:,:) &
 
   96      , 
qg(:,:,:), 
ng(:,:,:), 
m3g(:,:,:) 
 
  121   REAL(wp), 
allocatable :: 
dqv(:,:,:), 
dth(:,:,:), 
dqc(:,:,:), 
dnc(:,:,:)              &
 
  123      , 
dqi(:,:,:), 
dni(:,:,:), 
dqs(:,:,:), 
dns(:,:,:), 
dm3s(:,:,:)      & 
 
  225     type(model_state_type), 
target, 
intent(inout) :: current_state
 
  227     integer :: y_size_local, x_size_local
 
  229     if (is_component_enabled(current_state%options_database, 
"simplecloud")) 
then 
  230       call log_master_log(log_error, 
"Casim and Simplecloud are enabled, this does not work yet. Please disable one")
 
  236     y_size_local = current_state%local_grid%size(y_index)
 
  237     x_size_local = current_state%local_grid%size(x_index)
 
  246     kle=current_state%local_grid%size(z_index)
 
  252     kte=current_state%local_grid%size(z_index)
 
  259     allocate(
dz(
kte,1,1))
 
  266     allocate(
qv(
kte,1,1))
 
  267     allocate(
qc(
kte,1,1))
 
  268     allocate(
nc(
kte,1,1))
 
  269     allocate(
qr(
kte,1,1))
 
  270     allocate(
nr(
kte,1,1))
 
  272     allocate(
qi(
kte,1,1))
 
  273     allocate(
ni(
kte,1,1))
 
  274     allocate(
qs(
kte,1,1))
 
  275     allocate(
ns(
kte,1,1))
 
  277     allocate(
qg(
kte,1,1))
 
  278     allocate(
ng(
kte,1,1))
 
  337     call set_mphys_switches(option,aerosol_option)
 
  338     call mphys_init(
its, 
ite, 
jts, 
jte, 
kts, 
kte, 
ils, 
ile, 
jls, 
jle, 
kls, 
kle, l_tendency=.true.)
 
  348     if (.not. 
allocated(current_state%cq))
then 
  349        allocate(current_state%cq(current_state%number_q_fields))
 
  350        current_state%cq=0.0_default_precision
 
  354     iqv = get_q_index(standard_q_names%VAPOUR, 
'casim')
 
  356        iql = get_q_index(standard_q_names%CLOUD_LIQUID_MASS, 
'casim')
 
  357        current_state%cq(
iql) = -1.0
 
  360        iqr = get_q_index(standard_q_names%RAIN_MASS, 
'casim')
 
  361        current_state%rain_water_mixing_ratio_index=
iqr 
  362       current_state%cq(
iqr) = -1.0
 
  364     if (.not. l_warm)
then 
  366          iqi = get_q_index(standard_q_names%ICE_MASS, 
'casim')
 
  367          current_state%ice_water_mixing_ratio_index=
iqi 
  368         current_state%cq(
iqi) = -1.0
 
  371          iqs = get_q_index(standard_q_names%SNOW_MASS, 
'casim')
 
  372          current_state%snow_water_mixing_ratio_index=
iqs 
  373         current_state%cq(
iqs) = -1.0
 
  376          iqg = get_q_index(standard_q_names%GRAUPEL_MASS, 
'casim')
 
  377          current_state%graupel_water_mixing_ratio_index=
iqg 
  378         current_state%cq(
iqg) = -1.0
 
  383     if (l_2mc)
inl = get_q_index(standard_q_names%CLOUD_LIQUID_NUMBER, 
'casim')
 
  384     if (l_2mr)
inr = get_q_index(standard_q_names%RAIN_NUMBER, 
'casim')
 
  385     if (.not. l_warm)
then 
  386       if (l_2mi)
ini = get_q_index(standard_q_names%ICE_NUMBER, 
'casim')
 
  387       if (l_2ms)
ins = get_q_index(standard_q_names%SNOW_NUMBER, 
'casim')
 
  388       if (l_2mg)
ing = get_q_index(standard_q_names%GRAUPEL_NUMBER, 
'casim')
 
  392     if (l_3mr)
i3mr = get_q_index(standard_q_names%RAIN_THIRD_MOMENT, 
'casim')
 
  393     if (.not. l_warm)
then 
  394       if (l_3ms)
i3ms = get_q_index(standard_q_names%SNOW_THIRD_MOMENT, 
'casim')
 
  395       if (l_3mg)
i3mg = get_q_index(standard_q_names%GRAUPEL_THIRD_MOMENT, 
'casim')
 
  400        get_q_index(standard_q_names%AITKEN_SOL_MASS,     
'casim') 
 
  402        get_q_index(standard_q_names%AITKEN_SOL_NUMBER,   
'casim') 
 
  404        get_q_index(standard_q_names%ACCUM_SOL_MASS,      
'casim') 
 
  406        get_q_index(standard_q_names%ACCUM_SOL_NUMBER,    
'casim') 
 
  408        get_q_index(standard_q_names%COARSE_SOL_MASS,     
'casim') 
 
  410        get_q_index(standard_q_names%COARSE_SOL_NUMBER,   
'casim') 
 
  412        get_q_index(standard_q_names%ACTIVE_SOL_LIQUID,   
'casim') 
 
  414        get_q_index(standard_q_names%ACTIVE_SOL_RAIN,     
'casim') 
 
  416        get_q_index(standard_q_names%COARSE_DUST_MASS,    
'casim') 
 
  418        get_q_index(standard_q_names%COARSE_DUST_NUMBER,  
'casim') 
 
  420        get_q_index(standard_q_names%ACTIVE_INSOL_ICE,    
'casim') 
 
  422        get_q_index(standard_q_names%ACTIVE_SOL_ICE,      
'casim') 
 
  424        get_q_index(standard_q_names%ACTIVE_INSOL_LIQUID, 
'casim') 
 
  426        get_q_index(standard_q_names%ACCUM_INSOL_MASS,    
'casim') 
 
  428        get_q_index(standard_q_names%ACCUM_INSOL_NUMBER,  
'casim') 
 
  430        get_q_index(standard_q_names%ACTIVE_SOL_NUMBER,   
'casim') 
 
  432          get_q_index(standard_q_names%ACTIVE_INSOL_NUMBER, 
'casim')
 
  435     casdiags % l_dth = .true.
 
  436     casdiags % l_dqv = .true.
 
  437     if ( nq_l>0 ) casdiags % l_dqc = .true.
 
  438     if ( nq_r>0 ) casdiags % l_dqr = .true.
 
  439     if ( l_pcond ) casdiags % l_pcond = .true.
 
  441        casdiags % l_psedl = .true.
 
  442        casdiags % l_surface_rain = .true.
 
  443        casdiags % l_precip = .true.
 
  445     if ( l_praut ) casdiags % l_praut = .true.
 
  446     if ( l_pracw ) casdiags % l_pracw = .true.
 
  447     if ( l_prevp ) casdiags % l_prevp = .true.
 
  449        casdiags % l_psedr = .true.
 
  450        casdiags % l_surface_rain = .true.
 
  451        casdiags % l_precip = .true.
 
  453     if (.not. l_warm) 
then 
  454        if ( nq_i>0 ) casdiags % l_dqi = .true.
 
  455        if ( nq_s>0 ) casdiags % l_dqs = .true.
 
  456        if ( nq_g>0 ) casdiags % l_dqg = .true.
 
  457        if ( l_phomc ) casdiags % l_phomc = .true.
 
  458        if ( l_pinuc ) casdiags % l_pinuc = .true.
 
  459        if ( l_pidep ) casdiags % l_pidep = .true.
 
  460        if ( l_piacw ) casdiags % l_piacw = .true.
 
  461        if ( l_pisub ) casdiags % l_pisub = .true.
 
  462        if ( l_pimlt ) casdiags % l_pimlt = .true.
 
  464           casdiags % l_psedi = .true.
 
  465           casdiags % l_surface_snow = .true.
 
  466           casdiags % l_precip = .true.
 
  468        if ( l_psmlt ) casdiags % l_psmlt = .true.
 
  469        if ( l_psaut ) casdiags % l_psaut = .true.
 
  470        if ( l_psaci ) casdiags % l_psaci = .true.
 
  471        if ( l_psacw ) casdiags % l_psacw = .true.
 
  472        if ( l_psacr ) casdiags % l_psacr = .true.
 
  473        if ( l_pssub ) casdiags % l_pssub = .true.
 
  474        if ( l_psdep ) casdiags % l_psdep = .true.
 
  476           casdiags % l_pseds = .true.
 
  477           casdiags % l_surface_snow = .true.
 
  478           casdiags % l_precip = .true.
 
  480        if ( l_pgacw ) casdiags % l_pgacw = .true.
 
  481        if ( l_pgacs ) casdiags % l_pgacs = .true.
 
  482        if ( l_pgmlt ) casdiags % l_pgmlt = .true.
 
  483        if ( l_pgsub ) casdiags % l_pgsub = .true.
 
  485           casdiags % l_psedg = .true.
 
  486           casdiags % l_surface_graup = .true.
 
  487           casdiags % l_precip = .true.
 
  496     call allocate_casim_monc_dgs_space(current_state, casdiags)
 
  503     type(model_state_type), 
target, 
intent(inout) :: current_state
 
  506     INTEGER :: icol, jcol, iqx, target_x_index, target_y_index
 
  508     icol=current_state%column_local_x
 
  509     jcol=current_state%column_local_y
 
  510     target_y_index=jcol-current_state%local_grid%halo_size(y_index)
 
  511     target_x_index=icol-current_state%local_grid%halo_size(x_index)
 
  518     if (current_state%halo_column .or. current_state%timestep < 2) 
return 
  520     if (current_state%field_stepping == forward_stepping)
then 
  521       call log_master_log(log_error, 
'Currently, CASIM assumes CENTERED_STEPPING')
 
  522       dtwp = current_state%dtm
 
  524       dtwp = 2.0*current_state%dtm
 
  564     theta(:,1,1) = current_state%zth%data(:, jcol, icol) + current_state%global_grid%configuration%vertical%thref(:)
 
  565     dth(:,1,1) = current_state%sth%data(:, jcol, icol)
 
  566     exner(:,1,1) = current_state%global_grid%configuration%vertical%rprefrcp(:)
 
  567     pressure(:,1,1) = current_state%global_grid%configuration%vertical%prefn(:)
 
  568     z_centre(:,1,1) = current_state%global_grid%configuration%vertical%zn(:)
 
  569     dz(:,1,1) = current_state%global_grid%configuration%vertical%dz(:)
 
  570     z_half(:
kte-1,1,1) = current_state%global_grid%configuration%vertical%z(:)
 
  571     rho(:,1,1) = current_state%global_grid%configuration%vertical%rhon(:)
 
  572     w(:,1,1) = current_state%zw%data(:, jcol, icol)
 
  576     qv(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
 
  577     dqv(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
 
  582       qc(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
 
  583       dqc(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
 
  587       qr(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
 
  588       dqr(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
 
  592       nc(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
 
  593       dnc(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
 
  597       nr(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
 
  598       dnr(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
 
  602       m3r(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
 
  603       dm3r(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
 
  609       qi(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
 
  610       dqi(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
 
  614       qs(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
 
  615       dqs(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
 
  619       qg(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
 
  620       dqg(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
 
  624       ni(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
 
  625       dni(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
 
  629       ns(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
 
  630       dns(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
 
  634       ng(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
 
  635       dng(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
 
  639       m3s(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
 
  640       dm3s(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
 
  644       m3g(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
 
  645       dm3g(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
 
  683     CALL shipway_microphysics(                     &
 
  740     current_state%sth%data(:,jcol,icol) = current_state%sth%data(:,jcol,icol) + 
dth(:,1,1)
 
  743     current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + 
dqv(:,1,1)
 
  748       current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + 
dqc(:,1,1)
 
  753       current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + 
dqr(:,1,1)
 
  757       current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + 
dnc(:,1,1)
 
  761       current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + 
dnr(:,1,1)
 
  765       current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + 
dm3r(:,1,1)
 
  771       current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + 
dqi(:,1,1)
 
  775       current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + 
dqs(:,1,1)
 
  779       current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + 
dqg(:,1,1)
 
  783       current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + 
dni(:,1,1)
 
  787       current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + 
dns(:,1,1)
 
  791       current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + 
dng(:,1,1)
 
  795       current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + 
dm3s(:,1,1)
 
  799       current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + 
dm3g(:,1,1)
 
  843             casdiags % SurfaceRainR(1,1)
 
  846             casdiags % SurfaceRainR(1,1) + casdiags % SurfaceSnowR(1,1)
 
  848     call populate_casim_monc_dg(current_state, casdiags)
 
  859     Use mphys_parameters, 
only: p1, p2, p3, sp1, sp2, sp3   
 
  861     type(model_state_type), 
target, 
intent(inout) :: current_state
 
  865     option          = options_get_integer(current_state%options_database, 
'option')
 
  866     diag_mu_option  = options_get_integer(current_state%options_database, 
'diag_mu_option')
 
  867     iopt_act        = options_get_integer(current_state%options_database, 
'iopt_act')
 
  868     iopt_inuc       = options_get_integer(current_state%options_database, 
'iopt_inuc')
 
  869     process_level   = options_get_integer(current_state%options_database, 
'process_level')
 
  870     aerosol_option  = options_get_integer(current_state%options_database, 
'aerosol_option')
 
  871     max_step_length = options_get_real(current_state%options_database, 
'max_step_length')
 
  872     max_sed_length  = options_get_real(current_state%options_database, 
'max_sed_length')
 
  873     p1              = options_get_real(current_state%options_database, 
'p1')
 
  874     p2              = options_get_real(current_state%options_database, 
'p2')
 
  875     p3              = options_get_real(current_state%options_database, 
'p3')
 
  876     sp1             = options_get_real(current_state%options_database, 
'sp1')
 
  877     sp2             = options_get_real(current_state%options_database, 
'sp2')
 
  878     sp3             = options_get_real(current_state%options_database, 
'sp3')
 
  879     max_mu          = options_get_real(current_state%options_database, 
'max_mu')
 
  880     fix_mu          = options_get_real(current_state%options_database, 
'fix_mu')
 
  882     l_aaut          = options_get_logical(current_state%options_database, 
'l_aaut')
 
  883     l_aacc          = options_get_logical(current_state%options_database, 
'l_aacc')
 
  884     l_aevp          = options_get_logical(current_state%options_database, 
'l_aevp')
 
  885     l_ased          = options_get_logical(current_state%options_database, 
'l_ased')
 
  886     l_warm          = options_get_logical(current_state%options_database, 
'l_warm')
 
  887     l_inuc          = options_get_logical(current_state%options_database, 
'l_inuc')
 
  888     l_iaut          = options_get_logical(current_state%options_database, 
'l_iaut')
 
  889     l_idep          = options_get_logical(current_state%options_database, 
'l_idep')
 
  890     l_iacw          = options_get_logical(current_state%options_database, 
'l_iacw')
 
  891     l_active_inarg2000 = options_get_logical(current_state%options_database, 
'l_active_inarg2000')
 
  892     l_separate_rain = options_get_logical(current_state%options_database, 
'l_separate_rain')
 
  893     l_sg            = options_get_logical(current_state%options_database, 
'l_sg')
 
  894     l_g             = options_get_logical(current_state%options_database, 
'l_g')
 
  895     l_passive       = options_get_logical(current_state%options_database, 
'l_passive')
 
  896     l_passive3m     = options_get_logical(current_state%options_database, 
'l_passive3m')
 
  897     l_limit_psd     = options_get_logical(current_state%options_database, 
'l_limit_psd')
 
  898     l_override_checks = options_get_logical(current_state%options_database, 
'l_override_checks')
 
  899     l_raci_g        = options_get_logical(current_state%options_database, 
'l_raci_g')
 
  900     l_onlycollect   = options_get_logical(current_state%options_database, 
'l_onlycollect')
 
  901     l_abelshipway   = options_get_logical(current_state%options_database, 
'l_abelshipway')
 
  902     l_cons          = options_get_logical(current_state%options_database, 
'l_cons')
 
  903     l_rain          = options_get_logical(current_state%options_database, 
'l_rain')
 
  904     l_sed_3mdiff    = options_get_logical(current_state%options_database, 
'l_sed_3mdiff')
 
  905     l_sed_icecloud_as_1m = options_get_logical(current_state%options_database, 
'l_sed_icecloud_as_1m')
 
  906     l_tidy_conserve_e = options_get_logical(current_state%options_database, 
'l_tidy_conserve_E')
 
  907     l_tidy_conserve_q = options_get_logical(current_state%options_database, 
'l_tidy_conserve_q')
 
  909     l_inhom_revp    = options_get_logical(current_state%options_database, 
'l_inhom_revp')
 
  910     l_pcond         = options_get_logical(current_state%options_database, 
'l_pcond')
 
  911     l_praut         = options_get_logical(current_state%options_database, 
'l_praut')
 
  912     l_pracw         = options_get_logical(current_state%options_database, 
'l_pracw')
 
  913     l_pracr         = options_get_logical(current_state%options_database, 
'l_pracr')
 
  914     l_prevp         = options_get_logical(current_state%options_database, 
'l_prevp')
 
  915     l_psedl         = options_get_logical(current_state%options_database, 
'l_psedl')
 
  916     l_psedr         = options_get_logical(current_state%options_database, 
'l_psedr')
 
  917     l_ptidy         = options_get_logical(current_state%options_database, 
'l_ptidy')
 
  918     l_ptidy2        = options_get_logical(current_state%options_database, 
'l_ptidy2')
 
  919     l_pinuc         = options_get_logical(current_state%options_database, 
'l_pinuc')
 
  920     l_pidep         = options_get_logical(current_state%options_database, 
'l_pidep')
 
  921     l_piacw         = options_get_logical(current_state%options_database, 
'l_piacw')
 
  922     l_psaut         = options_get_logical(current_state%options_database, 
'l_psaut')
 
  923     l_psdep         = options_get_logical(current_state%options_database, 
'l_psdep')
 
  924     l_psacw         = options_get_logical(current_state%options_database, 
'l_psacw')
 
  925     l_pgdep         = options_get_logical(current_state%options_database, 
'l_pgdep')
 
  926     l_pseds         = options_get_logical(current_state%options_database, 
'l_pseds')
 
  927     l_psedi         = options_get_logical(current_state%options_database, 
'l_psedi')
 
  928     l_psedg         = options_get_logical(current_state%options_database, 
'l_psedg')
 
  929     l_psaci         = options_get_logical(current_state%options_database, 
'l_psaci')
 
  930     l_praci         = options_get_logical(current_state%options_database, 
'l_praci')
 
  931     l_psacr         = options_get_logical(current_state%options_database, 
'l_psacr')
 
  932     l_pgacr         = options_get_logical(current_state%options_database, 
'l_pgacr')
 
  933     l_pgacw         = options_get_logical(current_state%options_database, 
'l_pgacw')
 
  934     l_pgaci         = options_get_logical(current_state%options_database, 
'l_pgaci')
 
  935     l_pgacs         = options_get_logical(current_state%options_database, 
'l_pgacs')
 
  936     l_piagg         = options_get_logical(current_state%options_database, 
'l_piagg')
 
  937     l_psagg         = options_get_logical(current_state%options_database, 
'l_psagg')
 
  938     l_pgagg         = options_get_logical(current_state%options_database, 
'l_pgagg')
 
  939     l_psbrk         = options_get_logical(current_state%options_database, 
'l_psbrk')
 
  940     l_pgshd         = options_get_logical(current_state%options_database, 
'l_pgshd')
 
  941     l_pihal         = options_get_logical(current_state%options_database, 
'l_pihal')
 
  942     l_psmlt         = options_get_logical(current_state%options_database, 
'l_psmlt')
 
  943     l_pgmlt         = options_get_logical(current_state%options_database, 
'l_pgmlt')
 
  944     l_phomr         = options_get_logical(current_state%options_database, 
'l_phomr')
 
  945     l_phomc         = options_get_logical(current_state%options_database, 
'l_phomc')
 
  946     l_pssub         = options_get_logical(current_state%options_database, 
'l_pssub')
 
  947     l_pgsub         = options_get_logical(current_state%options_database, 
'l_pgsub')
 
  948     l_pisub         = options_get_logical(current_state%options_database, 
'l_pisub')
 
  949     l_pimlt         = options_get_logical(current_state%options_database, 
'l_pimlt')
 
  954     type(model_state_type), 
target, 
intent(inout) :: current_state
 
  955     character(len=*), 
intent(in) :: name
 
  956     type(component_field_information_type), 
intent(out) :: field_information
 
  958     field_information%field_type=component_array_field_type
 
  959     field_information%data_type=component_double_data_type
 
  960     if (name .eq. 
"surface_precip") 
then 
  961        field_information%number_dimensions=2
 
  962        field_information%dimension_sizes(1)=current_state%local_grid%size(y_index)
 
  963        field_information%dimension_sizes(2)=current_state%local_grid%size(x_index)
 
  968        field_information%number_dimensions=3
 
  969        field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
 
  970        field_information%dimension_sizes(2)=current_state%local_grid%size(y_index)
 
  971        field_information%dimension_sizes(3)=current_state%local_grid%size(x_index)
 
  974     field_information%enabled=.true.    
 
  983     type(model_state_type), 
target, 
intent(inout) :: current_state
 
  984     character(len=*), 
intent(in) :: name
 
  985     type(component_field_value_type), 
intent(out) :: field_value
 
  989     if (name .eq. 
"surface_precip") 
then 
  990        allocate(field_value%real_2d_array(current_state%local_grid%size(y_index), &
 
  991             current_state%local_grid%size(x_index)))
 
  993     else if (name .eq. 
"condensation_rate") 
then 
  994        allocate(field_value%real_3d_array(current_state%local_grid%size(z_index),  &
 
  995             current_state%local_grid%size(y_index),                                &
 
  996             current_state%local_grid%size(x_index)))
 
  997        field_value%real_3d_array(:,:,:) = casim_monc_dgs % pcond(:,:,:)