Ignore:
Timestamp:
11/10/17 17:04:49 (7 years ago)
Author:
dumas
Message:

determin_marais is now called only when isynchro=1 | sortie_hz_multi and hz_output are suppressed | step_time_loop_avec_iterbeta updated as step_time_loop

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/SOURCES/steps_time_loop_avec_iterbeta.f90

    r121 r157  
    2323  use diagno_mod 
    2424  use bilan_eau_mod 
    25  
    26  
    2725!  use track_debug  
     26 
    2827 
    2928  implicit none 
     
    5857 
    5958     call icethick3 
    60  
    6159     call flottab 
    62  
    6360     call calving 
    64       
    6561     call ablation_bord 
    66       
    6762     call bilan_eau 
    68      if (isynchro.eq.1) then 
    69          call shortoutput 
    70          diff_H = 0. 
    71          Bm_dtt(:,:) = 0. 
    72          bmelt_dtt(:,:) = 0. 
    73          calv_dtt(:,:)=0. 
    74          ablbord_dtt(:,:)=0. 
    75          diff_H_2D(:,:)=0. 
    76      endif 
    77          
     63     call bilan_flux_output 
    7864     call flottab 
    79       
    80      if (itracebug.eq.1)  call tracebug('apres calving') 
     65     if (isynchro.eq.1.or.nt.eq.1) call determin_marais 
     66     if (itracebug.eq.1)  call tracebug('apres marais') 
    8167 
    8268     ! new calculation of ice surface elevation 
     
    120106  !==================================================================== 
    121107 
    122   ! horizontal plan snapshots 
    123   !------------------------------------------------------------------ 
    124   !  Premiere partie des sorties horizontales 
    125  
    126   !     if (mod(abs(dble(TIME)),dble(DTSORTIE)).lt.dble(dtmin)) then 
    127   ! 
    128  
    129  
    130   if ((mod(abs(TIME),dtt).lt.dtmin).or.(isynchro.eq.1)) then 
    131      isynchro=1 
    132  
    133      !  sorties hz  
    134      call testsort_time(real(time)) 
    135      if (iglob_hz.eq.1) then 
    136         call sortie_hz_multi   ! pour les variables déclarées dans 3D 
    137         !              call hz_output(real(time)) 
    138      endif 
    139  
    140   else 
    141      iglob_hz=0 
    142  
    143   endif 
    144  
    145  
    146108  !   vertical plan snapshots (profiles) 
    147109  !------------------------------------------------------------------ 
     
    150112  !     .or.(mod(abs(dble(TIME)),dble(DTPROFILE)).lt.dble(dtmin)) & 
    151113  !     .or.(abs(TIME-TEND).lt.dtmin)) then 
    152  
    153      !        call sortieprofile() 
    154  
     114  !  call sortieprofile() 
    155115  !endif 
    156116 
     
    160120  call testsort_time_ncdf(time) 
    161121  if (iglob_ncdf .EQ. 1) call sortie_ncdf_cat 
    162  
     122  if (isynchro.eq.1) then 
     123    call shortoutput 
     124    diff_H = 0. 
     125    Bm_dtt(:,:) = 0. 
     126    bmelt_dtt(:,:) = 0. 
     127    calv_dtt(:,:)=0. 
     128    ablbord_dtt(:,:)=0. 
     129    diff_H_2D(:,:)=0. 
     130    grline_dtt(:,:)=0. 
     131  endif 
    163132 
    164133  !   sortie compteur tous les dtcpt ans  
    165134  !------------------------------------------------------------------ 
    166      !iout == 1 sortie cptr 
    167      !iout == 2 sortie nc 
    168     if (itracebug.eq.1)  call tracebug('dans steps_time_loop avant call out_recovery ') 
    169  
    170      call out_recovery(iout) 
     135  !iout == 1 sortie cptr 
     136  !iout == 2 sortie nc 
     137  if (itracebug.eq.1)  call tracebug('dans steps_time_loop avant call out_recovery ') 
     138 
     139  call out_recovery(iout) 
    171140 
    172141  ! end of outputs 
     
    295264     ! update values in the structures Geom_g, Temperature_g, ... 
    296265 
    297      calc_temp:     if ((nt.gt.2).and.(geoplace(1:5).ne.'mism3')) then 
     266!afq     calc_temp:     if ((nt.gt.2).and.(geoplace(1:5).ne.'mism3')) then 
     267     calc_temp:     if (geoplace(1:5).ne.'mism3') then 
    298268        if (itracebug.eq.1)  call tracebug('avant appel icetemp') 
    299269        call icetemp 
     
    443413          iter_visco = 10 
    444414        else 
    445            iter_visco = 2 
     415          iter_visco = 2 
    446416        end if 
    447417  
Note: See TracChangeset for help on using the changeset viewer.