Changeset 59


Ignore:
Timestamp:
04/29/16 15:25:33 (8 years ago)
Author:
aquiquet
Message:

Introduction of Betamax_2d for all geoms / call to sliding removed / Drastic change in dragging module based on effective pressure (no curvature but slow_ssa zones)

Location:
trunk/SOURCES
Files:
12 edited
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/SOURCES/3D-physique-gen_mod.f90

    r37 r59  
    253253  real, dimension(nx,ny) :: coef_drag   !< coefficient de la loi de friction non lineaire : depend de la valeur de alpha_drag 
    254254                                        !< si alpha_drag = 1, coef_drag = drag_centre   
     255  real, dimension(nx,ny) :: betamax_2d  !< (Pa) frottement maxi sous les streams 
    255256  ! 
    256257  real,dimension(nx,ny) :: BM           !< mass balance   'o' 
  • trunk/SOURCES/Draggings_modules/beta_iter_vitbil_mod.f90

    r8 r59  
    9999    betamy_file = trim(dirnameinp)//trim(betamy_file) 
    100100    betamax = beta_limgz 
    101  
     101    betamax_2d(:,:) = betamax 
    102102 
    103103!    call lect_input(1,'beta_c',1,drag_centre,beta_c_file,'') 
  • trunk/SOURCES/Draggings_modules/dragging_prescr_beta_buoyency_mod.f90

    r4 r59  
    100100    betamy_file = trim(dirnameinp)//trim(betamy_file) 
    101101    betamax = beta_limgz 
     102    betamax_2d(:,:) = betamax 
    102103 
    103104!  read the beta value on centered and staggered grids 
  • trunk/SOURCES/Draggings_modules/dragging_prescr_beta_mod.f90

    r4 r59  
    8282    betamy_file = trim(dirnameinp)//trim(betamy_file) 
    8383    betamax = beta_limgz 
     84    betamax_2d(:,:) = betamax 
    8485 
    8586!  read the beta value on centered and staggered grids 
  • trunk/SOURCES/Draggings_modules/dragging_prescr_beta_nolin_mod.f90

    r4 r59  
    169169    betamy_file = trim(dirnameinp)//trim(betamy_file) 
    170170    betamax = beta_limgz 
     171    betamax2d(:,:) = betamax 
    171172 
    172173 
  • trunk/SOURCES/GrIce2sea_files/climat_GrIce2sea_years_perturb_mod.f90

    r55 r59  
    126126  bm(:,:)  = tab(:,:) * coef_smb_unit 
    127127 
    128 !  where ((H(:,:).lt.1.).and.(Bsoc(:,:).gt.0.)) 
    129 !     bm(:,:) = bm(:,:) - 5.                     ! pour faire un masque a l'exterieur du Groenland actuel 
    130 !  end where 
    131  
     128  !where ((H(:,:).lt.1.).and.(Bsoc(:,:).gt.0.)) 
     129  !   bm(:,:) = bm(:,:) - 5.                     ! pour faire un masque a l'exterieur du Groenland actuel 
     130  !end where 
     131  where ((H(:,:).lt.1.).and.(Bsoc(:,:).gt.0.).and.(bm(:,:).gt.0.)) 
     132     bm(:,:) = -0.01 
     133  end where 
    132134!cdc test debug Hemin15 et Greeneem15 
    133135!  where (bm(:,:).lt.-1000) bm(:,:)=0. 
    134   where (bm(:,:).eq.0) bm(:,:)=-10. !afq 
     136  where (bm(:,:).eq.0) bm(:,:)=-5. !afq 
    135137   
    136138  acc(:,:) = 0. 
     
    413415        ! aurel marion dufresne: we might want to decrease the SMB during glacials..? 
    414416        if (pertsmb.eq.1) then 
    415            !bm(:,:) = bm_0(:,:) * exp( rapsmb *(Tann(:,:)-Ta0(:,:))) 
    416            ! afq, to match present day smb, I don't want to take S-elev feedb. into account 
    417            bm(:,:) = bm_0(:,:) * exp( rapsmb * Tafor ) 
     417           bm(:,:) = bm_0(:,:) * exp( rapsmb *(Tann(:,:)-Ta0(:,:))) 
     418           if (Tafor.lt.0.) then 
     419              where(bm(:,:).lt.0.) bm(:,:)=min(bm(:,:)-Tafor*0.05,1.) !10 degrees less give 0.5 meter more ? 
     420           end if 
    418421        end if 
    419422         
  • trunk/SOURCES/Makefile.grisli-gfortran.inc

    r57 r59  
    7373        dragging_hwatermax_0.2_mod.o dragging_calc_beta_mod.o  \ 
    7474        dragging_hwat-contigu_mod.o dragging_hwat_contmaj_mod.o \ 
    75         dragging_hwat_sedim_mod.o dragging_neff_contmaj_mod.o \ 
     75        dragging_hwat_sedim_mod.o dragging_neff_slope_mod.o \ 
    7676        calving_frange.o no_calving.o no_lakes.o \ 
    7777        out_profile_mod.o printtable_mod.o mix-SIA-L1_mod.o \ 
     
    714714        $(FT) dragging_hwat_sedim_mod.f90 
    715715 
    716 dragging_neff_contmaj_mod.o : dragging_neff_contmaj_mod.f90 
    717         $(FT) dragging_neff_contmaj_mod.f90 
     716dragging_neff_slope_mod.o : dragging_neff_slope_mod.f90 
     717        $(FT) dragging_neff_slope_mod.f90 
    718718 
    719719dragging_calc_beta_mod.o : Antarctique_general_files/dragging_calc_beta_mod.f90 
  • trunk/SOURCES/Makefile.grisli.inc

    r57 r59  
    7373        dragging_hwatermax_0.2_mod.o dragging_calc_beta_mod.o  \ 
    7474        dragging_hwat-contigu_mod.o dragging_hwat_contmaj_mod.o \ 
    75         dragging_hwat_sedim_mod.o dragging_neff_contmaj_mod.o \ 
     75        dragging_hwat_sedim_mod.o dragging_neff_slope_mod.o \ 
    7676        calving_frange.o no_calving.o no_lakes.o \ 
    7777        out_profile_mod.o printtable_mod.o mix-SIA-L1_mod.o \ 
     
    718718        $(FT) dragging_hwat_sedim_mod.f90 
    719719 
    720 dragging_neff_contmaj_mod.o : dragging_neff_contmaj_mod.f90 
    721         $(FT) dragging_neff_contmaj_mod.f90 
     720dragging_neff_slope_mod.o : dragging_neff_slope_mod.f90 
     721        $(FT) dragging_neff_slope_mod.f90 
    722722 
    723723dragging_calc_beta_mod.o : Antarctique_general_files/dragging_calc_beta_mod.f90 
     
    17191719        $(mod_communs) \ 
    17201720        $(mod_clim_tof) \ 
    1721         $(mod_no_tracers) \ 
     1721        $(mod_tracers) \ 
    17221722        $(mod_ell) $(Liste_greeneem15) \ 
    17231723        $(diagnoshelf) \ 
  • trunk/SOURCES/New-remplimat/remplimat-shelves-tabTu.f90

    r4 r59  
    412412 
    413413where (flgzmx(:,:)) 
    414    frotmx(:,:)=min(abs(betamx(:,:)),betamax) 
     414   frotmx(:,:)=min(abs(betamx(:,:)),betamax_2d(:,:)) 
    415415elsewhere 
    416416   frotmx(:,:)=0 
     
    418418 
    419419where (flgzmy(:,:)) 
    420    frotmy(:,:)=min(abs(betamy(:,:)),betamax) 
     420   frotmy(:,:)=min(abs(betamy(:,:)),betamax_2d(:,:)) 
    421421elsewhere 
    422422   frotmy(:,:)=0 
  • trunk/SOURCES/branche-Cat-spinup-dec2011/dragging_prescr_beta_mod.f90

    r4 r59  
    9999    betamy_file = trim(dirnameinp)//trim(betamy_file) 
    100100    betamax = beta_limgz 
     101    betamax_2d(:,:) = betamax 
    101102 
    102103!  read the beta value on centered and staggered grids 
  • trunk/SOURCES/diffusiv-polyn-0.6.f90

    r4 r59  
    6868call slope_surf 
    6969 
    70 call sliding     ! au sens vitesse de glissement 
     70!call sliding     ! au sens vitesse de glissement, afq, commented 21 apr 16 
    7171 
    7272!  le glissement est maintenant dans un module a part choisi dans le module choix 
  • trunk/SOURCES/dragging_neff_slope_mod.f90

    r58 r59  
    1616!< 
    1717 
    18 module dragging_neff_contmaj 
     18module dragging_neff_slope 
    1919 
    2020! Defini les zones de stream avec : 
     
    2525use module3d_phy 
    2626use param_phy_mod 
     27use interface_input 
     28use io_netcdf_grisli 
    2729 
    2830implicit none 
     
    3133logical,dimension(nx,ny) :: fleuve 
    3234logical,dimension(nx,ny) :: cote 
    33  
     35logical,dimension(nx,ny) :: slowssa ! not actual stream, but ssa used as Ub 
     36logical,dimension(nx,ny) :: slowssamx 
     37logical,dimension(nx,ny) :: slowssamy 
     38 
     39real,dimension(nx,ny) :: hires_slope ! slope comupted on a high resolution topography 
     40character(len=100) :: slope_fich     ! fichier grille 
     41character(len=100) :: file_ncdf      !< fichier netcdf issue des fichiers .dat 
    3442 
    3543real :: valmax 
     
    6674implicit none 
    6775  
    68 namelist/drag_neff_cont/hwatstream,cf,betamax,betamin,toblim,seuil_neff,coef_gz,coef_ile 
     76namelist/drag_neff_slope/hwatstream,cf,betamax,betamin,toblim,tostick,seuil_neff,coef_gz,coef_ile,slope_fich 
    6977 
    7078if (itracebug.eq.1)  call tracebug(' dragging avec hwatermax') 
     
    7886 
    7987rewind(num_param)        ! pour revenir au debut du fichier param_list.dat 
    80 read(num_param,drag_neff_cont) 
     88read(num_param,drag_neff_slope) 
    8189 
    8290write(num_rep_42,428)'!___________________________________________________________'  
     
    8896write(num_rep_42,*) 'betamin         = ', betamin 
    8997write(num_rep_42,*) 'toblim          = ', toblim 
     98write(num_rep_42,*) 'tostick          = ', tostick 
    9099write(num_rep_42,*) 'seuil_neff      = ', seuil_neff 
    91100write(num_rep_42,*) 'coef_gz         = ', coef_gz 
    92101write(num_rep_42,*) 'coef_ile        = ', coef_ile 
     102write(num_rep_42,'(A,A)') 'slope_fich = ', slope_fich   
    93103write(num_rep_42,*)'/'                             
    94104write(num_rep_42,428) '! hwatstream (m) :  critere de passage en stream en partant de la cote' 
     
    98108write(num_rep_42,428) '! betamin : (Pa) frottement mini sous les streams ' 
    99109write(num_rep_42,428) '! toblim : (Pa)  pour les iles ' 
     110write(num_rep_42,428) '! tostick : (Pa)  pour les points non flgzmx ' 
    100111write(num_rep_42,428) '! seuil_neff (Pa) seuil sur la pression effective pour avoir glissement' 
    101112write(num_rep_42,428) '! coef_gz : coef frottement zones stream std' 
     
    103114write(num_rep_42,*) 
    104115 
    105 tostick=1.e5   ! valeurs pour les points non flgzmx 
     116!tostick=1.e5   ! valeurs pour les points non flgzmx 
    106117tob_ile=betamax/2. 
    107118moteurmax=toblim 
    108119 
     120! betamax_2d depends on sub-grid slopes. 
     121slope_fich=trim(dirnameinp)//trim(slope_fich) 
     122call lect_input(1,'slope',1,hires_slope(:,:),slope_fich,file_ncdf) 
     123 
     124write (*,*) slope_fich 
     125write (*,*) hires_slope(:,:) 
     126write (*,*) "fin test" 
     127! from slopes, we create an index between 0 & 1 
     128! 1 is very mountainous, 0 is flat 
     129hires_slope(:,:)=(max(min(hires_slope(:,:),2000.),500.)-500.)/1500. 
     130! now we compute the actual betamax used by the remplimat routines 
     131! /!\ the slope is used to modify the beta where we have a temperate base, 
     132! but NO ice stream... -> Slow SSA zone (SSA used to compute Ub) 
     133betamax_2d(:,:)=max ( tostick * (1. - (1 - betamax / tostick ) * hires_slope(:,:)) , betamax ) 
     134do j=1,ny 
     135   do i=1,nx 
     136      write(18745,*) betamax_2d (i,j) 
     137   enddo 
     138enddo 
     139 
    109140!------------------------------------------------------------------- 
    110141! masque stream 
    111  
    112142      mstream_mx(:,:)=1 
    113143      mstream_my(:,:)=1 
     
    185215neff(nx,:)=1.e5 
    186216 
    187  
    188 fleuve_maj: do j=2,ny-1   
    189 ifleuve:   do i=2,nx-1                      
    190  
    191 cote_detect :  if (cote(i,j)) then 
    192          idep=i 
    193          jdep=j 
    194  
    195          if (socle_cry(i,j).lt.0.) then    ! dans une vallee 
    196             fleuve(i,j)=.true.  
    197          else 
    198             cote(i,j)=.false. 
    199             cycle ifleuve 
    200          endif 
    201  
    202 suit : do l=1,lmax         ! debut de la boucle de suivi, lmax longueur maxi des fleuves 
    203            i_moins1=max(idep-1,2) 
    204            j_moins1=max(jdep-1,1) 
    205            i_plus1=min(idep+1,nx) 
    206            j_plus1=min(jdep+1,ny) 
    207             
    208 ! recherche du max en suivant le socle le plus profond 
    209 ! * en excluant les points flottants 
    210 ! * et ceux qui sont deja tagges fleuves 
    211  
    212            valmax=1000. 
    213  
    214            do jloc=j_moins1,j_plus1 
    215               do iloc=i_moins1,i_plus1 
    216   
    217                  if ((B(iloc,jloc).lt.valmax)      &  
    218                       .and.(.not.flot(iloc,jloc))  & 
    219                       .and.(.not.fleuve(iloc,jloc)).and.(socle_cry(iloc,jloc).lt.cry_lim)) then 
    220                     imax=iloc 
    221                     jmax=jloc 
    222                     valmax=B(iloc,jloc) 
    223                  endif 
    224               end do 
    225            end do 
    226  
    227          if ((hwater(imax,jmax).gt.hwatstream).and.(socle_cry(i,j).lt.cry_lim)) then 
    228             fleuve(imax,jmax)=.true. 
    229             idep=imax 
    230             jdep=jmax 
    231          else 
    232             fleuve(imax,jmax)=.false. 
    233             exit suit 
    234          end if 
    235   
    236       end do suit 
    237  
    238    end if cote_detect 
    239  
    240 end do ifleuve 
    241 end do fleuve_maj 
     217!!$ 
     218!!$fleuve_maj: do j=2,ny-1   
     219!!$ifleuve:   do i=2,nx-1                      
     220!!$ 
     221!!$cote_detect :  if (cote(i,j)) then 
     222!!$         idep=i 
     223!!$         jdep=j 
     224!!$ 
     225!!$         if (socle_cry(i,j).lt.0.) then    ! dans une vallee 
     226!!$            fleuve(i,j)=.true.  
     227!!$         else 
     228!!$            cote(i,j)=.false. 
     229!!$            cycle ifleuve 
     230!!$         endif 
     231!!$ 
     232!!$suit : do l=1,lmax         ! debut de la boucle de suivi, lmax longueur maxi des fleuves 
     233!!$           i_moins1=max(idep-1,2) 
     234!!$           j_moins1=max(jdep-1,1) 
     235!!$           i_plus1=min(idep+1,nx) 
     236!!$           j_plus1=min(jdep+1,ny) 
     237!!$            
     238!!$! recherche du max en suivant le socle le plus profond 
     239!!$! * en excluant les points flottants 
     240!!$! * et ceux qui sont deja tagges fleuves 
     241!!$ 
     242!!$           valmax=1000. 
     243!!$ 
     244!!$           do jloc=j_moins1,j_plus1 
     245!!$              do iloc=i_moins1,i_plus1 
     246!!$  
     247!!$                 if ((B(iloc,jloc).lt.valmax)      &  
     248!!$                      .and.(.not.flot(iloc,jloc))  & 
     249!!$                      .and.(.not.fleuve(iloc,jloc)).and.(socle_cry(iloc,jloc).lt.cry_lim)) then 
     250!!$                    imax=iloc 
     251!!$                    jmax=jloc 
     252!!$                    valmax=B(iloc,jloc) 
     253!!$                 endif 
     254!!$              end do 
     255!!$           end do 
     256!!$ 
     257!!$         if ((hwater(imax,jmax).gt.hwatstream).and.(socle_cry(i,j).lt.cry_lim)) then 
     258!!$            fleuve(imax,jmax)=.true. 
     259!!$            idep=imax 
     260!!$            jdep=jmax 
     261!!$         else 
     262!!$            fleuve(imax,jmax)=.false. 
     263!!$            exit suit 
     264!!$         end if 
     265!!$  
     266!!$      end do suit 
     267!!$ 
     268!!$   end if cote_detect 
     269!!$ 
     270!!$end do ifleuve 
     271!!$end do fleuve_maj 
    242272 
    243273! aurel, we add the neff threshold: 
     
    255285end do 
    256286 
    257 ! pas de fleuve dans les endroits trop en pente 
    258  
    259 !fleuvemx(:,:)=fleuvemx(:,:).and.(abs(rog*Hmx(:,:)*sdx(:,:)).lt.toblim) 
    260 !fleuvemy(:,:)=fleuvemy(:,:).and.(abs(rog*Hmy(:,:)*sdy(:,:)).lt.toblim) 
     287! we look for the warm based points that will not be treated as stream (ub from SSA): 
     288slowssa(:,:)=.false. 
     289slowssamx(:,:)=.false. 
     290slowssamy(:,:)=.false. 
     291do  j=1,ny 
     292   do i=1,nx 
     293      !if ((not(flot(i,j))).and.(hwater(i,j).gt.0.1)) slowssa(i,j)=.true. 
     294      if ((not(flot(i,j))).and.(ibase(i,j).ne.1).and.(H(i,j).gt.1.)) slowssa(i,j)=.true. 
     295   end do 
     296end do 
     297do j=1,ny-1 
     298   do i=1,nx-1 
     299      if (slowssa(i,j)) then 
     300         slowssamx(i,j)=.true. 
     301         slowssamx(i+1,j)=.true. 
     302         slowssamy(i,j)=.true. 
     303         slowssamy(i,j+1)=.true. 
     304      end if 
     305   end do 
     306end do 
    261307 
    262308do j=1,ny 
    263309   do i=1,nx 
    264       if ((.not.ilemx(i,j)).and.(fleuvemx(i,j))) gzmx(i,j)=.true.  
    265  
     310 
     311      ! the actual streams and the warm based points are gzmx now: 
     312      if ( ((.not.ilemx(i,j)).and.(fleuvemx(i,j))) .or. ((.not.ilemx(i,j)).and.(slowssamx(i,j))) ) gzmx(i,j)=.true.  
     313 
     314       
    266315! calcul du frottement basal (ce bloc etait avant dans neffect) 
    267316 
     
    269318         betamx(i,j)=cf*neffmx(i,j)  
    270319         betamx(i,j)=min(betamx(i,j),betamax) 
    271       else if ((gzmx(i,j)).and.(.not.cotemx(i,j))) then  ! stream 
    272          betamx(i,j)=cf*neffmx(i,j)*coef_gz 
    273          betamx(i,j)=min(betamx(i,j),betamax) 
    274          betamx(i,j)=max(betamx(i,j),betamin) 
    275  
    276          !aurel, function of betamax and not 1500 as before: 
    277          if (cf*neffmx(i,j).gt.betamax*2.) then 
    278             gzmx(i,j)=.false. 
    279             betamx(i,j)=tostick 
     320 
     321      else if ((gzmx(i,j)).and.(.not.cotemx(i,j))) then ! tous les points SSA 
     322 
     323         if (fleuvemx(i,j)) then                 ! the actual streams 
     324            betamx(i,j)=cf*neffmx(i,j)*coef_gz 
     325            betamx(i,j)=min(betamx(i,j),betamax) 
     326            betamx(i,j)=max(betamx(i,j),betamin) 
     327 
     328            if (cf*neffmx(i,j).gt.betamax*2.) then  ! a stream that's becoming grounded... 
     329               if (slowssamx(i,j)) then 
     330                   
     331               else 
     332                  gzmx(i,j)=.false. 
     333                  betamx(i,j)=betamax_2d(i,j) !tostick 
     334               endif 
     335            endif 
     336 
     337         else                    ! not an actual stream, SSA is used to compute Ub 
     338            betamx(i,j)=betamax_2d(i,j) 
    280339         endif 
    281  
     340          
    282341      else if (ilemx(i,j)) then 
    283342         betamx(i,j)=cf*neffmx(i,j)*coef_ile  
     
    286345         betamx(i,j)=0. 
    287346      else                                         ! grounded, SIA 
    288          betamx(i,j)=tostick                       ! frottement glace posee (1 bar) 
     347         betamx(i,j)=betamax_2d(i,j) !tostick                       ! frottement glace posee (1 bar) 
    289348      endif 
    290349 
     
    292351end do 
    293352 
    294  
    295 do j=1,ny                  ! le noeud 1 n'est pas attribue 
    296    do i=1,nx    
    297  
    298       if ((.not.ilemy(i,j)).and.(fleuvemy(i,j))) gzmy(i,j)=.true.  
    299  
    300  
    301  ! calcul du frottement basal (ce bloc etait avant dans neffect) 
     353do j=1,ny 
     354   do i=1,nx 
     355 
     356      ! the actual streams and the warm based points are gzmx now: 
     357      if ( ((.not.ilemy(i,j)).and.(fleuvemy(i,j))) .or. ((.not.ilemy(i,j)).and.(slowssamy(i,j))) ) gzmy(i,j)=.true.  
     358 
     359       
     360! calcul du frottement basal (ce bloc etait avant dans neffect) 
    302361 
    303362      if (cotemy(i,j)) then                        ! point cotier 
    304363         betamy(i,j)=cf*neffmy(i,j)  
    305364         betamy(i,j)=min(betamy(i,j),betamax) 
    306       else if ((gzmy(i,j)).and.(.not.cotemy(i,j))) then  ! stream 
    307          betamy(i,j)=cf*neffmy(i,j)*coef_gz 
    308          betamy(i,j)=min(betamy(i,j),betamax) 
    309          betamy(i,j)=max(betamy(i,j),betamin) 
    310  
    311          !aurel, function of betamax and not 1500 as before: 
    312          if (cf*neffmy(i,j).gt.betamax*2.) then 
    313             gzmy(i,j)=.false. 
    314             betamy(i,j)=tostick 
     365 
     366      else if ((gzmy(i,j)).and.(.not.cotemy(i,j))) then ! tous les points SSA 
     367 
     368         if (fleuvemy(i,j)) then                 ! the actual streams 
     369            betamy(i,j)=cf*neffmy(i,j)*coef_gz 
     370            betamy(i,j)=min(betamy(i,j),betamax) 
     371            betamy(i,j)=max(betamy(i,j),betamin) 
     372 
     373            if (cf*neffmy(i,j).gt.betamax*2.) then  ! a stream that's becoming grounded... 
     374               if (slowssamy(i,j)) then 
     375                   
     376               else 
     377                  gzmy(i,j)=.false. 
     378                  betamy(i,j)=betamax_2d(i,j) !tostick 
     379               endif 
     380            endif 
     381 
     382         else                    ! not an actual stream, SSA is used to compute Ub 
     383            betamy(i,j)=betamax_2d(i,j) 
    315384         endif 
    316  
     385          
    317386      else if (ilemy(i,j)) then 
    318          betamy(i,j)=cf*neffmy(i,j)*coef_ile 
    319          betamy(i,j)=min(betamy(i,j),tob_ile)      
     387         betamy(i,j)=cf*neffmy(i,j)*coef_ile  
     388         betamy(i,j)=min(betamy(i,j),tob_ile)        
    320389      else if (flotmy(i,j)) then     ! flottant ou ile 
    321390         betamy(i,j)=0. 
    322       else                               ! grounded, SIA 
    323          betamy(i,j)=tostick             ! frottement glace posee 
     391      else                                         ! grounded, SIA 
     392         betamy(i,j)=betamax_2d(i,j) !tostick                       ! frottement glace posee (1 bar) 
    324393      endif 
    325        
     394 
     395   end do 
     396end do 
     397 
     398 
     399do j=2,ny-1 
     400   do i=2,nx-1 
     401      beta_centre(i,j) = ((betamx(i,j)+betamx(i+1,j)) & 
     402          + (betamy(i,j)+betamy(i,j+1)))*0.25 
    326403   end do 
    327404end do 
     
    371448end subroutine dragging 
    372449 
    373 end module dragging_neff_contmaj 
    374  
     450end module dragging_neff_slope 
     451 
  • trunk/SOURCES/initial-0.3.f90

    r34 r59  
    121121  call init_diagno     ! initialisation de la resolution equation elliptique vitesses  
    122122 
    123   call init_sliding    ! initialisation du glissement 
     123  !call init_sliding    ! initialisation du glissement, afq, commented 21 apr 16 
    124124 
    125125  call init_spinup     ! initialisation du spinup 
Note: See TracChangeset for help on using the changeset viewer.