Ignore:
Timestamp:
05/09/17 10:20:19 (7 years ago)
Author:
aquiquet
Message:

Schoof: back force in x/y from ramollos.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/SOURCES/furst_schoof_mod.f90

    r97 r104  
    1111real :: alpha_flot 
    1212integer :: gr_select 
    13 real,dimension(nx,ny) :: back_force 
     13real,dimension(nx,ny) :: back_force_x 
     14real,dimension(nx,ny) :: back_force_y 
    1415 
    1516contains 
     
    3536  ! choix Tsai (loi de Coulomb) ou Schoof (loi de Weertman) 
    3637  alpha_flot= ro/row 
    37   back_force(:,:)=0.1 
     38  back_force_x(:,:)=0.1 
     39  back_force_y(:,:)=0.1 
    3840   
    3941end subroutine init_furst_schoof   
     
    6870   
    6971  real,dimension(nx,ny) :: archimtab 
     72   
     73  real,dimension(nx,ny) :: imx_diag_in 
    7074 
    7175  phi_prescr_tabx=0. 
     
    8286  archimtab(:,:) = Bsoc(:,:)+H(:,:)*alpha_flot -sealevel 
    8387 
     88  imx_diag_in(:,:) = imx_diag(:,:) 
     89   
    8490  ! detection des noeuds grounding line 
    8591  do j= 3,ny-3 
     
    98104 
    99105              if (gr_select.eq.1) then ! flux de Tsai 
    100                  call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),back_force(i-1,j),phi_prescr) 
     106                 call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),back_force_x(i-1,j),phi_prescr) 
    101107              else 
    102108                 print*,'ATTENTION FLUX AUTRE QUE TSAI NON IMPLEMENTE' 
     
    167173              Hglx_tab(i,j)=Hgl 
    168174              if (gr_select.eq.1) then ! flux de Tsai 
    169                  call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),back_force(i+1,j),phi_prescr) 
     175                 call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),back_force_x(i+1,j),phi_prescr) 
    170176              else 
    171177                 print*,'ATTENTION FLUX AUTRE QUE TSAI NON IMPLEMENTE' 
     
    232238              Hgly_tab(i,j)=Hgl 
    233239              if (gr_select.eq.1) then ! flux de Tsai 
    234                  call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),back_force(i,j-1),phi_prescr) 
     240                 call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),back_force_y(i,j-1),phi_prescr) 
    235241              else 
    236242                 print*,'ATTENTION FLUX AUTRE QUE TSAI NON IMPLEMENTE' 
     
    293299              Hgly_tab(i,j)=Hgl 
    294300              if (gr_select.eq.1) then ! flux de Tsai 
    295                  call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),back_force(i,j+1),phi_prescr) 
     301                 call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),back_force_y(i,j+1),phi_prescr) 
    296302              else 
    297303                 print*,'ATTENTION FLUX AUTRE QUE TSAI NON IMPLEMENTE' 
     
    350356     end do 
    351357  end do 
    352   where (countx(:,:).ne.0) uxbar(:,:)=uxbartemp(:,:)/countx(:,:) 
    353   where (county(:,:).ne.0) uybar(:,:)=uybartemp(:,:)/county(:,:) 
    354    
    355   uxbar(:,:)= max(min(uxbar(:,:),V_limit),-V_limit) 
    356   uybar(:,:)= max(min(uybar(:,:),V_limit),-V_limit) 
    357    
     358 
     359  ! afq -- if we discard the points with multiple fluxes coming, uncomment: 
     360  !where (countx(:,:).ge.2) 
     361  !   uxbartemp(:,:)=uxbar(i,j)*countx(:,:) 
     362  !   imx_diag(:,:) = imx_diag_in(:,:) 
     363  !end where 
     364  !where (county(:,:).ge.2) 
     365  !   uybartemp(:,:)=uybar(:,:)*county(:,:) 
     366  !   imy_diag(:,:) = imx_diag_in(:,:) 
     367  !end where 
     368  ! afq -- 
     369   
     370  where (countx(:,:).ne.0) uxbar(:,:)= max(min(uxbartemp(:,:)/countx(:,:),1000.),-1000.) 
     371  where (county(:,:).ne.0) uybar(:,:)= max(min(uybartemp(:,:)/county(:,:),1000.),-1000.) 
     372            
    358373  do j= 3,ny-3 
    359374     do i=3,nx-3 
     
    433448         
    434449  if (xpos.LT.0..OR.xpos.GT.1.) then 
    435                 print*,'calc_xgl4schoof : xpos value error i,j=',i,j 
    436                 print*, 'xpos,Cgl', xpos,Cgl 
    437                 print*,'B_0, alpha, H_0, SL', B_0, alpha, H_0, SL 
    438                 print*,'archim=',B_1+H_1*alpha - SL 
    439                 !stop 
    440                 xpos = min(max(0.,xpos),1.) 
     450     print*,'calc_xgl4schoof : xpos value error i,j=',i,j 
     451     print*, 'xpos,Cgl', xpos,Cgl 
     452     print*,'B_0, alpha, H_0, SL', B_0, alpha, H_0, SL 
     453     print*,'archim=',B_1+H_1*alpha - SL 
     454     !stop 
     455     xpos = min(max(0.,xpos),1.) 
    441456  endif 
    442457         
Note: See TracChangeset for help on using the changeset viewer.