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.f90

    r150 r157  
    6161     call ablation_bord 
    6262     call bilan_eau 
    63      call bilan_flux_output 
    64  
    65 !~      if (isynchro.eq.1) then 
    66 !~          call shortoutput 
    67 !~          diff_H = 0. 
    68 !~          Bm_dtt(:,:) = 0. 
    69 !~          bmelt_dtt(:,:) = 0. 
    70 !~          calv_dtt(:,:)=0. 
    71 !~          ablbord_dtt(:,:)=0. 
    72 !~          diff_H_2D(:,:)=0. 
    73 !~          grline_dtt(:,:)=0. 
    74 !~       endif 
    75       
     63     call bilan_flux_output      
    7664     call flottab 
    77  
    78      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') 
    7967 
    8068     ! new calculation of ice surface elevation 
     
    118106  !==================================================================== 
    119107 
    120   ! horizontal plan snapshots 
    121   !------------------------------------------------------------------ 
    122   !  Premiere partie des sorties horizontales 
    123  
    124   !     if (mod(abs(dble(TIME)),dble(DTSORTIE)).lt.dble(dtmin)) then 
    125   ! 
    126  
    127  
    128   if ((mod(abs(TIME),dtt).lt.dtmin).or.(isynchro.eq.1)) then 
    129      isynchro=1 
    130  
    131      !  sorties hz  
    132      call testsort_time(real(time)) 
    133      if (iglob_hz.eq.1) then 
    134         call sortie_hz_multi   ! pour les variables déclarées dans 3D 
    135         !              call hz_output(real(time)) 
    136      endif 
    137  
    138   else 
    139      iglob_hz=0 
    140  
    141   endif 
    142  
    143  
    144108  !   vertical plan snapshots (profiles) 
    145109  !------------------------------------------------------------------ 
     
    148112  !     .or.(mod(abs(dble(TIME)),dble(DTPROFILE)).lt.dble(dtmin)) & 
    149113  !     .or.(abs(TIME-TEND).lt.dtmin)) then 
    150  
    151      !        call sortieprofile() 
    152  
     114  !  call sortieprofile() 
    153115  !endif 
    154116 
     
    357319        if (itracebug.eq.1)  call tracebug(' Dans spinup_3_bed') 
    358320 
    359 !        if ((nbed.eq.1).and.nt.ne.1.and.isynchro.eq.1) then 
    360          if ((nbed.eq.1).and.nt.ne.1.and.isynchro.eq.1.and.(mod(abs(TIME),50.).lt.dtmin)) then 
     321        if ((nbed.eq.1).and.nt.ne.1.and.isynchro.eq.1.and.(mod(abs(TIME),50.).lt.dtmin)) then 
    361322           call bedrock                                              !  bedrock adjustment 
    362323        endif 
     
    449410        else if ((icompteur.ne.1).and.(nt.le.1)) then  ! initialisation avec reprise partielle  
    450411                                                       ! ou nulle du vecteur d' etat 
    451           iter_visco =  10 
     412          iter_visco = 10 
    452413        else 
    453            iter_visco = 2 
     414          iter_visco = 2 
    454415        end if 
    455416  
    456 !cdc        iter_visco= 10                                 ! warning, test sur l'impact iteration dragging et visco  
    457                                                        ! Cat 18 janv 2013 
    458417 
    459418           do m=1,iter_visco               
    460419              call diagnoshelf 
    461               call  mix_SIA_L1   
    462               call strain_rate() 
     420              call mix_SIA_L1   
     421              call strain_rate 
    463422              if (iter_beta.eq.0) then 
    464423                call dragging           
Note: See TracChangeset for help on using the changeset viewer.